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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 3 03:10:08 UTC 2016


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

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

Name: VMMaker.oscog-eem.1705
Author: eem
Time: 2 March 2016, 7:08:07.484944 pm
UUID: 47d289d4-7673-412f-95a2-c2633e2b0181
Ancestors: VMMaker.oscog-eem.1704

Fix immutability suport in the Cogit by making sure that the Slang output for the bytecode generatorTable marks inst var store bytecode generators as mapped if IMMUTABILITY is set.

Change vm parameter 65 to be a set of flags, not merely the boolean for MULTIPLE_BYTECODE_SETS, and make the flags answer MULTIPLE_BYTECODE_SETS & IMMUTABILITY.

Add a PC map printer to the Cogit (used to debug the above issue).  Make the current image facade support more of the printing api so that the map printer can be tested in-image.

Nuke an obsolete method.

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

Item was changed:
  ----- Method: CogBytecodeDescriptor>>isMapped (in category 'accessing') -----
  isMapped
+ 	"Answer the value of isMapped.  Note we send value because this may be the binding for #IMMUTABILITY"
+ 	^isMapped value!
- 	"Answer the value of isMapped"
- 
- 	^isMapped!

Item was changed:
  ----- Method: CogBytecodeDescriptor>>printCInitializerOn:in: (in category 'translation') -----
  printCInitializerOn: aStream in: aCCodeGenerator
  	<doNotGenerate>
  	| first |
  	first := true.
  	aStream nextPut: ${; space.
  	self class instVarNamesAndTypesForTranslationDo:
  		[:ivn :type| | value |
  		first ifTrue: [first := false] ifFalse: [aStream nextPut: $,; space].
  		value := self instVarNamed: ivn.
+ 		value isVariableBinding
+ 			ifTrue: [aStream nextPutAll: value key]
+ 			ifFalse:
+ 				[(#(#'unsigned char' #'signed char' #('unsigned' ' : 1')) includes: type)
+ 					ifTrue: [value isInteger
+ 								ifTrue: [ivn = 'opcode'
+ 											ifTrue: [aStream nextPutAll: (CogRTLOpcodes nameForOpcode: value)]
+ 											ifFalse: [aStream print: value]]
+ 								ifFalse: [aStream nextPut: ((value notNil and: [value]) ifTrue: [$1] ifFalse: [$0])]]
+ 					ifFalse: [(false and: [#('spanFunction' 'isBackwardBranchFunction') includes: ivn]) ifTrue:
+ 								[aStream nextPut: $(; nextPutAll: type first; nextPutAll: type last; nextPut: $)].
+ 							aStream nextPutAll: (value
+ 													ifNotNil: [aCCodeGenerator cFunctionNameFor: value]
+ 													ifNil: ['0'])]]].
- 		(#(#'unsigned char' #'signed char' #('unsigned' ' : 1')) includes: type)
- 			ifTrue: [value isInteger
- 						ifTrue: [ivn = 'opcode'
- 									ifTrue: [aStream nextPutAll: (CogRTLOpcodes nameForOpcode: value)]
- 									ifFalse: [aStream print: value]]
- 						ifFalse: [aStream nextPut: ((value notNil and: [value]) ifTrue: [$1] ifFalse: [$0])]]
- 			ifFalse: [(false and: [#('spanFunction' 'isBackwardBranchFunction') includes: ivn]) ifTrue:
- 						[aStream nextPut: $(; nextPutAll: type first; nextPutAll: type last; nextPut: $)].
- 					aStream nextPutAll: (value
- 											ifNotNil: [aCCodeGenerator cFunctionNameFor: value]
- 											ifNil: ['0'])]].
  	aStream space; nextPut: $}!

Item was removed:
- ----- Method: Cogit class>>bytecodeTable (in category 'translation') -----
- bytecodeTable
- 	| selectors |
- 	selectors := Set new.
- 	generatorTable object do:
- 		[:bytecodeDescriptor|
- 		selectors add: bytecodeDescriptor generator.
- 		bytecodeDescriptor spanFunction ifNotNil:
- 			[selectors add: bytecodeDescriptor spanFunction]].
- 	^selectors!

Item was changed:
  ----- Method: Cogit class>>generatorTableFrom: (in category 'class initialization') -----
  generatorTableFrom: anArray
  	| blockCreationBytecodeSize |
  	generatorTable := CArrayAccessor on: (Array new: 256).
  	anArray do:
  		[:tuple| | descriptor |
  		(descriptor := CogBytecodeDescriptor new)
  						numBytes: tuple first;
  						generator: tuple fourth;
  						isReturn: (tuple includes: #return);
+ 						isMapped: ((tuple includes: #isMappedIfImmutability)
+ 										ifTrue: [self bindingOf: #IMMUTABILITY]
+ 										ifFalse: [tuple includes: #isMapped]);
- 						isMapped: ((tuple includes: #isMapped) or: [IMMUTABILITY and: [ tuple includes: #isMappedIfImmutability]]);
  						isMappedInBlock: (tuple includes: #isMappedInBlock);
  						isBlockCreation: (tuple includes: #block);
  						spanFunction: (((tuple includes: #block) or: [(tuple includes: #branch)]) ifTrue:
  										[tuple detect: [:thing| thing isSymbol and: [thing numArgs = 4]]]);
  						isBranchTrue: (tuple includes: #isBranchTrue);
  						isBranchFalse: (tuple includes: #isBranchFalse);
  						isExtension: (tuple includes: #extension);
  						isInstVarRef: (tuple includes: #isInstVarRef);	"for Spur"
  						hasIRC: (tuple includes: #hasIRC);			"for Newspeak"
  						yourself.
  		"As a hack to cut down on descriptor flags, use opcode to tag unusedBytecode for scanning.
  		 Currently descriptors are exactly 16 bytes with all 8 flag bits used (in Newspeak at least 17 bytes,
  		 9 flag bits).  As another hack to eliminate a test in scanMethod mark unknowns as extensions."
  		descriptor generator == #unknownBytecode ifTrue:
  			[descriptor opcode: Nop; isExtension: true].
  		descriptor isBlockCreation ifTrue:
  			[blockCreationBytecodeSize
  				ifNil: [blockCreationBytecodeSize := descriptor numBytes]
  				ifNotNil: [self assert: blockCreationBytecodeSize = descriptor numBytes]].
  		tuple do:
  			[:thing|
  			thing isSymbol ifTrue:
  				[(thing beginsWith: #needsFrame) ifTrue:
  					[descriptor needsFrameFunction: thing].
  				 (CogRTLOpcodes classPool at: thing ifAbsent: []) ifNotNil:
  					[:opcode| descriptor opcode: opcode]]].
  		tuple last isInteger
  			ifTrue: [descriptor stackDelta: tuple last]
  			ifFalse:
  				[descriptor needsFrameFunction ifNotNil:
  					[self error: 'frameless block bytecodes must specify a stack delta']].
  		tuple second to: tuple third do:
  			[:index|
  			generatorTable at: index put: descriptor]].
  	BlockCreationBytecodeSize := blockCreationBytecodeSize.
  	^generatorTable!

Item was added:
+ ----- Method: Cogit>>printPCMapPairsFor: (in category 'method map') -----
+ printPCMapPairsFor: cogMethod
+ 	<api>
+ 	<var: 'cogMethod' type: #'CogMethod *'>
+ 	| 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>>printPCMapPairsFor:on: (in category 'method map') -----
  printPCMapPairsFor: cogMethod on: aStream
  	<doNotGenerate>
  	<inline: true>
  	| mcpc map mapByte annotation |
  	mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
  	map := self mapStartFor: cogMethod.
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
  		[annotation := mapByte >> AnnotationShift.
  		 annotation ~= IsAnnotationExtension ifTrue:
  			[mcpc := mcpc + (backEnd codeGranularity
  								* (annotation = IsDisplacementX2N
  									ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
  									ifFalse: [mapByte bitAnd: DisplacementMask]))].
  		 aStream ensureCr.
  		 map printOn: aStream base: 16.
  		 aStream nextPutAll: ': '.
+ 		 mapByte printOn: aStream base: 16 length: 2 padded: true.
- 		 mapByte printOn: aStream base: 16.
  		 aStream space.
  		 annotation printOn: aStream base: 16.
  		 aStream nextPutAll: ' ('; print: (AnnotationConstantNames at: annotation + 1); nextPutAll: ') '.
  		 (mapByte bitAnd: DisplacementMask) printOn: aStream base: 16.
  		 aStream space.
  		 aStream nextPut: $@.
  		 mcpc printOn: aStream base: 16.
  		 aStream flush.
  		 map := map - 1]!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>flush (in category 'printing') -----
+ flush
+ 	coInterpreter transcript flush!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>printChar: (in category 'printing') -----
+ printChar: aCharacter
+ 	coInterpreter transcript nextPut: aCharacter!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>printHex: (in category 'printing') -----
  printHex: anInteger
  	| it16 |
  	it16 := anInteger radix: 16.
  	coInterpreter transcript
  		next: 8 - it16 size put: Character space;
+ 		nextPutAll: (anInteger printStringBase: 16)!
- 		nextPutAll: (anInteger storeStringBase: 16)!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>printHexnp: (in category 'printing') -----
+ printHexnp: anInteger
+ 	coInterpreter transcript nextPutAll: (anInteger printStringBase: 16)!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>printNum: (in category 'printing') -----
+ printNum: anInteger
+ 	coInterpreter transcript print: anInteger!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>putchar: (in category 'printing') -----
+ putchar: aCharacter
+ 	coInterpreter transcript nextPut: aCharacter!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>space (in category 'printing') -----
  space
+ 	coInterpreter transcript space!
- 	Transcript space!

Item was changed:
  ----- Method: StackInterpreter>>flush (in category 'debug printing') -----
  flush
+ 	<api>
  	<cmacro: '() fflush(stdout)'>!

Item was added:
+ ----- Method: StackInterpreter>>getCogVMFeatureFlags (in category 'internal interpreter access') -----
+ getCogVMFeatureFlags
+ 	"Answer an array of flags indicating various optional features of the Cog VM.
+ 	 Bit 0: supports two btecode sets (MULTIPLEBYTECODESETS)
+ 	 Bit 1: supports immtablity (IMMUTABILITY)"
+ 	^objectMemory integerObjectOf: (MULTIPLEBYTECODESETS ifTrue: [1] ifFalse: [0])
+ 									+ (IMMUTABILITY ifTrue: [2] ifFalse: [0])!

Item was changed:
  ----- Method: StackInterpreter>>printHexnp: (in category 'debug printing') -----
  printHexnp: n
+ 	<api>
  	"Print n in hex,  in the form '0x1234', unpadded"
  	self print: '0x%lx' f: (self cCoerceSimple: n to: #'unsigned long')!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVMParameter (in category 'system control primitives') -----
(excessive size, no diff calculated)



More information about the Vm-dev mailing list