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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 23 21:16:35 UTC 2022


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

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

Name: VMMaker.oscog-eem.3199
Author: eem
Time: 23 June 2022, 2:16:20.958945 pm
UUID: 3866dedc-ccfd-4fc1-a487-85095ada8bba
Ancestors: VMMaker.oscog-eem.3198

Eliminate some printf format/parameter warnings, in particular by casting length parameters to int.

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

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 }.
  			 (objectMemory isBytesNonImm: s)
+ 				ifTrue: ['%P %.*s\n' f: transcript printf: { s asVoidPointer. objectMemory numBytesOfBytes: s. objectMemory firstIndexableField: s }]
- 				ifTrue: ['%P %.*s\n' f: transcript printf: { s asVoidPointer. (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: CoInterpreter>>printPrimLogEntryAt:hasParameter: (in category 'debug support') -----
  printPrimLogEntryAt: i hasParameter: hasParameter
  	<inline: false>
  	"print the entry and answer if it takes a parameter (as the following entry)"
  	| entryOop className length |
  	entryOop := primTraceLog at: i.
  	hasParameter ifTrue:
  		[(objectMemory addressCouldBeObj: entryOop)
  			ifTrue: [className := self nameOfClass: entryOop lengthInto: (self addressOf: length put: [:v| length := v])]
  			ifFalse: [className := 'bad class'. length := 9].
  		 '%.*s\n' f: transcript printf: { length. className }.
  		 ^false].
  	(objectMemory isImmediate: entryOop)
  		ifTrue:
  			[entryOop = TraceIncrementalGC ifTrue:
  				[self print: '**IncrementalGC**\n'. ^false].
  			 entryOop = TraceFullGC ifTrue:
  				[self print: '**FullGC**\n'. ^false].
  			 entryOop = TraceCodeCompaction ifTrue:
  				[self print: '**CompactCode**\n'. ^false].
  			 entryOop = TraceStackOverflow ifTrue:
  				[self print: '**StackOverflow**\n'. ^false].
  			 entryOop = TracePrimitiveFailure ifTrue:
  				[self print: '**PrimitiveFailure** '. ^true].
  			 entryOop = TracePrimitiveRetry ifTrue:
  				[self print: '**PrimitiveRetry**\n'. ^false].
  			 self print: '???\n']
  		ifFalse:
  			[(objectMemory addressCouldBeObj: entryOop)
+ 				ifFalse: ['%ld!!!!!!\n' f: transcript printf: i]
- 				ifFalse: ['%d!!!!!!\n' f: transcript printf: i]
  				ifTrue:
  					[(objectMemory isCompiledMethod: entryOop)
  						ifTrue:
  							[| methodClass methodSel |
  							 className := '???'. length := 3.
  							 methodClass := self safeMethodClassOf: entryOop.
  							 methodClass ~= objectMemory nilObject ifTrue:
  								[className := self nameOfClass: methodClass lengthInto: (self addressOf: length put: [:v| length := v])].
  							 methodSel := self findSelectorOfMethod: entryOop.
  							 methodSel = objectMemory nilObject
  								ifTrue:
  									['%.*s>>bad selector %p\n'
  										f: transcript
  										printf: { length. className. methodSel }]
  								ifFalse:
  									['%.*s>>#%.*s\n'
  										f: transcript
  										printf: { length. className.
  												objectMemory numBytesOfBytes: methodSel. objectMemory firstIndexableField: methodSel }]]
  						ifFalse: [objectMemory safePrintStringOf: entryOop. self cr]]].
  	^false!

Item was changed:
  ----- Method: Cogit>>warnMultiple:selectors: (in category 'debug printing') -----
  warnMultiple: cogMethod selectors: aSelectorOop
  	<inline: true>
  	<var: 'cogMethod' type: #'CogMethod *'>
  	 'Warning, attempt to use method with selector %.*s and selector %.*s\n'
  		f: #stderr
+ 		printf: {objectMemory numBytesOf: cogMethod selector.
+ 				objectMemory firstIndexableField: cogMethod selector.
+ 				objectMemory numBytesOf: aSelectorOop.
+ 				objectMemory firstIndexableField: aSelectorOop }!
- 		printf: {self cCoerceSimple: (objectMemory numBytesOf: cogMethod selector) to: #int.
- 				self cCoerceSimple: (objectMemory firstIndexableField: cogMethod selector) to: #'char *'.
- 				self cCoerceSimple: (objectMemory numBytesOf: aSelectorOop) to: #int.
- 				self cCoerceSimple: (objectMemory firstIndexableField: aSelectorOop) to: #'char *' }!

Item was changed:
  ----- Method: InterpreterPrimitives>>traceInputEvent: (in category 'I/O primitive support') -----
  traceInputEvent: evtBuf
  	<var: #evtBuf declareC: 'sqIntptr_t evtBuf[8]'>
  	| eventTypeNames |
  	eventTypeNames := self
  							cCoerce: #('None' 'Mouse' 'Keyboard' 'DragDropFiles' 'Menu' 'Window' 'Complex' 'MouseWheel' 'Plugin')
  							to: #'char **'.
+ 	'Event%s/%ld @ %u\t\t%ld/%x %ld/%x\n\t%ld/%x %ld/%x\t %ld/%x %p\n'
- 	'Event%s/%d @ %u\t\t%d/%x %d/%x\n\t%d/%x %d/%x\t %d/%x %p\n'
  		f: #stderr
  		printf: {	((evtBuf at: 0) between: 0 and: 8)
  						ifTrue: [eventTypeNames at: (evtBuf at: 0)]
  						ifFalse: ['?'].
  					evtBuf at: 0.
  					evtBuf at: 1. "timestamp"
  					evtBuf at: 2. evtBuf at: 2. evtBuf at: 3. evtBuf at: 3.
  					evtBuf at: 4. evtBuf at: 4. evtBuf at: 5. evtBuf at: 5.
  					evtBuf at: 6. evtBuf at: 6.
  					(evtBuf at: 7) asVoidPointer } "windowIndex"!

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
  		printf: { name. memField asVoidPointer. memField. length }.
  	length ~= 0 ifTrue:
+ 		['/%lu' f: coInterpreter getTranscript printf: length].
- 		['/%ld' f: coInterpreter getTranscript printf: length].
  	coInterpreter cr!

Item was added:
+ ----- Method: PrintfFormatDescriptor>>isNumberHolder (in category '*VMMaker-testing') -----
+ isNumberHolder
+ 	^false!

Item was added:
+ ----- Method: PrintfNumberHolderDescriptor>>isNumberHolder (in category '*VMMaker-testing') -----
+ isNumberHolder
+ 	^true!

Item was changed:
  ----- Method: SpurMemoryManager>>printOopsFrom:to: (in category 'debug printing') -----
  printOopsFrom: startAddress to: endAddress
  	<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"
  	| oop limit firstNonEntity inEmptySpace lastNonEntity |
  	oop := self objectBefore: startAddress.
  	limit := endAddress asUnsignedIntegerPtr min: endOfMemory.
  	oop := oop
  				ifNil: [startAddress]
  				ifNotNil: [(self objectAfter: oop) = startAddress
  							ifTrue: [startAddress]
  							ifFalse: [oop]].
  	inEmptySpace := false.
  	[self oop: oop isLessThan: limit] whileTrue:
  		[self printEntity: oop.
  		 [oop := self objectAfter: oop.
  		  (self long64At: oop) = 0] whileTrue:
  			[inEmptySpace ifFalse:
  				[inEmptySpace := true.
  				 firstNonEntity := oop].
  			 lastNonEntity := oop].
  		 inEmptySpace ifTrue:
  			[inEmptySpace := false.
  			 coInterpreter
+ 				print: 'skipped empty space from '; printHexnp: firstNonEntity;
+ 				print:' to '; printHexnp: lastNonEntity; cr.
- 				print: 'skipped empty space from '; printHexPtrnp: firstNonEntity;
- 				print:' to '; printHexPtrnp: lastNonEntity; cr.
  			 oop := self objectStartingAt: oop]]!

Item was changed:
  ----- Method: StackInterpreter>>printFrameThing:at: (in category 'debug printing') -----
  printFrameThing: name at: address
  	<inline: #always>
+ 	<var: #name type: #'char *'>
+ 	<var: #address type: #'char *'>
  	self printFrameThing: name at: address extraString: (self cCoerceSimple: nil to: #'char *')!

Item was changed:
  ----- Method: StackInterpreter>>printStackPage:useCount: (in category 'debug printing') -----
  printStackPage: page useCount: n
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	self print: 'page '; printHexPtrnp: (self cCode: [page] inSmalltalk: [page baseAddress]);
  		print: ' ('; printNum: (stackPages pageIndexFor: page realStackLimit).
  	n >= 0 ifTrue:
  		[self print: ','; printNum: n].
  	self print: ')  (trace: '; printNum: page trace; printChar: $).
  	(stackPages isFree: page) ifTrue:
  		[self print: ' (free)'].
  	page = stackPages mostRecentlyUsedPage ifTrue:
  		[self print: ' (MRU)'].
  	page prevPage = stackPages mostRecentlyUsedPage ifTrue:
  		[self print: ' (LRU)'].
  	self cr; tab; print: 'ba: ';
+ 		printHexPtrnp: page baseAddress; print: ' - sl: ';
+ 		printHexPtrnp: page realStackLimit; print: ' - sl-so: ';
+ 		printHexPtrnp: page realStackLimit - self stackLimitOffset; print: ' - la:';
+ 		printHexPtrnp: page lastAddress.
- 		printHex: page baseAddress; print: ' - sl: ';
- 		printHex: page realStackLimit; print: ' - sl-so: ';
- 		printHex: page realStackLimit - self stackLimitOffset; print: ' - la:';
- 		printHex: page lastAddress.
  	(stackPages isFree: page) ifFalse:
  		[self cr; tab; print: 'baseFP '; printHexPtrnp: page baseFP.
  		 self "cr;" tab; print: 'headFP '; printHexPtrnp: page headFP.
  		 self "cr;" tab; print: 'headSP '; printHexPtrnp: page headSP].
  	self cr; tab; print: 'prev '; printHexPtrnp: (self cCode: 'page->prevPage' inSmalltalk: [page prevPage baseAddress]);
  		print: ' ('; printNum: (stackPages pageIndexFor: page prevPage realStackLimit); printChar: $).
  	self tab; print: 'next '; printHexPtrnp: (self cCode: 'page->nextPage' inSmalltalk: [page nextPage baseAddress]);
  		print: ' ('; printNum: (stackPages pageIndexFor: page nextPage realStackLimit); printChar: $).
  	self cr!

Item was changed:
  ----- Method: TVarArgsSendNode>>transformPrintfFor:in: (in category 'transformations') -----
  transformPrintfFor: aTMethod in: aCodeGen
  	"Handle forms of f:printf: & printf:. f:printf: is either
  		logFile f: formatLiteral printf: args
  	 or
  		formatLiteral f: streamName printf: args
  	 printf is
  		formatLiteral printf: args"
+ 	| formatNode map newArgs fileParameterIndex |
- 	| map newArgs |
  	"precicely one of the arguments will be the format string. nodesDo: is top-down,
  	 left-to-right, so it will encounter the format string first."
  	map := Dictionary new.
  	self nodesDo:
  		[:subNode|
  		 (map isEmpty
  		  and: [subNode isConstant
  		  and: [subNode value isString and: [subNode value includes: $%]]]) ifTrue:
+ 			[map at: subNode put: (formatNode := subNode asPrintfFormatStringNode)]].
- 			[map at: subNode put: subNode asPrintfFormatStringNode]].
  	self replaceNodesIn: map.
  
  	"inline any brace of arguments..."
  	newArgs := OrderedCollection new.
  	arguments do:
  		[:arg|
  		arg isBrace
  			ifTrue: [newArgs addAllLast: arg elements]
  			ifFalse: [newArgs addLast: arg]].
  
+ 	fileParameterIndex := 0.
+ 	"ensure that the FILE * arg, if any, is first."
- 	"ensure that the FILE * arg is first"
  	selector first == $f ifTrue:
  		[| originalReceiver |
  		 "format string will either be receiver or first argument. Use type of FILE * argument
  		   to determine which. This is because of the pst: hook in frame printing."
  		 self assert: ((self isFileParameter: receiver for: aTMethod in: aCodeGen)
  					or: [self isFileParameter: arguments first for: aTMethod in: aCodeGen]).
  		 originalReceiver := receiver.
  		 receiver := TVariableNode new setName: 'self'.
  		(self isFileParameter: originalReceiver for: aTMethod in: aCodeGen)
  			ifTrue: "transcript f: fmt printf: args => self f: transcript printf: fmt _: args"
+ 				[newArgs addFirst: originalReceiver. fileParameterIndex := 1]
- 				[newArgs addFirst: originalReceiver]
  			ifFalse: "fmt f: transcript printf: args => self f: transcript printf: fmt _: args"
+ 				[newArgs add: originalReceiver afterIndex: 1. fileParameterIndex := 2]].
+ 
+ 	"Automatically cast length arguments to int to avoid compiler warnings."
+ 	formatNode notNil ifTrue:
+ 		[| format |
+ 		format := PrintfFormatString new setFormat: (formatNode value copyReplaceAll: '%WP' with: '%p').
+ 		newArgs withIndexDo:
+ 			[:paramNode :index| | formatDescriptor |
+ 			(index > fileParameterIndex
+ 			and: [(formatDescriptor := format nextFormat) notNil
+ 			and: [formatDescriptor isNumberHolder
+ 			and: [(paramNode typeOrNilFrom: aCodeGen in: aTMethod) ~= #int]]]) ifTrue:
+ 					[newArgs at: index put: (TSendNode new
+ 												setSelector: #signedIntFromLong
+ 												receiver: paramNode
+ 												arguments: #())]]].
+ 
- 				[newArgs add: originalReceiver afterIndex: 1]].
  	arguments := newArgs!



More information about the Vm-dev mailing list