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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 17 18:43:44 UTC 2015


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

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

Name: VMMaker.oscog-eem.1609
Author: eem
Time: 17 December 2015, 10:41:49.192 am
UUID: 771cdc25-5d27-4818-8943-2ba5c0e31791
Ancestors: VMMaker.oscog-eem.1608

Cogit: Fix the (arguably bogus) register save/restore code for safe trampolines, including the ceScheduleScavenge call.

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

Item was added:
+ ----- Method: CogARMCompiler>>genSaveRegForCCall (in category 'abi') -----
+ genSaveRegForCCall
+ 	"Save the general purpose registers for a call into the C run-time from a trampoline."
+ 	"Save none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
+ 	"cogit gen: STMFD operand: 16r7F"!

Item was removed:
- ----- Method: CogARMCompiler>>genSaveRegisters (in category 'abi') -----
- genSaveRegisters
- 	"Save the general purpose registers for a trampoline call."
- 	"Save none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
- 	"cogit gen: STMFD operand: 16r7F"!

Item was added:
+ ----- Method: CogARMCompiler>>genSaveRegsForCCall (in category 'abi') -----
+ genSaveRegsForCCall
+ 	"Save the general purpose registers for a trampoline call."
+ 	"Save none, because the ARM ABI only defines callee saved registers, no caller-saved regs."
+ 	"cogit gen: STMFD operand: 16r7F"
+ 	self flag: 'this will change with Sista when we hope to be able to allocate arbitrary registers'!

Item was removed:
- ----- Method: CogAbstractInstruction>>genSaveRegisters (in category 'abi') -----
- genSaveRegisters
- 	"Save the general purpose registers for a trampoline call."
- 	self subclassResponsibility!

Item was changed:
  ----- Method: CogIA32Compiler>>genRestoreRegsExcept: (in category 'abi') -----
  genRestoreRegsExcept: abstractReg
  	| realReg |
  	realReg := self concreteRegister: abstractReg.
  	self assert: (EDI > EAX and: [EDI - EAX + 1 = 6]).
  	EAX to: EDI do:
  		[:reg|
+ 		(reg between: ESP and: EBP) ifFalse:
+ 			[realReg = reg
+ 				ifTrue: [cogit AddCq: 4 R: ESP]
+ 				ifFalse: [cogit PopR: reg]]].
- 		realReg = reg ifTrue: [cogit AddCq: 4 R: ESP] ifFalse: [cogit PopR: reg]].
  	^0!

Item was removed:
- ----- Method: CogIA32Compiler>>genSaveRegisters (in category 'abi') -----
- genSaveRegisters
- 	"Save the general purpose registers for a trampoline call."
- 
- 	self assert: (EDI > EAX and: [EDI - EAX + 1 = 8]).
- 	EDI to: EAX by: -1 do:
- 		[:reg|
- 		 (reg between: ESP and: EBP) ifFalse:
- 			[cogit PushR: reg]].
- 	^0!

Item was added:
+ ----- Method: CogIA32Compiler>>genSaveRegsForCCall (in category 'abi') -----
+ genSaveRegsForCCall
+ 	"Save the general purpose registers for a call into the C run-time from a trampoline."
+ 
+ 	self assert: (EDI > EAX and: [EDI - EAX + 1 = 8]).
+ 	EDI to: EAX by: -1 do:
+ 		[:reg|
+ 		 (reg between: ESP and: EBP) ifFalse:
+ 			[cogit PushR: reg]].
+ 	^0!

Item was removed:
- ----- Method: CogMIPSELCompiler>>genSaveRegisters (in category 'abi') -----
- genSaveRegisters
- 	"This method is poorly named. Is this for a Smalltalk -> C call or C -> Smalltalk call?
- 	 If the former we don't need to do anything because all of the abstract registers are
- 	 allocated to C preserved registers."
- 	self flag: #bogus.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genSaveRegsForCCall (in category 'abi') -----
+ genSaveRegsForCCall
+ 	"Save the general purpose registers for a call into the C run-time from a trampoline.
+ 	 We don't need to do anything because all of the abstract registers are
+ 	 allocated to C preserved registers."
+ 	self flag: 'this will change with Sista when we hope to be able to allocate arbitrary registers'!

