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

commits at source.squeak.org commits at source.squeak.org
Fri Dec 11 00:21:03 UTC 2015


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

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

Name: VMMaker.oscog-eem.1577
Author: eem
Time: 10 December 2015, 4:19:07.642 pm
UUID: 89d1673b-bb42-4cc1-a5c7-57d047cc4520
Ancestors: VMMaker.oscog-eem.1576

Cogit: More NoReg uses

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

Item was removed:
- ----- Method: CogARMCompiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
- genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
- "ARM doesn't push the first 4 arguments. Now, currently Cog doesn't use more than 4 args so we should never need to push any - but just in case we'll check for it"
- 	| wordsPushedModAlignment delta |
- 	wordsPushedModAlignment := ((saveRegs ifTrue: [self numberOfSaveableRegisters] ifFalse: [0])
- 									+ (numArgs > 4 ifTrue:[numArgs - 4] ifFalse:[0]))
- 									\\ alignment.
- 	wordsPushedModAlignment ~= 0 ifTrue:
- 		[delta := alignment - wordsPushedModAlignment.
- 		 cogit SubCq: delta * 4 R: SPReg].
- 	^0!

Item was changed:
  ----- Method: CogAbstractInstruction>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
  genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
  	| wordsPushedModAlignment delta |
  	self numIntRegArgs >= (saveRegs
  								ifTrue: [self numberOfSaveableRegisters + numArgs]
  								ifFalse: [numArgs])  ifTrue:
  		[^0].
  	wordsPushedModAlignment := ((saveRegs ifTrue: [self numberOfSaveableRegisters] ifFalse: [0])
  									+ numArgs)
  									\\ alignment.
  	wordsPushedModAlignment ~= 0 ifTrue:
  		[delta := alignment - wordsPushedModAlignment.
+ 		 cogit SubCq: delta * objectMemory wordSize R: SPReg].
- 		 cogit SubCq: delta * 4 R: SPReg].
  	^0!

Item was removed:
- ----- Method: CogMIPSELCompiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
- genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
- 	| wordsPushedModAlignment delta |
- 	self numIntRegArgs >= (saveRegs
- 								ifTrue: [self numberOfSaveableRegisters + numArgs]
- 								ifFalse: [numArgs])  ifTrue:
- 		[^0].
- 	wordsPushedModAlignment := ((saveRegs ifTrue: [self numberOfSaveableRegisters] ifFalse: [0])
- 									+ numArgs)
- 									\\ alignment.
- 	wordsPushedModAlignment ~= 0 ifTrue:
- 		[delta := alignment - wordsPushedModAlignment.
- 		 cogit SubCq: delta * 4 R: SPReg].
- 	^0!

