[Vm-dev] VM Maker: VMMaker.oscog-tpr.1411.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Jul 12 20:22:56 UTC 2015


tim Rowledge uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tpr.1411.mcz

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

Name: VMMaker.oscog-tpr.1411
Author: tpr
Time: 12 July 2015, 1:21:23.189 pm
UUID: f10b2335-024d-4641-8c0f-fb88f7dccafc
Ancestors: VMMaker.oscog-rmacnak.1410

simulation phase support for ARM div/mod 'instruction'. Works in sim-land; a new ABI call-out short-circuits some of the more general call-out support and the register-smashing is more restricted since we need R0/1/lr to survive.

Next stop - finding out how to call the real __aeabit_idivmod call and find ing out how it differs from intel's IDIV instruction in its treatment of value.

=============== Diff against VMMaker.oscog-rmacnak.1410 ===============

Item was added:
+ ----- Method: CogARMCompiler>>aeabiDiv:Mod: (in category 'simulation') -----
+ aeabiDiv: dividend Mod: divisor
+ "simulate the __aeabi_idivmod call"
+ 	|result|
+ 
+ 	cogit processor r0: (result :=dividend quo: divisor).
+ 	cogit processor r1: (dividend rem: divisor).
+ 	^result!

Item was added:
+ ----- Method: CogARMCompiler>>aeabiDivModFunctionAddr (in category 'ARM convenience instructions') -----
+ aeabiDivModFunctionAddr
+ "return the address of the __aeabi_idivmod() call provided by the ARM low level libs to do an integer divide that returns the quo in R0 and rem in R1"
+ 	<var: #'__aeabi_idivmod' declareC: 'extern void __aeabi_idivmod(int dividend, ind divisor)'>
+ 	^self cCode: '__aeabi_idivmod' inSmalltalk:[#aeabiDiv:Mod:]!

Item was changed:
  ----- Method: CogARMCompiler>>canDivQuoRem (in category 'testing') -----
  canDivQuoRem
  	<inline: true>
+ 	^true!
- 	^false!

Item was changed:
  ----- Method: CogARMCompiler>>genDivR:R:Quo:Rem: (in category 'abstract instructions') -----
  genDivR: abstractRegDivisor R: abstractRegDividend Quo: abstractRegQuotient Rem: abstractRegRemainder
+ "Currently no instruction level support for divide on ARM. See also #canDivQuoRem"
+ 	| rDividend rDivisor rQuotient rRemainder divRemFunctionAddr |
+ 
+ 	self assert: abstractRegDividend ~= abstractRegDivisor.
+ 	self assert: abstractRegQuotient ~= abstractRegRemainder.
+ 	rDividend := self concreteRegister: abstractRegDividend.
+ 	rDivisor := self concreteRegister: abstractRegDivisor.
+ 	rDividend = CArg0Reg ifFalse:[
+ 		"we need to move the value in rDividend to CArg0Reg. Best to double check if rDivisor is already using it first"
+ 		rDivisor = CArg0Reg ifTrue:[ "oh dear; we also need to move rDivisor's value out of the way first.. I'll move it to CArg1Reg and if some nitwit has managed to put rDividend there they deserve the crash"
+ 			rDividend = CArg1Reg ifTrue:[self error: 'register choices in genDivR:R:Quo:Rem: made life impossible'].
+ 			cogit MoveR: rDivisor R: CArg1Reg.
+ 			"and update rDivisor or we get buggerd by the next clause"
+ 			rDivisor := CArg1Reg].
+ 		cogit MoveR: rDividend R: CArg0Reg.
+ 	].
+ 	rDivisor = CArg1Reg ifFalse:[
+ 		cogit MoveR: rDivisor R: CArg1Reg].
+ 	divRemFunctionAddr := self aeabiDivModFunctionAddr.
+ 	cogit backEnd saveAndRestoreLinkRegAround:
+ 		[cogit CallFullRT: (self cCode: [divRemFunctionAddr asUnsignedInteger]
+ 					   inSmalltalk: [cogit simulatedTrampolineFor: divRemFunctionAddr])].
+ 	"Now we need to move the r0/1 results back to rQuotient & rRemainder"
+ 	rQuotient := self concreteRegister: abstractRegQuotient.
+ 	rRemainder := self concreteRegister: abstractRegRemainder.
+ 	rQuotient = CArg0Reg ifFalse:["oh good grief, not again"
+ 		cogit MoveR: CArg0Reg R: rQuotient.
+ 		rQuotient = CArg1Reg ifTrue:[self error: 'register choices in genDivR:R:Quo:Rem: made life impossible'] ].
+ 	rRemainder = CArg1Reg  ifFalse:[
+ 		cogit MoveR: CArg1Reg R: rRemainder].
+ 	
+ 				
+ !
- "Currently no instruction level support for divide on ARM. See also #canDivQuoRem"!

Item was changed:
  ----- Method: Cogit>>handleABICallOrJumpSimulationTrap:evaluable: (in category 'simulation only') -----
  handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable
+ 
  	self assert: aProcessorSimulationTrap type = #call.
  	processor
  		simulateLeafCallOf: aProcessorSimulationTrap address
  		nextpc: aProcessorSimulationTrap nextpc
  		memory: coInterpreter memory.
  	self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. evaluable selector. ')'}.
  	evaluable valueWithArguments: (processor
  										postCallArgumentsNumArgs: evaluable numArgs
  										in: coInterpreter memory).
  	self recordInstruction: {'(simulated return to '. processor retpcIn: coInterpreter memory. ')'}.
  	processor
