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

commits at source.squeak.org commits at source.squeak.org
Wed Aug 27 10:03:18 UTC 2014


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

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

Name: VMMaker.oscog-eem.866
Author: eem
Time: 27 August 2014, 10:58:56.882 am
UUID: 5b1723bd-9d29-4685-be23-7816f5af9822
Ancestors: VMMaker.oscog-eem.865

Define the SmallFloat primitive numbers for 64-bit Spur.
Have Slang and the simulators elide primitives that are
unimplemented or optional and not selected from the
primitive table.

Sista:
Fix slip in genBinaryVarOpVarInlinePrimitive: reg alloc.

Implement numSLots in genUnaryInlinePrimitive:.

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

Item was added:
+ ----- Method: CogObjectRepresentation>>genGetNumSlotsOf:into: (in category 'compile abstract instructions') -----
+ genGetNumSlotsOf: srcReg into: destReg
+ 	"Get the size in word-sized slots of the object in srcReg into destReg.
+ 	 srcReg may equal destReg."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genGetNumSlotsOf:into: (in category 'compile abstract instructions') -----
+ genGetNumSlotsOf: srcReg into: destReg
+ 	"Get the size in word-sized slots of the object in srcReg into destReg.
+ 	 srcReg may equal destReg."
+ 	<var: #jmp type: #'AbstractInstruction'>
+ 	| jmp |
+ 	self genGetRawSlotSizeOfNonImm: srcReg into: TempReg.
+ 	cogit CmpCq: objectMemory numSlotsMask R: TempReg.
+ 	jmp := cogit JumpLess: 0.
+ 	cogit MoveMw: objectMemory wordSize negated r: srcReg R: TempReg.
+ 	jmp jmpTarget: (cogit MoveR: TempReg R: destReg).
+ 	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>ssFlushNoUpdateTo: (in category 'simulation stack') -----
  ssFlushNoUpdateTo: index
+ 	"This version of ssFlushTo: does /not/ update the simulation stack; it merely generates the spill code.
+ 	 It is used to spill all values to the stack on a rare failing branch (the class trap) when we don't want to
- 	"This version of ssFlushTo: does /not/ update the simulation stack; it merely h=generates the spill code.
- 	 It is used to spill all valiues to teh stack on a rare failing branch (the class trap) when we don't want to
  	 flush the stack on the main path and hence mustn't update the simulation stack if there is no spill."
  	<var: 'copiedEntry' type: #CogSimStackEntry>
  	self assert: needsFrame.
  	methodOrBlockNumTemps to: simSpillBase - 1 do:
  		[:i| self assert: (self simStackAt: i) spilled].
  	simSpillBase <= index ifTrue:
  		[(simSpillBase max: 0) to: index do:
  			[:i| | copiedEntry |
  			copiedEntry := self cCode: [simStack at: index]
  								inSmalltalk: [(simStack at: index) copy].
  			copiedEntry
  				ensureSpilledAt: (self frameOffsetOfTemporary: i)
  				from: FPReg]]!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter class>>primitiveAccessorDepthTable (in category 'constants') -----
  primitiveAccessorDepthTable
  	| cg |
  	cg := CCodeGenerator new.
  	cg vmClass: StackInterpreter.
+ 	^self primitiveTable collect:
- 	^PrimitiveTable collect:
  		[:thing| |class  method |
  		(thing isInteger "quick prims, 0 for fast primitve fail"
  		 or: [thing == #primitiveFail
  		 or: [(class := self primitivesClass whichClassIncludesSelector: thing) isNil]])
  			ifTrue: [-1]
  			ifFalse:
  				[method := (class >> thing) methodNode asTranslationMethodOfClass: TMethod.
  				 cg accessorDepthForMethod: method]]!

Item was changed:
  ----- Method: StackInterpreter class>>primitiveTable (in category 'constants') -----
  primitiveTable