Item was changed:
  ----- Method: Cogit>>genCheckForInterruptsTrampoline (in category 'initialization') -----
  genCheckForInterruptsTrampoline
  	self zeroOpcodeIndex.
  	"if we have a link register we will assume that it does not get automatically pushed onto the stack
  	and thus there is no need to pop it before saving to instructionPointerAddress"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceCheckForInterrupts
  		called: 'ceCheckForInterruptsTrampoline'
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genNSSendTrampolineFor:numArgs:enclosingObjectCheck:called: (in category 'initialization') -----
  genNSSendTrampolineFor: aRoutine numArgs: numArgs enclosingObjectCheck: eoCheckFlag called: aString
  	"ReceiverResultReg: method receiver
  	SendNumArgsReg: the NSSendCache cache"
  	<option: #NewspeakVM>
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	| jumpMiss jumpItsTheReceiverStupid |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
  	self zeroOpcodeIndex.
  	objectRepresentation
  		genGetInlineCacheClassTagFrom: ReceiverResultReg
  		into: ClassReg
  		forEntry: false.
  	self MoveMw: NSCClassTagIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  	self CmpR: ClassReg R: TempReg.
  	jumpMiss := self JumpNonZero: 0.
  
  	eoCheckFlag ifTrue:
  		[self MoveMw: NSCEnclosingObjectIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  		self CmpCq: 0 R: TempReg.
  		jumpItsTheReceiverStupid := self JumpZero: 0.
  		self MoveR: TempReg R: ReceiverResultReg.
  		"Now set the stacked receiver, if needed.  If there are reg args this is
  		 not required; see genPushRegisterArgsForNumArgs:numArgs: below."
  		(self numRegArgs = 0 or: [numArgs > self numRegArgs]) ifTrue:
  			[numArgs >= (NumSendTrampolines - 1)
  				ifTrue: "arbitrary argument count"
  					[self MoveMw: NSCNumArgsIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  					 backEnd hasLinkRegister ifFalse:
  						[self AddCq: 1 R: TempReg]..
  					 self MoveR: ReceiverResultReg Xwr: TempReg R: SPReg]
  				ifFalse: "Known argument count"
  					[self MoveR: TempReg Mw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]) + numArgs * objectMemory wordSize r: SPReg]].
  		jumpItsTheReceiverStupid jmpTarget: self Label].
  
  	self MoveMw: NSCTargetIndex * objectMemory wordSize r: SendNumArgsReg R: TempReg.
  	self JumpR: TempReg.
  
  	jumpMiss jmpTarget: self Label.
  	objectRepresentation
  		genEnsureOopInRegNotForwarded: ReceiverResultReg
  		scratchReg: TempReg
  		updatingMw: FoxMFReceiver
  		r: FPReg.
  	self numRegArgs > 0 ifTrue:
  		[backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: TempReg].
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: SendNumArgsReg "The NSSendCache"
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genNonLocalReturnTrampoline (in category 'initialization') -----
  genNonLocalReturnTrampoline
  	self zeroOpcodeIndex.
  	"write the return address to the coInterpreter instructionPointerAddress;
  	 following the CallRT to this CISCs will have pushed it on the stack, so pop it first; RISCs will have it in
  	 their link register so just write it directly."
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceNonLocalReturn:
  		called: 'ceNonLocalReturnTrampoline'
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genReturnTrampolineFor:called:arg: (in category 'initialization') -----
  genReturnTrampolineFor: aRoutine  called: aString arg: regOrConst0
  	"Generate a trampoline for a routine used as a return address, that has one argument.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: false "Since the routine is reached by a return instruction it should /not/ push the link register."
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genSafeTrampolineFor:called: (in category 'initialization') -----
  genSafeTrampolineFor: aRoutine called: aString
  	"Generate a trampoline with no arguments that will
  	 save and restore all registers around the call"
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: true
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genSafeTrampolineFor:called:arg: (in category 'initialization') -----
  genSafeTrampolineFor: aRoutine called: aString arg: regOrConst0
  	"Generate a trampoline with one argument that will
  	 save and restore all registers around the call"
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: true
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genSafeTrampolineFor:called:arg:arg: (in category 'initialization') -----
  genSafeTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1
  	"Generate a trampoline with two arguments that
  	 will save and restore all registers around the call"
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		saveRegs: true
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString
  	"Generate a trampoline with no arguments"
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine  called: aString arg: regOrConst0
  	"Generate a trampoline with one argument.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1
  	"Generate a trampoline with two arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2
  	"Generate a trampoline with three arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:arg:arg: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate a trampoline with four arguments.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<var: #aString type: #'char *'>
  	^self
  		genTrampolineFor: aRoutine
  		called: aString
  		numArgs: 4
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
  	<var: #trampolineName type: #'char *'>
  	<inline: false>
  	self zeroOpcodeIndex.
  	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
  	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
  	self AddCq: boolean R: TempReg.
  	^self genTrampolineFor: #ceSendMustBeBoolean:
  		called: trampolineName
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPICMissTrampolineFor: (in category 'initialization') -----
  genPICMissTrampolineFor: numArgs
  	<inline: false>
  	| startAddress |
  	startAddress := methodZoneBase.
  	self zeroOpcodeIndex.
  	"N.B. a closed PIC jumps to the miss routine, not calls it, so there is only one retpc on the stack."
  	backEnd genPushRegisterArgsForNumArgs: numArgs scratchReg: SendNumArgsReg.
  	self genTrampolineFor: #ceCPICMiss:receiver:
  		called: (self trampolineName: 'cePICMiss' numRegArgs: numArgs)
  		numArgs: 2
  		arg: ClassReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
  		pushLinkReg: true
+ 		resultReg: NoReg
- 		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!



More information about the Vm-dev mailing list