+ 		smashABICallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
- 		smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize;
  		simulateLeafReturnIn: coInterpreter memory!

Item was changed:
  ----- Method: Cogit>>simulatedTrampolineFor: (in category 'initialization') -----
  simulatedTrampolineFor: selectorOrAddress
  	"Set a simulated trampoline.  This is a method in the cogit, coInterpreter
  	 or objectMemory that is called from a machine code trampoline."
  	<doNotGenerate>
  	| address |
  	selectorOrAddress isInteger ifTrue:
  		[self assert: (simulatedTrampolines includesKey: selectorOrAddress).
  		 ^selectorOrAddress].
  	self assert: selectorOrAddress isSymbol.
  	address := self simulatedAddressFor: selectorOrAddress.
  	simulatedTrampolines
  		at: address
  		ifAbsentPut:
  			[MessageSend
  				receiver: ((self respondsTo: selectorOrAddress)
  							ifTrue: [self]
  							ifFalse: [(coInterpreter respondsTo: selectorOrAddress)
  										ifTrue: [coInterpreter]
  										ifFalse: [(objectMemory respondsTo: selectorOrAddress)
  											ifTrue: [objectMemory]
+ 											ifFalse: [(backEnd respondsTo: selectorOrAddress)
+ 												ifTrue:[backEnd]
+ 												ifFalse:[self notify: 'cannot find receiver for ', selectorOrAddress]]]])
- 											ifFalse: [self notify: 'cannot find receiver for ', selectorOrAddress]]])
  				selector: selectorOrAddress
  				arguments: (1 to: selectorOrAddress numArgs) asArray].
  	^address!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveDiv (in category 'primitive generators') -----
  genPrimitiveDiv
  	| jumpNotSI jumpZero jumpExact jumpSameSign convert |
