[Vm-dev] VM Maker: VMMaker.oscog-nice.1728.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Mar 14 21:58:53 UTC 2016


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.1728.mcz

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

Name: VMMaker.oscog-nice.1728
Author: nice
Time: 14 March 2016, 10:56:44.166 pm
UUID: a993107d-99a8-411f-9fe6-310bb1cf5a67
Ancestors: VMMaker.oscog-eem.1726

Fix some printf format/argument mismatch.

Note: there is another mismatch in platforms sources that needs fixing::

--- platforms/unix/plugins/SocketPlugin/sqUnixSocket.c  (revision 3635)
+++ platforms/unix/plugins/SocketPlugin/sqUnixSocket.c  (working copy)
@@ -612,7 +612,7 @@
   if (-1 == newSocket)
     {
       /* socket() failed, or incorrect protocol type */
-      fprintf(stderr, "primSocketCreateRAW: socket() failed; protocol = %d, errno = %d\n", protocol, errno);
+      fprintf(stderr, "primSocketCreateRAW: socket() failed; protocol = %ld, errno = %d\n", protocol, errno);
       interpreterProxy->success(false);
       return;
     }

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

Item was changed:
  ----- Method: Cogit>>printPCMapPairsFor: (in category 'method map') -----
  printPCMapPairsFor: cogMethod
  	<api>
  	<var: 'cogMethod' type: #'CogMethod *'>
+ 	<var: 'mapByte' type: #'unsigned char'>
  	| mcpc map mapByte annotation value |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
  		[annotation := mapByte >> AnnotationShift.
  		 annotation = IsAnnotationExtension
  			ifTrue:
  				[value := (mapByte bitAnd: DisplacementMask) + IsSendCall]
  			ifFalse:
  				[value := annotation.
  				 mcpc := mcpc + (backEnd codeGranularity
  									* (annotation = IsDisplacementX2N
  										ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  										ifFalse: [mapByte bitAnd: DisplacementMask]))].
  		 coInterpreter
  			printHexnp: map;
  		 	print: ': '.
  		 self
  			cCode: [self print: '%02x' f: mapByte]
  			inSmalltalk:
  				[mapByte < 16 ifTrue:
  					[coInterpreter putchar: $0].
  				 coInterpreter printHexnp: mapByte].
  		 coInterpreter
  		 	printChar: $ ;
  			printNum: annotation;
  			print: ' ('.
  		 self cppIf: NewspeakVM
  			ifTrue:
  				[value
  					caseOf: {
  						[IsDisplacementX2N]		->	[coInterpreter print: 'IsDisplacementX2N'].
  						[IsAnnotationExtension]		->	[coInterpreter print: 'IsAnnotationExtension'].
  						[IsObjectReference]		->	[coInterpreter print: 'IsObjectReference'].
  						[IsAbsPCReference]		->	[coInterpreter print: 'IsAbsPCReference'].
  						[HasBytecodePC]			->	[coInterpreter print: 'HasBytecodePC'].
  						[IsRelativeCall]				->	[coInterpreter print: 'IsRelativeCall'].
  						[IsNSSendCall]				->	[coInterpreter print: 'IsNSSendCall'].
  						[IsSendCall]					->	[coInterpreter print: 'IsSendCall'].
  						[IsSuperSend]				->	[coInterpreter print: 'IsSuperSend'].
  						[IsDirectedSuperSend]		->	[coInterpreter print: 'IsDirectedSuperSend'].
  						[IsNSSelfSend]				->	[coInterpreter print: 'IsNSSelfSend'].
  						[IsNSDynamicSuperSend]	->	[coInterpreter print: 'IsNSDynamicSuperSend'].
  						[IsNSImplicitReceiverSend]	->	[coInterpreter print: 'IsNSImplicitReceiverSend'] }
  					otherwise: [coInterpreter print: '??? '; printHexnp: value]]
  			ifFalse:
  				[value
  					caseOf: {
  						[IsDisplacementX2N]		->	[coInterpreter print: 'IsDisplacementX2N'].
  						[IsAnnotationExtension]		->	[coInterpreter print: 'IsAnnotationExtension'].
  						[IsObjectReference]		->	[coInterpreter print: 'IsObjectReference'].
  						[IsAbsPCReference]		->	[coInterpreter print: 'IsAbsPCReference'].
  						[HasBytecodePC]			->	[coInterpreter print: 'HasBytecodePC'].
  						[IsRelativeCall]				->	[coInterpreter print: 'IsRelativeCall'].
  						[IsSendCall]					->	[coInterpreter print: 'IsSendCall'].
  						[IsSuperSend]				->	[coInterpreter print: 'IsSuperSend'].
  						[IsDirectedSuperSend]		->	[coInterpreter print: 'IsDirectedSuperSend'] }
  					otherwise: [coInterpreter print: '??? '; printHexnp: value]].
  		 coInterpreter
  			print: ') ';
  			printHexnp: (mapByte bitAnd: DisplacementMask);
  			printChar: $ ;
  			putchar: $@;
  		 printHex: mcpc;
  		 cr;
  		 flush.
  		 map := map - 1]!

