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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 21 20:44:35 UTC 2019


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

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

Name: VMMaker.oscog-eem.2624
Author: eem
Time: 21 December 2019, 12:44:17.50236 pm
UUID: 5a6548d5-4461-43c9-bec3-34c122fc04cc
Ancestors: VMMaker.oscog-eem.2623

Cogit:
genPrimitiveHashMultiply needs to obey backEnd canMulRR.

Simulation: Make sure that mcprims are called via leaf calls so that tjeir unaligned stack pointer doesn't violate the ARMv8 ABI stack alignment (mcprims run on the Smalltalk stack).  Nuke the unused Cogit>>simulateCallOf:nextpc:memory:.

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

Item was added:
+ ----- Method: CoInterpreter>>mcprims (in category 'cog jit support') -----
+ mcprims
+ 	<doNotGenerate>
+ 	"Answer all the short-cut machine code primitives that run on the Smalltalk stack, not the C stack."
+ 	^#(mcprimHashMultiply:)!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount rpc |
  	evaluable := simulatedTrampolines
  					at: aProcessorSimulationTrap address
  					ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  								in: simulatedTrampolines].
  	function := evaluable isBlock
  					ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse:
  						[evaluable receiver == backEnd ifTrue:
  							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  						 evaluable selector].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
+ 	(backEnd wantsNearAddressFor: function) ifTrue:
- 	(function beginsWith: 'ceShort') ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
+ 	memory := coInterpreter memory.
  	aProcessorSimulationTrap type == #call
  		ifTrue:
+ 			[(coInterpreter mcprims includes: function)
+ 				ifTrue:
+ 					[processor
+ 						simulateLeafCallOf: aProcessorSimulationTrap address
+ 						nextpc: aProcessorSimulationTrap nextpc
+ 						memory: memory]
+ 				ifFalse:
+ 					[processor
+ 						simulateCallOf: aProcessorSimulationTrap address
+ 						nextpc: aProcessorSimulationTrap nextpc
+ 						memory: memory].
- 			[processor
- 				simulateCallOf: aProcessorSimulationTrap address
- 				nextpc: aProcessorSimulationTrap nextpc
- 				memory: (memory := coInterpreter memory).
  			 self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}]
  		ifFalse:
  			[processor
  				simulateJumpCallOf: aProcessorSimulationTrap address
+ 				memory: memory.
- 				memory: (memory := coInterpreter memory).
  			 self recordInstruction: {'(simulated jump to '. aProcessorSimulationTrap address. '/'. function. ')'}].
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
  					[clickConfirm := false. self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: ex returnValue].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter checkForLastObjectOverwrite.
  		 coInterpreter primFailCode = 0
  			ifTrue: [(#(	primitiveClosureValue primitiveClosureValueWithArgs primitiveClosureValueNoContextSwitch
  						primitiveFullClosureValue primitiveFullClosureValueWithArgs primitiveFullClosureValueNoContextSwitch
  						primitiveSignal primitiveWait primitiveResume primitiveSuspend primitiveYield
  						primitiveExecuteMethodArgsArray primitiveExecuteMethod
  						primitivePerform primitivePerformWithArgs primitivePerformInSuperclass
  						primitiveTerminateTo primitiveStoreStackp primitiveDoPrimitiveWithArgs)
  							includes: function) ifFalse:
  						["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  						 (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse:
  							[self assert: savedFramePointer = coInterpreter framePointer.
  							 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  									= coInterpreter stackPointer]]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}.
  		 rpc := processor retpcIn: memory.
  		 self assert: (rpc >= codeBase and: [rpc < methodZone freeStart]).
+ 		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory.
+ 		 (coInterpreter mcprims includes: function)
+ 			ifTrue: [processor simulateLeafReturnIn: memory]
+ 			ifFalse: [processor simulateReturnIn: memory]].
- 		 processor
- 			smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory;
- 			simulateReturnIn: memory].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [#(nil continue continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
  							ifNil: [0]
  							ifNotNil: [result isInteger
  										ifTrue: [result]
  										ifFalse: [16rF00BA222]])
  
  	"coInterpreter cr.
  	 processor sp + 32 to: processor sp - 32 by: -4 do:
  		[:sp|
  		 sp = processor sp
  			ifTrue: [coInterpreter print: 'sp->'; tab]
  			ifFalse: [coInterpreter printHex: sp].
  		 coInterpreter tab; printHex: (coInterpreter longAt: sp); cr]"!

Item was removed:
- ----- Method: Cogit>>simulateCallOf:nextpc:memory: (in category 'simulation processor access') -----
- simulateCallOf: address nextpc: nextpc memory: aMemory
- 	<doNotGenerate>
- 	self assertCorrectProcessorOwnership.
- 	^processor simulateCallOf: address nextpc: nextpc memory: aMemory!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveHashMultiply (in category 'primitive generators') -----
  genPrimitiveHashMultiply
  	"Implement 28-bit hashMultiply for SmallInteger and LargePositiveInteger receivers."
  	| jmpFailImm jmpFailNonImm jmpNotSmallInt reenter |
+ 	backEnd canMulRR ifFalse:
+ 		[^UnimplementedPrimitive].
+ 
  	jmpNotSmallInt := objectRepresentation genJumpNotSmallInteger: ReceiverResultReg.
  
  	objectRepresentation genConvertSmallIntegerToIntegerInReg: ReceiverResultReg.
  	reenter :=
  	self MoveCq: HashMultiplyConstant R: TempReg.
  	self MulR: TempReg R: ReceiverResultReg.
  	self AndCq: HashMultiplyMask R: ReceiverResultReg.
  	objectRepresentation genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
  	self RetN: 0.
  
  	jmpNotSmallInt jmpTarget: self Label.
  	jmpFailImm := objectRepresentation genJumpImmediate: ReceiverResultReg.
  	objectRepresentation genGetCompactClassIndexNonImmOf: ReceiverResultReg into: ClassReg.
  	self CmpCq: ClassLargePositiveIntegerCompactIndex R: ClassReg.
  	jmpFailNonImm := self JumpNonZero: 0.
  	objectRepresentation genLoadSlot: 0 sourceReg: ReceiverResultReg destReg: ReceiverResultReg.
  	self Jump: reenter.
  
  	jmpFailImm jmpTarget: (jmpFailNonImm jmpTarget: self Label).
  	^0!



More information about the Vm-dev mailing list