+ 	"this is for primitive 12"
  	<var: #convert type: #'AbstractInstruction *'>
  	<var: #jumpZero type: #'AbstractInstruction *'>
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpExact type: #'AbstractInstruction *'>
  	<var: #jumpSameSign type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: ClassReg.
  	self MoveR: Arg0Reg R: Arg1Reg.
  	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	"We must shift away the tags, not just subtract them, so that the
  	 overflow case doesn't actually overflow the machine instruction."
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: ClassReg].
  	jumpZero := self JumpZero: 0.
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
  	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
  	"If remainder is zero we must check for overflow."
  	self CmpCq: 0 R: ClassReg.
  	jumpExact := self JumpZero: 0.
  	"If arg and remainder signs are different we must round down."
  	self XorR: ClassReg R: Arg1Reg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: Arg1Reg].
  	jumpSameSign := self JumpGreaterOrEqual: 0.
  	self SubCq: 1 R: TempReg.
  	jumpSameSign jmpTarget: (convert := self Label).
  	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
  	self MoveR: TempReg R: ReceiverResultReg.
  	self RetN: 0.
  	"test for overflow; the only case is SmallInteger minVal // -1"
  	jumpExact jmpTarget:
  		(self CmpCq: (1 << (objectRepresentation numSmallIntegerBits - 1)) R: TempReg).
  	self JumpLess: convert.
  	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveDivide (in category 'primitive generators') -----
  genPrimitiveDivide
  	| jumpNotSI jumpZero jumpInexact jumpOverflow |
+ 	"this is for primitive 10"
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpZero type: #'AbstractInstruction *'>
  	<var: #jumpInexact type: #'AbstractInstruction *'>
  	<var: #jumpOverflow type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: ClassReg.
  	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	"We must shift away the tags, not just subtract them, so that the
  	 overflow case doesn't actually overflow the machine instruction."
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
  	jumpZero := self JumpZero: 0.
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
  	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
  	"If remainder is non-zero fail."
  	self CmpCq: 0 R: ClassReg.
  	jumpInexact := self JumpNonZero: 0.
  	"test for overflow; the only case is SmallInteger minVal / -1"
  	self CmpCq: (1 << (objectRepresentation numSmallIntegerBits - 1)) R: TempReg.
  	jumpOverflow := self JumpGreaterOrEqual: 0.
  	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
  	self MoveR: TempReg R: ReceiverResultReg.
  	self RetN: 0.
  	jumpOverflow jmpTarget: (jumpInexact jmpTarget: (jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label))).
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveMod (in category 'primitive generators') -----
  genPrimitiveMod
  	| jumpNotSI jumpZero jumpExact jumpSameSign |
+ 	"this is for primitive 11"
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpZero type: #'AbstractInstruction *'>
  	<var: #jumpExact type: #'AbstractInstruction *'>
  	<var: #jumpSameSign type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: ClassReg.
  	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ClassReg.
  	jumpZero := self JumpZero: 0.
  	self MoveR: ClassReg R: Arg1Reg.
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genRemoveSmallIntegerTagsInScratchReg: TempReg.
  	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
  	"If remainder is zero we're done."
  	self CmpCq: 0 R: ClassReg.
  	jumpExact := self JumpZero: 0.
  	"If arg and remainder signs are different we must reflect around zero."
  	self XorR: ClassReg R: Arg1Reg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: Arg1Reg].
  	jumpSameSign := self JumpGreaterOrEqual: 0.
  	self XorR: ClassReg R: Arg1Reg.
  	self AddR: Arg1Reg R: ClassReg.
  	jumpSameSign jmpTarget: (jumpExact jmpTarget: self Label).
  	objectRepresentation genSetSmallIntegerTagsIn: ClassReg.
  	self MoveR: ClassReg R: ReceiverResultReg.
  	self RetN: 0.
  	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveQuo (in category 'primitive generators') -----
  genPrimitiveQuo
  	| jumpNotSI jumpZero jumpOverflow |
+ 	"this is for primitive 13"
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpZero type: #'AbstractInstruction *'>
  	<var: #jumpOverflow type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: ClassReg.
  	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	"We must shift away the tags, not just subtract them, so that the
  	 overflow case doesn't actually overflow the machine instruction."
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: ClassReg].
  	jumpZero := self JumpZero: 0.
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
  	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
  	"test for overflow; the only case is SmallInteger minVal quo: -1"
  	self CmpCq: (1 << (objectRepresentation numSmallIntegerBits - 1)) R: TempReg.
  	jumpOverflow := self JumpGreaterOrEqual: 0.
  	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
  	self MoveR: TempReg R: ReceiverResultReg.
  	self RetN: 0.
  	jumpOverflow jmpTarget: (jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label)).
  	^0!



More information about the Vm-dev mailing list