Item was changed:
  ----- Method: Cogit>>trampolineName:numArgs:limit: (in category 'initialization') -----
  trampolineName: routinePrefix numArgs: numArgs limit: argsLimit
  	"Malloc a string with the contents for the trampoline table"
  	<inline: true>
  	<returnTypeC: #'char *'>
  	<var: #routinePrefix type: #'char *'>
+ 	<var: #numArgs type: #int>
  	| theString |
  	<var: #theString type: #'char *'>
  	self cCode: '' inSmalltalk:
  		[^routinePrefix, (numArgs <= argsLimit ifTrue: [numArgs printString] ifFalse: ['N']), 'Args'].
  	theString := self malloc: (self strlen: routinePrefix) + 6.
  	self s: theString pr: '%s%cArgs' in: routinePrefix tf: (numArgs <= argsLimit ifTrue: [$0 + numArgs] ifFalse: [$N]).
  	^theString!

Item was changed:
  ----- Method: StackInterpreter>>longPrintOop: (in category 'debug printing') -----
  longPrintOop: oop
  	<api>
  	| fmt lastIndex startIP bytecodesPerLine column |
  	((objectMemory isImmediate: oop)
  	 or: [(objectMemory addressCouldBeObj: oop) not
  	 or: [(oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  	 or: [(objectMemory isFreeObject: oop)
  	 or: [objectMemory isForwarded: oop]]]]) ifTrue:
  		[self printOop: oop.
  		 ^self].
  	self printHex: oop.
  	(objectMemory fetchClassOfNonImm: oop)
  		ifNil: [self print: ' has a nil class!!!!']
  		ifNotNil: [:class|
  			self print: ': a(n) '; printNameOfClass: class count: 5;
  				print: ' ('.
  			objectMemory hasSpurMemoryManagerAPI ifTrue:
  				[self printHexnp: (objectMemory compactClassIndexOf: oop); print: '=>'].
  			self printHexnp: class; print: ')'].
  	fmt := objectMemory formatOf: oop.
  	self print: ' format '; printHexnp: fmt.
  	fmt > objectMemory lastPointerFormat
  		ifTrue: [self print: ' nbytes '; printNum: (objectMemory numBytesOf: oop)]
  		ifFalse: [(objectMemory isIndexableFormat: fmt) ifTrue:
  					[| len |
  					len := objectMemory lengthOf: oop.
  					self print: ' size '; printNum: len - (objectMemory fixedFieldsOf: oop format: fmt length: len)]].
  	objectMemory printHeaderTypeOf: oop.
  	self print: ' hash '; printHexnp: (objectMemory rawHashBitsOf: oop).
  	self cr.
  	(fmt between: objectMemory firstByteFormat and: objectMemory firstCompiledMethodFormat - 1) ifTrue:
  		[^self printStringOf: oop; cr].
  	(fmt between: objectMemory firstLongFormat and: objectMemory firstByteFormat - 1) ifTrue:
  		[0 to: ((objectMemory num32BitUnitsOf: oop) min: 256) - 1 do:
  			[:i| | fieldOop |
  			fieldOop := objectMemory fetchLong32: i ofObject: oop.
  			self space; printNum: i; space; printHex: fieldOop; space; cr].
  		 ^self].
  	"this is nonsense.  apologies."
  	startIP := (objectMemory lastPointerOf: oop) + objectMemory bytesPerOop - objectMemory baseHeaderSize / objectMemory bytesPerOop.
  	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 cCode: [self printOopShort: fieldOop]
  							inSmalltalk: [self print: (self shortPrint: fieldOop)]].
  			self cr]].
  	(objectMemory isCompiledMethod: oop)
  		ifFalse:
  			[startIP > lastIndex ifTrue: [self print: '...'; cr]]
  		ifTrue:
  			[startIP := startIP * objectMemory wordSize + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 100 ifTrue:
  				[lastIndex := startIP + 100].
  			 bytecodesPerLine := 8.
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
+ 					[self cCode: 'printf("0x%08lx: ", oop+BaseHeaderSize+index-1)'
- 					[self cCode: 'printf("0x%08x: ", oop+BaseHeaderSize+index-1)'
  						inSmalltalk: [self print: (oop+objectMemory baseHeaderSize+index-1) hex; print: ': ']].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
+ 				self cCode: 'printf(" %02x/%-3d", (int)byte,(int)byte)'
- 				self cCode: 'printf(" %02x/%-3d", byte,byte)'
  					inSmalltalk: [self space; print: (byte radix: 16); printChar: $/; printNum: byte].
  				column := column + 1.
  				column > bytecodesPerLine ifTrue:
  					[column := 1. self cr]].
  			column = 1 ifFalse:
  				[self cr]]!