Item was changed:
  ----- Method: CogX64Compiler>>genRestoreRegs (in category 'abi') -----
  genRestoreRegs
  	"Restore the general purpose registers for a trampoline call.
  	 c.f. genSaveRegisters"
+ 	RAX to: R15 do:
+ 		[:reg|
+ 		 (reg between: RSP and: RBP) ifFalse:
+ 			[cogit PopR: reg]].
- 	cogit
- 		PopR: RAX;
- 		PopR: RBX;
- 		PopR: RCX;
- 		PopR: RDX;
- 		PopR: RSI;
- 		PopR: RDI;
- 		PopR: R8;
- 		PopR: R9;
- 		PopR: R10;
- 		PopR: R11;
- 		PopR: R12;
- 		PopR: R13;
- 		PopR: R14;
- 		PopR: R15.
  	^0!

Item was changed:
  ----- Method: CogX64Compiler>>genRestoreRegsExcept: (in category 'abi') -----
  genRestoreRegsExcept: abstractReg
  	| realReg |
  	realReg := self concreteRegister: abstractReg.
  	self assert: (R15 > RAX and: [R15 - RAX + 1 = 16]).
  	RAX to: R15 do:
  		[:reg|
+ 		(reg between: RSP and: RBP) ifFalse:
+ 			[realReg = reg
+ 				ifTrue: [cogit AddCq: 8 R: RSP]
+ 				ifFalse: [cogit PopR: reg]]].
- 		realReg = reg ifTrue: [cogit AddCq: 4 R: RSP] ifFalse: [cogit PopR: reg]].
  	^0!

Item was removed:
- ----- Method: CogX64Compiler>>genSaveRegisters (in category 'abi') -----
- genSaveRegisters
- 	"Save the general purpose registers for a trampoline call."
- 
- 	self assert: (R15 > RAX and: [R15 - RAX + 1 = 16]).
- 	R15 to: RAX by: -1 do: [:reg| cogit PushR: reg].
- 	^0!

Item was added:
+ ----- Method: CogX64Compiler>>genSaveRegsForCCall (in category 'abi') -----
+ genSaveRegsForCCall
+ 	"Save the general purpose registers for a trampoline call."
+ 
+ 	self assert: (R15 > RAX and: [R15 - RAX + 1 = 16]).
+ 	R15 to: RAX by: -1 do:
+ 		[:reg|
+ 		 (reg between: RSP and: RBP) ifFalse:
+ 			[cogit PushR: reg]].
+ 	^0!

Item was changed:
  ----- Method: Cogit>>compileCallFor:numArgs:arg:arg:arg:arg:resultReg:saveRegs: (in category 'initialization') -----
  compileCallFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 resultReg: resultRegOrNone saveRegs: saveRegs
  	"Generate a call to aRoutine with up to 4 arguments.  If resultRegOrNone is not
  	 NoReg assign the C result to resultRegOrNone.  If saveRegs, save all registers.
  	 Hack: a negative arg value indicates an abstract register, a non-negative value
  	 indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	cStackAlignment > objectMemory wordSize ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: saveRegs
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / objectMemory wordSize].
  	saveRegs ifTrue:
+ 		[backEnd genSaveRegsForCCall].
- 		[backEnd genSaveRegisters].
  	backEnd genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3.
  	self CallFullRT: (self cCode: [aRoutine asUnsignedInteger]
  					   inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	resultRegOrNone ~= NoReg ifTrue:
  		[backEnd genWriteCResultIntoReg: resultRegOrNone].
  	 saveRegs ifTrue:
  		[numArgs > 0 ifTrue:
  			[backEnd genRemoveNArgsFromStack: numArgs].
  		resultRegOrNone ~= NoReg
  			ifTrue: [backEnd genRestoreRegsExcept: resultRegOrNone]
  			ifFalse: [backEnd genRestoreRegs]]!



More information about the Vm-dev mailing list