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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 7 21:40:00 UTC 2014


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

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

Name: VMMaker.oscog-eem.763
Author: eem
Time: 7 June 2014, 2:37:09.941 pm
UUID: bb0b3235-2b4e-4748-aa8c-e69463f849dd
Ancestors: VMMaker.oscog-eem.762

Add a pushLinkReg arg to the core trampoline generation
routins.  This is true everywhere but in the nonLocalReturn
and checkForInterrupts trampolines, which (on RISCs) write
the link reg to instructionPointer.

Remove the callJumpBar: parameter; this is always true.

Remember to save and restore the link register around the
call to ceCheckProfileTick in the primitive return machinery.

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

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genActiveContextTrampoline (in category 'initialization') -----
  genActiveContextTrampoline
  	"Short-circuit the interpreter call if a frame is already married."
  	| jumpSingle |
  	<var: #jumpSingle type: #'AbstractInstruction *'>
  	cogit
  		zeroOpcodeIndex;
  		MoveMw: FoxMethod r: FPReg R: TempReg;
  		AndCq: MFMethodFlagHasContextFlag R: TempReg.
  	jumpSingle := cogit JumpZero: 0.
  	cogit
  		MoveMw: FoxThisContext r: FPReg R: ReceiverResultReg;
  		RetN: 0.
  	jumpSingle jmpTarget: cogit Label.
  	^cogit genTrampolineFor: #ceActiveContext
  		called: 'ceActiveContextTrampoline'
- 		callJumpBar: true
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: ReceiverResultReg
  		appendOpcodes: true!