+ 	| cg |
+ 	cg := CCodeGenerator new.
+ 	cg vmClass: StackInterpreter.
+ 	^PrimitiveTable collect:
+ 		[:thing|
+ 		(thing isInteger "quick prims, 0 for fast primitve fail"
+ 		 or: [thing == #primitiveFail])
+ 			ifTrue: [thing]
+ 			ifFalse:
+ 				[(self primitivesClass whichClassIncludesSelector: thing)
+ 					ifNil: [#primitiveFail]
+ 					ifNotNil:
+ 						[:class|
+ 						 (cg shouldIncludeMethodFor: class selector: thing)
+ 							ifTrue: [thing]
+ 							ifFalse: [#primitiveFail]]]]!
- 
- 	^ PrimitiveTable!

Item was changed:
  ----- Method: StackInterpreter>>tryLoadNewPlugin:pluginEntries: (in category 'primitive support') -----
  tryLoadNewPlugin: pluginString pluginEntries: pluginEntries
  	"Load the plugin and if on Spur, populate pluginEntries with the prmitives in the plugin."
  	<doNotGenerate>
  	| plugin realPluginClass plugins simulatorClasses |
  	self transcript cr; show: 'Looking for module ', pluginString.
  	"Defeat loading of the FloatArrayPlugin & Matrix2x3Plugin since complications with 32-bit
  	 float support prevent simulation.  If you feel up to tackling this start by implementing
  		cCoerce: value to: cType
  			^cType = 'float'
  				ifTrue: [value asIEEE32BitWord]
  				ifFalse: [value]
  	 in FloatArrayPlugin & Matrix2x3Plugin and then address the issues in the BalloonEnginePlugin.
  	 See http://forum.world.st/Simulating-the-BalloonEnginePlugin-FloatArrayPlugin-amp-Matrix2x3Plugin-primitives-td4734673.html"
  	(#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: pluginString) ifTrue:
  		[self transcript show: ' ... defeated'. ^nil].
  	pluginString isEmpty
  		ifTrue:
  			[plugin := self]
  		ifFalse:
  			[plugins := InterpreterPlugin allSubclasses select: [:psc| psc moduleName asString = pluginString asString].
  			simulatorClasses := (plugins
  									select: [:psc| psc simulatorClass notNil]
  									thenCollect: [:psc| psc simulatorClass]) asSet.
  			simulatorClasses isEmpty ifTrue: [self transcript show: ' ... not found'. ^nil].
  			simulatorClasses size > 1 ifTrue: [^self error: 'This won''t work...'].
  			plugins size > 1 ifTrue:
  				[self transcript show: '...multiple plugin classes; choosing ', plugins last name].
  			realPluginClass := plugins last. "hopefully lowest in the hierarchy..."
  			plugin := simulatorClasses anyOne newFor: realPluginClass.
  			plugin setInterpreter: objectMemory. "Ignore return value from setInterpreter"
  			(plugin respondsTo: #initialiseModule) ifTrue:
  				[plugin initialiseModule ifFalse:
  					[self transcript show: ' ... initialiser failed'. ^nil]]]. "module initialiser failed"
  	self transcript show: ' ... loaded'.
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[| realPlugin cg |
  		 self transcript show: '...computing accessor depths'.
  		 plugin class isPluginClass
  			ifTrue:
  				[realPlugin := (plugin isSmartSyntaxPluginSimulator
  									ifTrue: [realPluginClass]
  									ifFalse: [plugin class])
  								 withAllSuperclasses detect: [:class| class shouldBeTranslated].
  				 cg := realPlugin buildCodeGeneratorUpTo: realPlugin]
  			ifFalse:
  				[cg := self codeGeneratorToComputeAccessorDepth.
  				 primitiveTable withIndexDo:
  					[:prim :index| | depth |
  					 prim isSymbol ifTrue:
  						[depth := cg accessorDepthForSelector: prim.
+ 						 self assert: (depth isInteger or: [depth isNil and: [(plugin class whichClassIncludesSelector: prim) isNil]]).
- 						 self assert: depth isInteger.
  						 primitiveAccessorDepthTable at: index - 1 put: depth]]].
  		 cg exportedPrimitiveNames do:
  			[:primName| | fnSymbol |
  			 fnSymbol := primName asSymbol.
  			 pluginEntries addLast: {plugin.
  									fnSymbol.
  									[plugin perform: fnSymbol. self].
  									cg accessorDepthForSelector: fnSymbol}].
  		 self transcript show: '...done'].
  	^pluginString asString -> plugin!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryVarOpVarInlinePrimitive: (in category 'inline primitive generators') -----
  genBinaryVarOpVarInlinePrimitive: prim
  	"Var op var version of binary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
  	| ra rr |
  	(rr := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
  		[self ssAllocateRequiredReg:
  			(rr := optStatus isReceiverResultRegLive
  					ifTrue: [Arg0Reg]
  					ifFalse: [ReceiverResultReg])].
  	(ra := backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: rr))) ifNil:
+ 		[self ssAllocateRequiredReg: (ra := Arg1Reg)].
- 		[self ssAllocateRequiredReg: (rr := Arg1Reg)].
  	(rr = ReceiverResultReg or: [ra = ReceiverResultReg]) ifTrue:
  		[optStatus isReceiverResultRegLive: false].
  	self ssTop popToReg: ra.
  	self ssPop: 1.
  	self ssTop popToReg: rr.
  	self ssPop: 1.
  	prim caseOf: {
  		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  		[0]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
  				 self AddR: ra R: rr].
  		[1]	->	[self SubR: ra R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: rr.
  				 objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ra.
  				 self MulR: ra R: rr.
  				 objectRepresentation genAddSmallIntegerTagsTo: rr].
  
  		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
  
  		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
  
  		"64	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
  
  		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
  
  	}
  	otherwise: [^EncounteredUnknownBytecode].
  	self ssPushRegister: rr.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUnaryInlinePrimitive: (in category 'inline primitive generators') -----
  genUnaryInlinePrimitive: prim
  	"Unary inline primitives."
  	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
  	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	| rcvrReg resultReg |
+ 	self ssTop type = SSRegister
+ 		ifTrue: [rcvrReg := self ssTop register]
+ 		ifFalse:
+ 			[(rcvrReg := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
+ 				[self ssAllocateRequiredReg:
+ 					(rcvrReg := optStatus isReceiverResultRegLive
+ 							ifTrue: [Arg0Reg]
+ 							ifFalse: [ReceiverResultReg])]].
+ 	self ssTop popToReg: rcvrReg.
+ 	self ssPop: 1.
+ 	(resultReg := backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
+ 		[self ssFlushUpThroughRegister: rcvrReg].
+ 	prim
+ 		caseOf: {
+ 			[1] ->	"01		unchecked pointer numSlots"
+ 				[resultReg ifNil: [resultReg := rcvrReg].
+ 				 objectRepresentation
+ 					genGetNumSlotsOf: rcvrReg into: resultReg;
+ 					genConvertIntegerToSmallIntegerInScratchReg: resultReg.
+ 				 self ssPushRegister: resultReg].
+ 				  }
+ 		otherwise:
+ 			[^EncounteredUnknownBytecode].
+ 	^0!
- 	"not yet implemented"
- 	^EncounteredUnknownBytecode!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>ssFlushUpThroughRegister: (in category 'simulation stack') -----
+ ssFlushUpThroughRegister: reg
+ 	"Any occurrences on the stack of the register must be
+ 	 flushed, and hence any values colder than them stack."
+ 	<var: #desc type: #'CogSimStackEntry *'>
+ 	simStackPtr - 1 to: (simSpillBase max: 0) by: -1 do:
+ 		[:index| | desc |
+ 		desc := self simStackAt: index.
+ 		(desc type = SSRegister
+ 		 and: [desc register = reg]) ifTrue:
+ 			[self ssFlushTo: index.
+ 			 ^self]]!



More information about the Vm-dev mailing list