Item was changed:
  ----- Method: StackInterpreter>>printOop: (in category 'debug printing') -----
  printOop: oop
  	| cls fmt lastIndex startIP bytecodesPerLine column |
  	<inline: false>
  	(objectMemory isImmediate: oop) ifTrue:
  		[^self shortPrintOop: oop].
  	self printHex: oop.
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  						ifTrue: [' is misaligned']
  						ifFalse: [self whereIs: oop]); cr].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[self print: ' is a free chunk of size '; printNum: (objectMemory sizeOfFree: oop).
  		 objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[self print: ' 0th: '; printHex: (objectMemory fetchPointer: 0 ofFreeChunk: oop).
  			 objectMemory printHeaderTypeOf: oop].
  		 ^self cr].
  	(objectMemory isForwarded: oop) ifTrue:
  		[self
  			print: ' is a forwarded object to '; printHex: (objectMemory followForwarded: oop);
  			print: ' of slot size '; printNum: (objectMemory numSlotsOfAny: oop).
  		 objectMemory printHeaderTypeOf: oop.
  		 ^self cr].
  	self print: ': a(n) '.
  	self printNameOfClass: (cls := objectMemory fetchClassOfNonImm: oop) count: 5.
  	cls = (objectMemory splObj: ClassFloat) ifTrue:
  		[^self cr; printFloat: (objectMemory dbgFloatValueOf: oop); cr].
  	fmt := objectMemory formatOf: oop.
  	fmt > objectMemory lastPointerFormat ifTrue:
  		[self print: ' nbytes '; printNum: (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:
  			[self print: ' datasize '; printNum: (self sizeOfAlienData: oop).
  			self print: ((self isIndirectAlien: oop)
  							ifTrue: [' indirect @ ']
  							ifFalse:
  								[(self isPointerAlien: oop)
  									ifTrue: [' pointer @ ']
  									ifFalse: [' direct @ ']]).
  			 ^self printHex: (self startOfAlienData: oop) asUnsignedInteger; cr].
  		 (objectMemory isWords: oop) ifTrue:
  			[lastIndex := 64 min: ((objectMemory numBytesOf: oop) / objectMemory wordSize).
  			 lastIndex > 0 ifTrue:
  				[1 to: lastIndex do:
  					[:index|
  					self space; printHex: (objectMemory fetchLong32: index - 1 ofObject: oop).
  					(index \\ self elementsPerPrintOopLine) = 0 ifTrue:
  						[self cr]].
  				(lastIndex \\ self elementsPerPrintOopLine) = 0 ifFalse:
  					[self cr]].
  			^self].
  		^self printStringOf: oop; cr].
  	"this is nonsense.  apologies."
  	startIP := (objectMemory lastPointerOf: oop) + objectMemory bytesPerOop - objectMemory baseHeaderSize / objectMemory bytesPerOop.
  	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 := startIP * objectMemory wordSize + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 100 ifTrue:
  				[lastIndex := startIP + 100].
  			 bytecodesPerLine := 8.
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
+ 					[self cCode: 'printf("0x%08lx: ", oop+BaseHeaderSize+index-1)'
- 					[self cCode: 'printf("0x%08x: ", oop+BaseHeaderSize+index-1)'
  						inSmalltalk: [self print: (oop+objectMemory baseHeaderSize+index-1) hex; print: ': ']].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
+ 				self cCode: 'printf(" %02x/%-3d", (int)byte,(int)byte)'
- 				self cCode: 'printf(" %02x/%-3d", byte,byte)'
  					inSmalltalk: [self space; print: (byte radix: 16); printChar: $/; printNum: byte].
  				column := column + 1.
  				column > bytecodesPerLine ifTrue:
  					[column := 1. self cr]].
  			column = 1 ifFalse:
  				[self cr]]!



More information about the Vm-dev mailing list