[Vm-dev] VM Maker: VMMaker.oscog-eem.3101.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Nov 15 05:04:37 UTC 2021


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.3101.mcz

==================== Summary ====================

Name: VMMaker.oscog-eem.3101
Author: eem
Time: 14 November 2021, 9:04:23.449192 pm
UUID: 343b46dc-8e9f-48c8-bb97-74b76f1d07cc
Ancestors: VMMaker.oscog-eem.3100

Tidy-up VMMaker.oscog-eem.3100.  Fix several C compiler warnings.  Don't translate non-long format specifiers into the PRI?SQINT form.  For Slang C typing clients outside of StackInterpreter must send getTranscript, not transcript.

Note to self: It would be nice to have TVarArgsSendNode add casts to arguments for printfs.  Fairly easy to do.

=============== Diff against VMMaker.oscog-eem.3100 ===============

Item was changed:
  ----- Method: CoInterpreter>>printFrameFlagsForFP: (in category 'debug printing') -----
  printFrameFlagsForFP: theFP
- 	| address it |
- 	<inline: false>
  	<var: #theFP type: #'char *'>
+ 	<inline: false>
+ 	| address it |
  	<var: #address type: #'char *'>
  	(self isMachineCodeFrame: theFP)
  		ifTrue:
  			[address := theFP + FoxMethod.
  			it := (stackPages longAt: address) bitAnd: 16r7]
  		ifFalse:
  			[address := theFP + FoxIFrameFlags.
  			 it := stackPages longAt: address].
+ 	self printFrameAddress: address.
+ 	'%3sfrm flags: %p'
+ 		f: transcript
+ 		printf: { (self isMachineCodeFrame: theFP) ifTrue: ['mc'] ifFalse: ['int'].
+ 				it asVoidPointer }.
- 	self printFrameAddress: address;
- 		print: ((self isMachineCodeFrame: theFP)
- 				ifTrue: [' mcfrm flags: ']
- 				ifFalse: ['intfrm flags: ']);
- 		printHex: it.
  	it ~= 0 ifTrue:
+ 		['=%d' f: transcript printf: (self cCoerceSimple: it to: #int)].
- 		[self printChar: $=; printNum: it].
  	'  numArgs: %d %sContext %sBlock\n'
  		f: transcript
+ 		printf: { self cCoerceSimple: (self frameNumArgs: theFP) to: #int.
- 		printf: { self frameNumArgs: theFP.
  				(self frameHasContext: theFP) ifTrue: ['is'] ifFalse: ['no'].
  				(self frameIsBlockActivation: theFP) ifTrue: ['is'] ifFalse: ['not'] }!

Item was changed:
  ----- Method: CoInterpreter>>printFrameMethodFor: (in category 'debug printing') -----
  printFrameMethodFor: theFP
  	<var: #theFP type: #'char *'>
  	<var: #address type: #'char *'>
  	<inline: false>
+ 	| address it |
- 	| address it homeMethod obj |
  	address := theFP + FoxMethod.
  	it := stackPages longAt: address.
  	self printFrameAddress: address.
  	(self pst: '      method: %WP\t') f: transcript printf: it asVoidPointer.
  	((self isMachineCodeFrame: theFP)
  	 and: [self mframeIsBlockActivation: theFP]) ifTrue:
+ 		['hm: %P\t' f: transcript printf: (self mframeHomeMethod: theFP) asVoidPointer].
+ 	self shortPrintOop: (self frameMethodObject: theFP)!
- 		[homeMethod := self mframeHomeMethod: theFP.
- 		 'hm: %P\t' f: transcript printf: homeMethod asInteger].
- 	obj := self frameMethodObject: theFP.
- 	self shortPrintOop: obj!

Item was changed:
  ----- Method: CoInterpreter>>printMethodCacheFor: (in category 'debug printing') -----
  printMethodCacheFor: thing
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| n |
  	n := 0.
  	0 to: MethodCacheSize - 1 by: MethodCacheEntrySize do:
  		[:i | | s c m p |
  		s := methodCache at: i + MethodCacheSelector.
  		c := methodCache at: i + MethodCacheClass.
  		m := methodCache at: i + MethodCacheMethod.
  		p := methodCache at: i + MethodCachePrimFunction.
  		((thing = -1 or: [s = thing or: [c = thing or: [p = thing or: [m = thing
  			or: [(objectMemory addressCouldBeObj: m)
  				and: [(self maybeMethodHasCogMethod: m)
  				and: [(self cogMethodOf: m) asInteger = thing]]]]]]])
  		 and: [(objectMemory addressCouldBeOop: s)
  		 and: [c ~= 0
  		 and: [(self addressCouldBeClassObj: c)
  			or: [self addressCouldBeClassObj: (objectMemory classForClassTag: c)]]]]) ifTrue:
  			[n := n + 1.
  			 self cCode: [] inSmalltalk: [self transcript ensureCr].
+ 			 '%ld %lx\n\t' f: transcript printf: { i. i }.
- 			 self printNum: i; space; printHexnp: i; cr; tab.
  			 (objectMemory isBytesNonImm: s)
+ 				ifTrue: ['%P %.*s\n' f: transcript printf: { s asVoidPointer. (objectMemory numBytesOfBytes: s) signedIntFromLong. objectMemory firstIndexableField: s }]
- 				ifTrue: ['%p %.*s\n' f: transcript printf: { s. (objectMemory numBytesOfBytes: s) signedIntFromLong. objectMemory firstIndexableField: s }]
  				ifFalse: [self shortPrintOop: s].
  			 self tab.
  			 (self addressCouldBeClassObj: c)
  				ifTrue: [self shortPrintOop: c]
  				ifFalse: [self printNum: c; space; printHexnp: c; space; shortPrintOop: (objectMemory classForClassTag: c)].
  			self tab; shortPrintOop: m; tab.
  			self cCode:
  					[p > 1024
  						ifTrue: [self printHexnp: p]
  						ifFalse: [self printNum: p]]
  				inSmalltalk:
  					[p isSymbol ifTrue: [self print: p] ifFalse: [self printNum: p]].
  			self cr]].
  	n > 1 ifTrue:
  		[self printNum: n; cr]!

Item was changed:
  ----- Method: NewObjectMemory>>printMemField:name:size: (in category 'debug printing') -----
  printMemField: memField name: name size: length
  	<var: #memField type: #usqInt>
  	<var: #name type: #'char *'>
  	'%s\t%P/%ld sz: %p'
+ 		f: coInterpreter getTranscript
- 		f: coInterpreter transcript
  		printf: { name. memField asVoidPointer. memField. length }.
  	length ~= 0 ifTrue:
+ 		['/%ld' f: coInterpreter getTranscript printf: length].
- 		['/%ld' f: coInterpreter transcript printf: length].
  	coInterpreter cr!

Item was changed:
  ----- Method: ObjectMemory>>printFreeObject:on: (in category 'debug printing') -----
  printFreeObject: oop on: aStream
  	<var: 'aStream' type: #'FILE *'>
+ 	<inline: false>
  	'%P is a free chunk of size %ld\n'
  		f: aStream
  		printf: {oop asVoidPointer. self sizeOfFree: oop}!

Item was changed:
  ----- Method: PrintfNumberFormatDescriptor>>transformForVMMaker (in category '*VMMaker-C code generation') -----
  transformForVMMaker
  	operator == $P ifTrue:
  		[^'%', (width = 0 ifTrue: [''] ifFalse: [(width - 1) printString]), 'p'].
+ 	(lengthModifier == $l
+ 	 and: ['duxX' includes: operator]) ifTrue:
- 	('duxX' includes: operator) ifTrue:
  		[^'%',
  			(width = 0 ifTrue: [''] ifFalse: [(width - 1) printString]),
  			'" PRI',
  			(String with: operator),
  			'SQINT "'].
  	^super transformForVMMaker!

Item was changed:
  ----- Method: SpurMemoryManager>>printForwarder:on: (in category 'debug printing interpreter support') -----
  printForwarder: oop on: aStream
  	<var: 'aStream' type: #'FILE *'>
+ 	<inline: false>
  	'%P is a forwarded hdr%d slot size %ud object to %P\n'
  		f: aStream
  		printf: { oop asVoidPointer.
+ 				(self hasOverflowHeader: oop) ifTrue: [16] ifFalse: [8].
- 				(self rawNumSlotsOf: oop) = self numSlotsMask ifTrue: [16] ifFalse: [8].
  				self numSlotsOfAny: oop.
+ 				(self followForwarded: oop) asVoidPointer}!
- 				self objectMemory followForwarded: oop}!

Item was changed:
  ----- Method: SpurMemoryManager>>printFreeObject:on: (in category 'debug printing') -----
  printFreeObject: oop on: aStream
  	<var: 'aStream' type: #'FILE *'>
+ 	<inline: false>
  	'%P is a free chunk of size %ld 0th field:%P\n'
  		f: aStream
+ 		printf: {oop asVoidPointer. self bytesInBody: oop. (self fetchPointer: 0 ofFreeChunk: oop) asVoidPointer }!
- 		printf: {oop asVoidPointer. self bytesInBody: oop. self fetchPointer: 0 ofFreeChunk: oop }!

Item was changed:
  ----- Method: SpurMemoryManager>>printHeaderOf: (in category 'debug printing') -----
  printHeaderOf: objOop
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	"N.B. No safety bounds checks!!!!  We need to look e.g. at corpses."
  	coInterpreter printHexnp: objOop.
+ 	(self hasOverflowHeader: objOop)
- 	(self numSlotsOfAny: objOop) >= self numSlotsMask
  		ifTrue: [coInterpreter
  					print: ' hdr16 slotf '; printHexnp: (self numSlotsOfAny: objOop - self allocationUnit);
  					print: ' slotc '; printHexnp: (self rawOverflowSlotsOf: objOop); space]
  		ifFalse: [coInterpreter print: ' hdr8 slots '; printHexnp: (self numSlotsOfAny: objOop)].
  	coInterpreter
  		space;
  		printChar: ((self isMarked: objOop) ifTrue: [$M] ifFalse: [$m]);
  		printChar: ((self isGrey: objOop) ifTrue: [$G] ifFalse: [$g]);
  		printChar: ((self isPinned: objOop) ifTrue: [$P] ifFalse: [$p]);
  		printChar: ((self isRemembered: objOop) ifTrue: [$R] ifFalse: [$r]);
  		printChar: ((self isImmutable: objOop) ifTrue: [$I] ifFalse: [$i]);
  		print: ' hash '; printHexnp: (self rawHashBitsOf: objOop);
  		print: ' fmt '; printHexnp: (self formatOf: objOop);
  		print: ' cidx '; printHexnp: (self classIndexOf: objOop);
  		cr!

Item was changed:
  ----- Method: SpurMemoryManager>>printNonPointerDataOf:on: (in category 'debug printing interpreter support') -----
  printNonPointerDataOf: oop on: aStream
  	<var: 'aStream' type: #'FILE *'>
  	| elementsPerLine format lastIndex |
  	format := self formatOf: oop.
  	self assert: (format between: self sixtyFourBitIndexableFormat and: self firstCompiledMethodFormat - 1).
  	lastIndex := self lengthOf: oop format: format.
  	lastIndex = 0 ifTrue:
  		[^self].
  	format = self sixtyFourBitIndexableFormat ifTrue:
  		[lastIndex := 32 min: lastIndex.
  		 elementsPerLine := 4. "0x/16r0123456789ABCDEF<space|cr> x 4 = 76/80"
  		 1 to: lastIndex do:
  			[:index|
  			'%19P%c' f: aStream printf: {
  				self cCoerceSimple: (self fetchLong64: index - 1 ofObject: oop) to: #usqLong.
  				(index \\ elementsPerLine = 0 or: [index = lastIndex])
  					ifTrue: [Character cr] ifFalse: [Character space] }].
  		 ^self].
  	format < self firstShortFormat ifTrue:
  		[lastIndex := 64 min: lastIndex.
  		 elementsPerLine := 8. "0x/16r12345678<space|cr> x 8 = 80/88"
  		1 to: lastIndex do:
  			[:index|
  			'%11P%c' f: aStream printf: {
+ 				(self fetchLong32: index - 1 ofObject: oop) asVoidPointer.
- 				self cCoerceSimple: (self fetchLong32: index - 1 ofObject: oop) to: #unsigned.
  				(index \\ elementsPerLine = 0 or: [index = lastIndex])
  					ifTrue: [Character cr] ifFalse: [Character space] }].
  		 ^self].
  	format < self firstByteFormat ifTrue:
  		[lastIndex := 128 min: lastIndex.
  		 elementsPerLine := 10. "0x/16r1234<space|cr> x 10 = 70/80"
  		1 to: lastIndex do:
  			[:index|
  			'%7P%c' f: aStream printf: {
+ 				(self fetchShort16: index - 1 ofObject: oop)  asVoidPointer.
- 				self fetchShort16: index - 1 ofObject: oop.
  				(index \\ elementsPerLine = 0 or: [index = lastIndex])
  					ifTrue: [Character cr] ifFalse: [Character space] }].
  		 ^self].
  	lastIndex := 256 min: lastIndex.
  	elementsPerLine := 16. "0x/16r12<space|cr> x 16 = 80/96"
  	1 to: lastIndex do:
  		[:index|
  		'%5P%c' f: aStream printf: {
+ 			(self fetchByte: index - 1 ofObject: oop) asVoidPointer.
- 			self fetchByte: index - 1 ofObject: oop.
  			(index \\ elementsPerLine = 0 or: [index = lastIndex])
  				ifTrue: [Character cr] ifFalse: [Character space] }]!

Item was changed:
  ----- Method: StackInterpreter>>longPrintOop: (in category 'debug printing') -----
  longPrintOop: oop
  	<export: true> "useful for VM debugging; use export: not api, so it will be accessible on win32 and won't be written to cointerp.h"
  	| fmt lastIndex startIP column cls |
  
  	(objectMemory isImmediate: oop) ifTrue:
  		[^objectMemory printImmediateObject: oop on: transcript].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^objectMemory printCantBeObject: oop on: transcript].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[^objectMemory printFreeObject: oop on: transcript].
  	 (objectMemory isForwarded: oop) ifTrue:
  		[^objectMemory printForwarder: oop on: transcript].
  	
  	(cls := objectMemory fetchClassOfNonImm: oop)
  		ifNil: ['%P has a nil class!!!!\n' f: transcript printf: oop asVoidPointer]
  		ifNotNil:
  			[| className length |
  			className := self nameOfClass: cls lengthInto: (self addressOf: length put: [:v| length := v]).
+ 			'%P: a(n) %.*s' f: transcript printf: {oop asVoidPointer. length. className }.
- 			'%P: a(n) %.*s' f: transcript printf: {oop. length. className }.
  			objectMemory hasSpurMemoryManagerAPI ifTrue:
  				['(%lx=>%P)' f: transcript printf: { objectMemory compactClassIndexOf: oop. cls asVoidPointer }]].
  	fmt := objectMemory formatOf: oop.
  	' format %lx' f: transcript printf: fmt.
  	fmt > objectMemory lastPointerFormat
  		ifTrue: [' nbytes %ld' f: transcript printf:  (objectMemory numBytesOf: oop)]
  		ifFalse: [(objectMemory isIndexableFormat: fmt) ifTrue:
  					[| len |
  					len := objectMemory lengthOf: oop.
  					' size %ld' f: transcript printf: len - (objectMemory fixedFieldsOf: oop format: fmt length: len)]].
  	objectMemory printHeaderTypeOf: oop on: transcript.
  	self print: ' hash '; printHex: (objectMemory rawHashBitsOf: oop).
  	self cr.
  	(fmt between: objectMemory firstLongFormat and: objectMemory firstCompiledMethodFormat - 1) ifTrue:
  		["This will answer false if splObj: ClassAlien is nilObject"
  		 (self is: oop KindOfClass: (objectMemory splObj: ClassAlien)) ifTrue:
  			[^' datasize %ld %s @ %p\n' f: transcript printf:
  				{objectMemory sizeFieldOfAlien: oop.
  				  (self isIndirectAlien: oop)
  							ifTrue: ['indirect']
  							ifFalse:
  								[(self isPointerAlien: oop)
  									ifTrue: ['pointer']
  									ifFalse: ['direct']].
  				 self startOfAlienData: oop }].
  		(self is: oop KindOfClass: (self superclassOf: (objectMemory splObj: ClassString))) ifTrue:
  			[^objectMemory printStringDataOf: oop on: transcript].
  		 ^objectMemory printNonPointerDataOf: oop on: transcript].
  	startIP := fmt >= objectMemory firstCompiledMethodFormat
  				ifTrue: [(self startPCOfMethod: oop) / objectMemory wordSize]
  				ifFalse: [objectMemory numSlotsOf: oop].
  	lastIndex := 256 min: startIP.
  	lastIndex > 0 ifTrue:
  		[1 to: lastIndex do:
  			[:i| | fieldOop |
  			fieldOop := objectMemory fetchPointer: i - 1 ofObject: oop.
  			self space; printNum: i - 1; space; printHex: fieldOop; space.
  			(i = 1 and: [objectMemory isCompiledMethod: oop])
  				ifTrue: [self printMethodHeaderOop: fieldOop]
  				ifFalse: [self printOopShortInner: fieldOop].
  			self cr]].
  	(objectMemory isCompiledMethod: oop)
  		ifFalse:
  			[startIP > lastIndex ifTrue: [self print: '...'; cr]]
  		ifTrue:
  			[startIP := (self startPCOfMethod: oop) + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 256 ifTrue:
  				[lastIndex := startIP + 256].
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
  					['%11P' f: transcript printf: (oop+BaseHeaderSize+index-1) asVoidPointer].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
  				'%02x/%-3d%c'
  					f: transcript
  					printf: { byte. byte. column = 8 ifTrue: [Character cr] ifFalse: [Character space] }.
  				(column := column + 1) > 8 ifTrue: [column := 1]].
  			(objectMemory lengthOf: oop) > lastIndex ifTrue:
  				[self print: '...'].
  			(column between: 2 and: 7) ifTrue:
  				[self cr]]!