Item was removed:
- ----- Method: Cogit>>compileTrampolineFor:callJumpBar:numArgs:arg:arg:arg:arg:saveRegs:resultReg: (in category 'initialization') -----
- compileTrampolineFor: aRoutine callJumpBar: callJumpBar "<Boolean>" numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 saveRegs: saveRegs resultReg: resultRegOrNil
- 	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutine
- 	 as requested by callJumpBar.  If generating a call and resultRegOrNil is non-zero pass the C result
- 	 back in resultRegOrNil.
- 	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
- 	<var: #aRoutine type: #'void *'>
- 	<inline: false>
- 	"If on a RISC processor the return address needs to be pushed to the
- 	 stack so that the interpreter sees the same stack layout as on CISC."
- 	backEnd hasLinkRegister ifTrue:
- 		[self PushR: LinkReg].
- 	self genSmalltalkToCStackSwitch.
- 	cStackAlignment > BytesPerWord ifTrue:
- 		[backEnd
- 			genAlignCStackSavingRegisters: saveRegs
- 			numArgs: numArgs
- 			wordAlignment: cStackAlignment / BytesPerWord].
- 	saveRegs ifTrue:
- 		[callJumpBar ifFalse:
- 			[self error: 'why save registers when you''re not going to return?'].
- 		 backEnd genSaveRegisters].
- 	numArgs > 0 ifTrue:
- 		[numArgs > 1 ifTrue:
- 			[numArgs > 2 ifTrue:
- 				[numArgs > 3 ifTrue:
- 					[regOrConst3 < 0
- 						ifTrue: [backEnd genPassReg: regOrConst3 asArgument: 3]
- 						ifFalse: [backEnd genPassConst: regOrConst3 asArgument: 3]].
- 				 regOrConst2 < 0
- 					ifTrue: [backEnd genPassReg: regOrConst2 asArgument: 2]
- 					ifFalse: [backEnd genPassConst: regOrConst2 asArgument: 2]].
- 			regOrConst1 < 0
- 				ifTrue: [backEnd genPassReg: regOrConst1 asArgument: 1]
- 				ifFalse: [backEnd genPassConst: regOrConst1 asArgument: 1]].
- 		regOrConst0 < 0
- 			ifTrue: [backEnd genPassReg: regOrConst0 asArgument: 0]
- 			ifFalse: [backEnd genPassConst: regOrConst0 asArgument: 0]].
- 	self gen: (callJumpBar ifTrue: [Call] ifFalse: [Jump])
- 		operand: (self cCode: [aRoutine asUnsignedInteger]
- 					   inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
- 	callJumpBar ifTrue:
- 		[resultRegOrNil ifNotNil:
- 			[backEnd genWriteCResultIntoReg: resultRegOrNil].
- 		 saveRegs ifTrue:
- 			[numArgs > 0 ifTrue:
- 				[backEnd genRemoveNArgsFromStack: numArgs].
- 			resultRegOrNil
- 				ifNotNil: [backEnd genRestoreRegsExcept: resultRegOrNil]
- 				ifNil: [backEnd genRestoreRegs]].
- 		backEnd genLoadStackPointers.
- 		backEnd hasLinkRegister ifTrue:
- 			[self PopR: LinkReg].
- 		self RetN: 0]!

Item was added:
+ ----- Method: Cogit>>compileTrampolineFor:numArgs:arg:arg:arg:arg:saveRegs:pushLinkReg:resultReg: (in category 'initialization') -----
+ compileTrampolineFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 saveRegs: saveRegs pushLinkReg: pushLinkReg resultReg: resultRegOrNil
+ 	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutine
+ 	 as requested by callJumpBar.  If generating a call and resultRegOrNil is non-zero pass the C result
+ 	 back in resultRegOrNil.
+ 	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
+ 	<var: #aRoutine type: #'void *'>
+ 	<inline: false>
+ 	"If on a RISC processor, the return address needs to be pushed to the
+ 	 stack so that the interpreter sees the same stack layout as on CISC."
+ 	(pushLinkReg and: [backEnd hasLinkRegister]) ifTrue:
+ 		[self PushR: LinkReg].
+ 	self genSmalltalkToCStackSwitch.
+ 	cStackAlignment > BytesPerWord ifTrue:
+ 		[backEnd
+ 			genAlignCStackSavingRegisters: saveRegs
+ 			numArgs: numArgs
+ 			wordAlignment: cStackAlignment / BytesPerWord].
+ 	saveRegs ifTrue:
+ 		[backEnd genSaveRegisters].
+ 	numArgs > 0 ifTrue:
+ 		[numArgs > 1 ifTrue:
+ 			[numArgs > 2 ifTrue:
+ 				[numArgs > 3 ifTrue:
+ 					[regOrConst3 < 0
+ 						ifTrue: [backEnd genPassReg: regOrConst3 asArgument: 3]
+ 						ifFalse: [backEnd genPassConst: regOrConst3 asArgument: 3]].
+ 				 regOrConst2 < 0
+ 					ifTrue: [backEnd genPassReg: regOrConst2 asArgument: 2]
+ 					ifFalse: [backEnd genPassConst: regOrConst2 asArgument: 2]].
+ 			regOrConst1 < 0
+ 				ifTrue: [backEnd genPassReg: regOrConst1 asArgument: 1]
+ 				ifFalse: [backEnd genPassConst: regOrConst1 asArgument: 1]].
+ 		regOrConst0 < 0
+ 			ifTrue: [backEnd genPassReg: regOrConst0 asArgument: 0]
+ 			ifFalse: [backEnd genPassConst: regOrConst0 asArgument: 0]].
+ 	self Call: (self cCode: [aRoutine asUnsignedInteger]
+ 					   inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
+ 	resultRegOrNil ifNotNil:
+ 		[backEnd genWriteCResultIntoReg: resultRegOrNil].
+ 	 saveRegs ifTrue:
+ 		[numArgs > 0 ifTrue:
+ 			[backEnd genRemoveNArgsFromStack: numArgs].
+ 		resultRegOrNil
+ 			ifNotNil: [backEnd genRestoreRegsExcept: resultRegOrNil]
+ 			ifNil: [backEnd genRestoreRegs]].
+ 	backEnd genLoadStackPointers.
+ 	backEnd hasLinkRegister ifTrue:
+ 		[self PopR: LinkReg].
+ 	self RetN: 0!

Item was changed:
  ----- Method: Cogit>>genCheckForInterruptsTrampoline (in category 'initialization') -----
  genCheckForInterruptsTrampoline
  	opcodeIndex := 0.
  	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'
- 		callJumpBar: true
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genInnerPICAbortTrampoline: (in category 'initialization') -----
  genInnerPICAbortTrampoline: name
  	"Generate the abort for a PIC.  This abort performs either a call of
  	 ceInterpretMethodFromPIC:receiver: to handle invoking an uncogged
  	 target or a call of ceMNUFromPICMNUMethod:receiver: to handle an
  	 MNU dispatch in a closed PIC.  It distinguishes the two by testing
  	 ClassReg.  If the register is zero then this is an MNU."
  	<var: #name type: #'char *'>
  	| jumpMNUCase |
  	<var: #jumpMNUCase type: #'AbstractInstruction *'>
  	self CmpCq: 0 R: ClassReg.
  	jumpMNUCase := self JumpZero: 0.
  	self compileTrampolineFor: #ceInterpretMethodFromPIC:receiver:
- 		callJumpBar: true
  		numArgs: 2
  		arg: SendNumArgsReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil.
  	jumpMNUCase jmpTarget: self Label.
  	^self genTrampolineFor: #ceMNUFromPICMNUMethod:receiver:
  		called: name
- 		callJumpBar: true
  		numArgs: 2
  		arg: SendNumArgsReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genMethodAbortTrampoline (in category 'initialization') -----
  genMethodAbortTrampoline
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  	"on machines with a link register, pop the stack if the ReceiverResultReg = 0,
  	 i.e. if coming through the stack check abort; frame build has already pushed it."
  	backEnd hasLinkRegister ifTrue:
  		[self AddCq: BytesPerWord R: SPReg].
  
  	self compileTrampolineFor: #ceStackOverflow:
- 		callJumpBar: true
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	^self genTrampolineFor: #ceSICMiss:
  		called: 'ceMethodAbort'
- 		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>genNonLocalReturnTrampoline (in category 'initialization') -----
  genNonLocalReturnTrampoline
  	opcodeIndex := 0.
  	"write the return address to the coInterpreter instructionPointerAddress;
  	 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'
- 		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: false
  		resultReg: nil
  		appendOpcodes: true!

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
- 		callJumpBar: true
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: true
+ 		pushLinkReg: true
  		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
- 		callJumpBar: true
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: true
+ 		pushLinkReg: true
  		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
- 		callJumpBar: true
  		numArgs: 0
  		arg: nil
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		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
- 		callJumpBar: true
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		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
- 		callJumpBar: true
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		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
- 		callJumpBar: true
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		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
- 		callJumpBar: true
  		numArgs: 4
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:arg:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 result: resultReg
  	"Generate a trampoline with two arguments that answers a result.
  	 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
- 		callJumpBar: true
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:arg:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 arg: regOrConst1 result: resultReg
  	"Generate a trampoline with two arguments that answers a result.
  	 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
- 		callJumpBar: true
  		numArgs: 2
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was changed:
  ----- Method: Cogit>>genTrampolineFor:called:arg:result: (in category 'initialization') -----
  genTrampolineFor: aRoutine called: aString arg: regOrConst0 result: resultReg
  	"Generate a trampoline with one argument that answers a result.
  	 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
- 		callJumpBar: true
  		numArgs: 1
  		arg: regOrConst0
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: resultReg
  		appendOpcodes: false!

Item was removed:
- ----- Method: Cogit>>genTrampolineFor:called:callJumpBar:numArgs:arg:arg:arg:arg:saveRegs:resultReg:appendOpcodes: (in category 'initialization') -----
- genTrampolineFor: aRoutine called: trampolineName callJumpBar: callJumpBar "<Boolean>" numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 saveRegs: saveRegs resultReg: resultRegOrNil appendOpcodes: appendBoolean
- 	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutineOrNil
- 	 as requested by callJumpBar.  If generating a call and resultRegOrNil is non-zero pass the C result
- 	 back in resultRegOrNil.
- 	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
- 	<var: #aRoutine type: #'void *'>
- 	<var: #trampolineName type: #'char *'>
- 	| startAddress |
- 	<inline: false>
- 	startAddress := methodZoneBase.
- 	appendBoolean ifFalse:
- 		[opcodeIndex := 0].
- 	self compileTrampolineFor: aRoutine
- 		callJumpBar: callJumpBar
- 		numArgs: numArgs
- 		arg: regOrConst0
- 		arg: regOrConst1
- 		arg: regOrConst2
- 		arg: regOrConst3
- 		saveRegs: saveRegs
- 		resultReg: resultRegOrNil.
- 	self outputInstructionsForGeneratedRuntimeAt: startAddress.
- 	self recordGeneratedRunTime: trampolineName address: startAddress.
- 	self recordRunTimeObjectReferences.
- 	^startAddress!

Item was added:
+ ----- Method: Cogit>>genTrampolineFor:called:numArgs:arg:arg:arg:arg:saveRegs:pushLinkReg:resultReg:appendOpcodes: (in category 'initialization') -----
+ genTrampolineFor: aRoutine called: trampolineName numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 saveRegs: saveRegs pushLinkReg: pushLinkReg resultReg: resultRegOrNil appendOpcodes: appendBoolean
+ 	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutineOrNil
+ 	 as requested by callJumpBar.  If generating a call and resultRegOrNil is non-zero pass the C result
+ 	 back in resultRegOrNil.
+ 	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
+ 	<var: #aRoutine type: #'void *'>
+ 	<var: #trampolineName type: #'char *'>
+ 	| startAddress |
+ 	<inline: false>
+ 	startAddress := methodZoneBase.
+ 	appendBoolean ifFalse:
+ 		[opcodeIndex := 0].
+ 	self compileTrampolineFor: aRoutine
+ 		numArgs: numArgs
+ 		arg: regOrConst0
+ 		arg: regOrConst1
+ 		arg: regOrConst2
+ 		arg: regOrConst3
+ 		saveRegs: saveRegs
+ 		pushLinkReg: pushLinkReg
+ 		resultReg: resultRegOrNil.
+ 	self outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	self recordGeneratedRunTime: trampolineName address: startAddress.
+ 	self recordRunTimeObjectReferences.
+ 	^startAddress!

Item was changed:
  ----- Method: Cogit>>generateNewspeakRuntime (in category 'initialization') -----
  generateNewspeakRuntime
  	<option: #NewspeakVM>
  	| jumpMiss jumpItsTheReceiverStupid |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
  	"Generate the non-send runtime support for Newspeak, explicit outer and implicit receiver.
  	 The dynamic frequency of explicit outer is so low we merely call an interpreter routine."
  	ceExplicitReceiverTrampoline := self genTrampolineFor: #ceExplicitReceiverAt:
  										called: 'ceExplicitReceiverTrampoline'
  										arg: SendNumArgsReg
  										result: ReceiverResultReg.
  	"Cached push implicit receiver implementation.  Caller looks like
  				mov selector, ClassReg
  				call ceImplicitReceiver
  				br continue
  		Lclass:	.word
  		Lmixin::	.word
  		continue:
  	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
  	 If 0, answer the actual receiver, otherwise the mixin.
  	 Generate the class fetch and cache probe inline for speed. Smashes Arg0Reg and caller-saved regs."
  	opcodeIndex := 0.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	objectRepresentation
  		genGetClassObjectOf: ReceiverResultReg
  		into: ClassReg
  		scratchReg: TempReg
  		instRegIsReceiver: true. "don't follow forwarding pointer here"
  	self MoveMw: 0 r: SPReg R: TempReg.
  	self MoveMw: backEnd jumpShortByteSize r: TempReg R: Arg1Reg.
  	self CmpR: ClassReg R: Arg1Reg.
  	jumpMiss := self JumpNonZero: 0.
  	self MoveMw: backEnd jumpShortByteSize + BytesPerOop r: TempReg R: ClassReg.
  	self CmpCq: 0 R: ClassReg.
  	jumpItsTheReceiverStupid := self JumpZero: 0.
  	self MoveR: ClassReg R: ReceiverResultReg.
  	jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
  	jumpMiss jmpTarget: self Label.
  	ceImplicitReceiverTrampoline := self
  										genTrampolineFor: #ceImplicitReceiverFor:receiver:class:
  										called: 'ceImplicitReceiverTrampoline'
- 										callJumpBar: true
  										numArgs: 3
  										arg: SendNumArgsReg
  										arg: ReceiverResultReg
  										arg: ClassReg
  										arg: nil
  										saveRegs: false
+ 										pushLinkReg: true
  										resultReg: ReceiverResultReg
  										appendOpcodes: true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
  	<var: #trampolineName type: #'char *'>
  	<inline: false>
  	opcodeIndex := 0.
  	"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
- 		callJumpBar: true
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimReturnEnterCogCodeEnilopmart: (in category 'initialization') -----
  genPrimReturnEnterCogCodeEnilopmart: profiling
  	"Generate the substitute return code for an external or FFI primitive call.
  	 On success simply return, extracting numArgs from newMethod.
  	 On primitive failure call ceActivateFailingPrimitiveMethod: newMethod."
  	| jmpSample continuePostSample jmpFail |
  	<var: #jmpSample type: #'AbstractInstruction *'>
  	<var: #continuePostSample type: #'AbstractInstruction *'>
  	<var: #jmpFail type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  
  	profiling ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick: if so.
  		  N.B. nextProfileTick is 64-bits so 32-bit systems need to test both halves."
  		BytesPerWord = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + BytesPerWord R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSample := self JumpNonZero: 0.
  		continuePostSample := self Label].
  
  	"Test primitive failure"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	self flag: 'ask concrete code gen if move sets condition codes?'.
  	self CmpCq: 0 R: TempReg.
  	jmpFail := self JumpNonZero: 0.
  
  	"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  		success:	stackPointer	->	result (was receiver)
  										arg1
  										...
  										argN
  										return pc
  		failure:							receiver
  										arg1
  										...
  					stackPointer	->	argN
  										return pc
  	We push the instructionPointer to reestablish the return pc in the success case,
  	but leave it to ceActivateFailingPrimitiveMethod: to do so in the failure case."
  
  	backEnd hasLinkRegister
  		ifTrue:
  			[backEnd genLoadStackPointers.									"Switch back to Smalltalk stack."
  			 self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  			 self MoveAw: coInterpreter instructionPointerAddress R: LinkReg.	"Get and restore ret pc"
  			 self RetN: BytesPerWord]											"Return, popping result from stack"
  		ifFalse:
  			[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.	"Get return pc"
  			 backEnd genLoadStackPointers.									"Switch back to Smalltalk stack."
  			 self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  			 self MoveR: ClassReg Mw: 0 r: SPReg.								"Restore return pc"
  			 self RetN: 0].														"Return, popping result from stack"
  
  	"Primitive failed.  Invoke C code to build the frame and continue."
  	jmpFail jmpTarget: (self MoveAw: coInterpreter newMethodAddress R: SendNumArgsReg).
  	"Reload sp with CStackPointer; easier than popping args of checkProfileTick."
  	self MoveAw: self cStackPointerAddress R: SPReg.
  	cStackAlignment > BytesPerWord ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: false
  			numArgs: 1
  			wordAlignment: cStackAlignment / BytesPerWord].
  	backEnd genPassReg: SendNumArgsReg asArgument: 0.
  	self CallRT: (self cCode: '(unsigned long)ceActivateFailingPrimitiveMethod'
  					inSmalltalk: [self simulatedTrampolineFor: #ceActivateFailingPrimitiveMethod:]).
  
  	profiling ifTrue:
+ 		["Call ceCheckProfileTick: to record sample and then continue.  newMethod
+ 		 should be up-to-date.  Need to save and restore the link reg around this call."
- 		["Call ceCheckProfileTick: to record sample and then continue.
- 		  newMethod should be up-to-date."
  		 jmpSample jmpTarget: self Label.
+ 		 backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  		 self CallRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
+ 		 backEnd hasLinkRegister ifTrue: [self PopR: LinkReg].
  		 self Jump: continuePostSample]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genMustBeBooleanTrampolineFor:called: (in category 'initialization') -----
  genMustBeBooleanTrampolineFor: boolean called: trampolineName
  	"This can be entered in one of two states, depending on SendNumArgsReg. See
  	 e.g. genJumpIf:to:.  If SendNumArgsReg is non-zero then this has been entered via
  	 the initial test of the counter in the jump executed count (i.e. the counter has
  	 tripped).  In this case TempReg contains the boolean to be tested and should not
  	 be offset, and ceCounterTripped should be invoked with the unoffset TempReg.
  	 If SendNumArgsReg is zero then this has been entered for must-be-boolean
  	 processing. TempReg has been offset by boolean and must be corrected and
  	 ceSendMustBeBoolean: invoked with the corrected value."
  	<var: #trampolineName type: #'char *'>
  	| jumpMBB |
  	<var: #jumpMBB type: #'AbstractInstruction *'>
  	<inline: false>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: SendNumArgsReg.
  	jumpMBB := self JumpZero: 0.
  	self compileTrampolineFor: #ceCounterTripped:
- 		callJumpBar: true
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil.
  	"For the case where the ceCounterTripped: call returns (e.g. because there's no callback selector
  	 installed), the call to the ceSendMustBeBooleanAddTrue/FalseTrampoline is followed by a jump
  	 back to the start of the counter/condition test sequence.  For this case copy the C result to
  	 TempReg (the register that is tested), to reload it with the boolean to be tested."
  	backEnd cResultRegister ~= TempReg ifTrue:
  		[self MoveR: backEnd cResultRegister R: TempReg].
  	"If the objectRepresentation does want true & false to be mobile then we need to record these addresses."
  	self assert: (objectRepresentation shouldAnnotateObjectReference: boolean) not.
  	jumpMBB jmpTarget: (self AddCq: boolean R: TempReg).
  	^self genTrampolineFor: #ceSendMustBeBoolean:
  		called: trampolineName
- 		callJumpBar: true
  		numArgs: 1
  		arg: TempReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genMethodAbortTrampolineFor: (in category 'initialization') -----
  genMethodAbortTrampolineFor: numArgs
  	
  	"Generate the abort for a method.  This abort performs either a call of ceSICMiss:
  	 to handle a single-in-line cache miss or a call of ceStackOverflow: to handle a
  	 stack overflow.  It distinguishes the two by testing ResultReceiverReg.  If the
  	 register is zero then this is a stack-overflow because a) the receiver has already
  	 been pushed and so can be set to zero before calling the abort, and b) the
  	 receiver must always contain an object (and hence be non-zero) on SIC miss."
  	| jumpSICMiss |
  	<var: #jumpSICMiss type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  	self CmpCq: 0 R: ReceiverResultReg.
  	jumpSICMiss := self JumpNonZero: 0.
  	"on machines with a link register, pop the stack if the ReceiverResultReg = 0,
  	 i.e. if coming through the stack check abort; frame build has already pushed it."
  	backEnd hasLinkRegister ifTrue:
  		[self AddCq: BytesPerWord R: SPReg].
  
  	self compileTrampolineFor: #ceStackOverflow:
- 		callJumpBar: true
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
  	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genTrampolineFor: #ceSICMiss:
  		called: (self trampolineName: 'ceMethodAbort' numArgs: (numArgs <= self numRegArgs ifTrue: [numArgs] ifFalse: [-1]))
- 		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPICMissTrampolineFor: (in category 'initialization') -----
  genPICMissTrampolineFor: numArgs
  	<inline: false>
  	| startAddress |
  	startAddress := methodZoneBase.
  	opcodeIndex := 0.
  	"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.
  	self genTrampolineFor: #ceCPICMiss:receiver:
  		called: (self trampolineName: 'cePICMiss' numArgs: (numArgs <= self numRegArgs ifTrue: [numArgs] ifFalse: [-1]))
- 		callJumpBar: true
  		numArgs: 2
  		arg: ClassReg
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendTrampolineFor:numArgs:called:arg:arg:arg: (in category 'initialization') -----
  genSendTrampolineFor: aRoutine numArgs: numArgs 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 *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
  	opcodeIndex := 0.
  	backEnd genPushRegisterArgsForNumArgs: numArgs.
  	self genTrampolineFor: aRoutine
  		called: aString
- 		callJumpBar: true
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSendTrampolineFor:numArgs:called:arg:arg:arg:arg: (in category 'initialization') -----
  genSendTrampolineFor: aRoutine numArgs: numArgs 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 *'>
  	| startAddress |
  	<inline: false>
  	startAddress := methodZoneBase.
  	opcodeIndex := 0.
  	backEnd genPushRegisterArgsForNumArgs: numArgs.
  	self genTrampolineFor: aRoutine
  		called: aString
- 		callJumpBar: true
  		numArgs: 4
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		saveRegs: false
+ 		pushLinkReg: true
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!



More information about the Vm-dev mailing list