Item was changed:
  ----- Method: StackInterpreter>>printFloat: (in category 'debug printing') -----
  printFloat: f
+ 	<var: 'f' type: #double>
+ 	<inline: #always>
  	'%g' f: transcript printf: f!

Item was changed:
  ----- Method: StackInterpreter>>printFrameThing:at:extraString: (in category 'debug printing') -----
  printFrameThing: name at: address extraString: extraStringOrNil
+ 	<var: 'name' type: #'char *'>
+ 	<var: 'address' type: #'char *'>
+ 	<var: 'extraStringOrNil' type: #'char *'>
- 	<var: #name type: #'char *'>
- 	<var: #address type: #'char *'>
  	<inline: false>
  	| it |
  	it := stackPages longAt: address.
  	self printFrameAddress: address.
+ 	(self pst: '%12s: %WP') f: transcript printf: {name. it asVoidPointer }.
- 	(self pst: '%12s: %WP') f: transcript printf: {name. it }.
  	self framePrintDescription: it.
  	extraStringOrNil ifNotNil: ['%s' f: transcript printf: extraStringOrNil].
  	self cr!

Item was changed:
  ----- Method: StackInterpreter>>printOop: (in category 'debug printing') -----
  printOop: oop
  	<export: true> "use export: not api, so it won't be written to cointerp.h"
  	| cls fmt lastIndex startIP bytecodesPerLine column className length |
  	<inline: false>
  	(objectMemory isImmediate: oop) ifTrue:
  		[^objectMemory printImmediateObject: oop on: transcript].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^objectMemory printCantBeObject: oop on: transcript].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[^objectMemory printFreeObject: oop on: transcript].
  	 (objectMemory isForwarded: oop) ifTrue:
  		[^objectMemory printForwarder: oop on: transcript].
  	
  	(cls := objectMemory fetchClassOfNonImm: oop) ifNil:
+ 		[^'%P has a nil class!!!!\n' f: transcript printf: oop asVoidPointer].
- 		[^'%P has a nil class!!!!\n' f: transcript printf: oop].
  	className := self nameOfClass: cls lengthInto: (self addressOf: length put: [:v| length := v]).
+ 	'%P: a(n) %.*s' f: transcript printf: {oop asVoidPointer. length. className }.
- 	'%P: a(n) %.*s' f: transcript printf: {oop. length. className }.
  	cls = (objectMemory splObj: ClassFloat) ifTrue:
  		[^'\n%g\n' f: transcript printf: (objectMemory dbgFloatValueOf: oop)].
  	fmt := objectMemory formatOf: oop.
  	fmt > objectMemory lastPointerFormat ifTrue:
  		[' nbytes %ld' f: transcript printf: (objectMemory numBytesOf: oop)].
  	self cr.
  	(fmt between: objectMemory firstLongFormat and: objectMemory firstCompiledMethodFormat - 1) ifTrue:
  		["This will answer false if splObj: ClassAlien is nilObject"
  		 (self is: oop KindOfClass: (objectMemory splObj: ClassAlien)) ifTrue:
  			[^' datasize %ld %s @ %p\n' f: transcript printf:
  				{objectMemory sizeFieldOfAlien: oop.
  				  (self isIndirectAlien: oop)
  							ifTrue: ['indirect']
  							ifFalse:
  								[(self isPointerAlien: oop)
  									ifTrue: ['pointer']
  									ifFalse: ['direct']].
+ 				 self startOfAlienData: oop }].
- 				 (self startOfAlienData: oop) asUnsignedInteger }].
  		(self is: oop KindOfClass: (self superclassOf: (objectMemory splObj: ClassString))) ifTrue:
  			[^objectMemory printStringDataOf: oop on: transcript].
  		 ^objectMemory printNonPointerDataOf: oop on: transcript].
  	startIP := fmt >= objectMemory firstCompiledMethodFormat
  				ifTrue: [(self startPCOfMethod: oop) / objectMemory wordSize]
  				ifFalse: [objectMemory numSlotsOf: oop].
  	lastIndex := 256 min: startIP.
  	lastIndex > 0 ifTrue:
  		[1 to: lastIndex do:
  			[:index|
  			self cCode: [self printHex: (objectMemory fetchPointer: index - 1 ofObject: oop); space]
  				inSmalltalk: [self space; printHex: (objectMemory fetchPointer: index - 1 ofObject: oop); space.
  							 self print: (self shortPrint: (objectMemory fetchPointer: index - 1 ofObject: oop))].
  			(index \\ self elementsPerPrintOopLine) = 0 ifTrue:
  				[self cr]].
  		(lastIndex \\ self elementsPerPrintOopLine) = 0 ifFalse:
  			[self cr]].
  	(objectMemory isCompiledMethod: oop)
  		ifFalse:
  			[startIP > 64 ifTrue: [self print: '...'; cr]]
  		ifTrue:
  			[startIP := (self startPCOfMethod: oop) + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 256 ifTrue:
  				[lastIndex := startIP + 256].
  			 bytecodesPerLine := 8.
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
  					['%11P' f: transcript printf: (oop+BaseHeaderSize+index-1) asVoidPointer].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
  				' %02x/%-3d' f: transcript printf: { self cCoerceSimple: byte to: #int. self cCoerceSimple: byte to: #int }.
  				column := column + 1.
  				column > bytecodesPerLine ifTrue:
  					[column := 1. self cr]].
  			(objectMemory lengthOf: oop) > lastIndex ifTrue:
  				[self print: '...'].
  			column = 1 ifFalse:
  				[self cr]]!



More information about the Vm-dev mailing list