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

commits at source.squeak.org commits at source.squeak.org
Thu May 15 17:58:33 UTC 2014


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

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

Name: VMMaker.oscog-eem.717
Author: eem
Time: 15 May 2014, 10:55:22.73 am
UUID: 357b0629-ccf0-45a8-92d9-a2c9a881f172
Ancestors: VMMaker.oscog-eem.716

Refactor the code around pushing register arguments and
switching between the Smalltalk and C stacks, moving the
actual generators into backEnd (the special instance of
the relevant CogAbstractInstruction subclass) .  This allows
CogARMInstruction to handle pushing the register args and
hence handle the difference of having a link reg.

Combine genSaveStackPointers & genLoadCStackPointers
into Cogit>>genSmalltalkToCStackSwitch.

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

Item was added:
+ ----- Method: CogARMCompiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
+ genLoadCStackPointer
+ 	"Load the stack pointer register with that of the C stack, effecting
+ 	 a switch to the C stack.  Used when machine code calls into the
+ 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	^0!

Item was added:
+ ----- Method: CogARMCompiler>>genLoadCStackPointers (in category 'smalltalk calling convention') -----
+ genLoadCStackPointers
+ 	"Load the frame and stack pointer registers with those of the C stack,
+ 	 effecting a switch to the C stack.  Used when machine code calls into
+ 	 the CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogARMCompiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
+ genLoadStackPointers
+ 	"Switch back to the Smalltalk stack. Assign SPReg first
+ 	 because typically it is used immediately afterwards."
+ 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit framePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogARMCompiler>>genPushRegisterArgsForAbortMissNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForAbortMissNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the outer and
+ 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
+ 	 outer retpc is that of a call at a send site.  The inner is the call
+ 	 from a method or PIC abort/miss to the trampoline."
+ 
+ 	"Putting the receiver and args above the return address means the
+ 	 CoInterpreter has a single machine-code frame format which saves
+ 	 us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		sp		->	outerRetpc		(send site retpc)
+ 		linkReg = innerRetpc		(PIC abort/miss retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 		sp		->	outerRetpc		(send site retpc)
+ 		linkReg = innerRetpc		(PIC abort/miss retpc)"
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
+ 		 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]].
+ 		cogit PushR: TempReg] "Restore return address"!

Item was added:
+ ----- Method: CogARMCompiler>>genPushRegisterArgsForNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
+ 	"This is easy on a RISC like ARM because the return address is in the link register.  Putting
+ 	 the receiver and args above the return address means the CoInterpreter has a single
+ 	 machine-code frame format which saves us a lot of work."
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: ReceiverResultReg.
+ 			 cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]]]!

Item was added:
+ ----- Method: CogARMCompiler>>genSaveStackPointers (in category 'smalltalk calling convention') -----
+ genSaveStackPointers
+ 	"Save the frame and stack pointer registers to the framePointer
+ 	 and stackPointer variables.  Used to save the machine code frame
+ 	 for use by the run-time when calling into the CoInterpreter run-time."
+ 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
+ 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
+ 	^0!

Item was added:
+ ----- Method: CogAbstractInstruction>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
+ genLoadCStackPointer
+ 	"Load the stack pointer register with that of the C stack, effecting
+ 	 a switch to the C stack.  Used when machine code calls into the
+ 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genLoadCStackPointers (in category 'smalltalk calling convention') -----
+ genLoadCStackPointers
+ 	"Load the frame and stack pointer registers with those of the C stack,
+ 	 effecting a switch to the C stack.  Used when machine code calls into
+ 	 the CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genLoadStackPointers (in category 'smalltalk calling convention') -----
+ genLoadStackPointers
+ 	"Switch back to the Smalltalk stack. Assign SPReg first
+ 	 because typically it is used immediately afterwards."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genPushRegisterArgsForAbortMissNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForAbortMissNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the outer and
+ 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
+ 	 outer retpc is that of a call at a send site.  The inner is the call
+ 	 from a method or PIC abort/miss to the trampoline."
+ 
+ 	"This won't be as clumsy on a RISC.  But putting the receiver and
+ 	 args above the return address means the CoInterpreter has a
+ 	 single machine-code frame format which saves us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		base	->	outerRetpc		(send site retpc)
+ 		sp		->	innerRetpc		(PIC abort/miss retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 					outerRetpc
+ 		sp		->	innerRetpc		(PIC abort/miss retpc)"
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genPushRegisterArgsForNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
+ 	"This won't be as clumsy on a RISC.  But putting the receiver and
+ 	 args above the return address means the CoInterpreter has a
+ 	 single machine-code frame format which saves us a lot of work."
+ 
+ 	"This won't be as clumsy on a RISC.  But putting the receiver and
+ 	 args above the return address means the CoInterpreter has a
+ 	 single machine-code frame format which saves us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		sp		->	retpc		(send site retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 		sp		->	retpc		(send site retpc)"
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction>>genSaveStackPointers (in category 'smalltalk calling convention') -----
+ genSaveStackPointers
+ 	"Save the frame and stack pointer registers to the framePointer
+ 	 and stackPointer variables.  Used to save the machine code frame
+ 	 for use by the run-time when calling into the CoInterpreter run-time."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogIA32Compiler>>genLoadCStackPointer (in category 'smalltalk calling convention') -----
+ genLoadCStackPointer
+ 	"Load the stack pointer register with that of the C stack, effecting
+ 	 a switch to the C stack.  Used when machine code calls into the
+ 	 CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	^0!

Item was added:
+ ----- Method: CogIA32Compiler>>genLoadCStackPointers (in category 'smalltalk calling convention') -----
+ genLoadCStackPointers
+ 	"Load the frame and stack pointer registers with those of the C stack,
+ 	 effecting a switch to the C stack.  Used when machine code calls into
+ 	 the CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogIA32Compiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
+ genLoadStackPointers
+ 	"Switch back to the Smalltalk stack. Assign SPReg first
+ 	 because typically it is used immediately afterwards."
+ 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit framePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogIA32Compiler>>genPushRegisterArgsForAbortMissNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForAbortMissNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the outer and
+ 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
+ 	 outer retpc is that of a call at a send site.  The inner is the call
+ 	 from a method or PIC abort/miss to the trampoline."
+ 
+ 	"This won't be as clumsy on a RISC.  But putting the receiver and
+ 	 args above the return address means the CoInterpreter has a
+ 	 single machine-code frame format which saves us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		base	->	outerRetpc		(send site retpc)
+ 		sp		->	innerRetpc		(PIC abort/miss retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 					outerRetpc
+ 		sp		->	innerRetpc		(PIC abort/miss retpc)"
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 numArgs = 0 ifTrue:
+ 			[cogit MoveMw: 0 r: SPReg R: TempReg.
+ 			 cogit PushR: TempReg.
+ 			 cogit MoveMw: BytesPerWord * 2 r: SPReg R: TempReg.
+ 			 cogit MoveR: TempReg Mw: BytesPerWord r: SPReg.
+ 			 cogit MoveR: ReceiverResultReg Mw: 2 * BytesPerWord r: SPReg.
+ 			 ^self].
+ 		 numArgs = 1 ifTrue:
+ 			[cogit MoveMw: BytesPerWord r: SPReg R: TempReg.
+ 			 cogit PushR: TempReg.
+ 			 cogit MoveMw: BytesPerWord r: SPReg R: TempReg.
+ 			 cogit PushR: TempReg.
+ 			 cogit MoveR: ReceiverResultReg Mw: 3 * BytesPerWord r: SPReg.
+ 			 cogit MoveR: Arg0Reg Mw: 2 * BytesPerWord r: SPReg.
+ 			 ^self].
+ 		 numArgs = 2 ifTrue:
+ 			[cogit PushR: Arg1Reg.
+ 			 cogit MoveMw: BytesPerWord * 2 r: SPReg R: TempReg.
+ 			 cogit PushR: TempReg.
+ 			 cogit MoveMw: BytesPerWord * 2 r: SPReg R: TempReg.
+ 			 cogit PushR: TempReg.
+ 			 cogit MoveR: ReceiverResultReg Mw: 4 * BytesPerWord r: SPReg.
+ 			 cogit MoveR: Arg0Reg Mw: 3 * BytesPerWord r: SPReg.
+ 			 ^self]]!

Item was added:
+ ----- Method: CogIA32Compiler>>genPushRegisterArgsForNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
+ 	"This won't be as clumsy on a RISC.  But putting the receiver and
+ 	 args above the return address means the CoInterpreter has a
+ 	 single machine-code frame format which saves us a lot of work."
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 false "these two variants show the same performance on Intel Core i7, but the second one may be shorter."
+ 			ifTrue:
+ 				[cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
+ 				 numArgs > 0 ifTrue:
+ 					[cogit PushR: Arg0Reg.
+ 					 numArgs > 1 ifTrue:
+ 						[cogit PushR: Arg1Reg]].
+ 				 cogit PushR: TempReg.
+ 				 cogit MoveR: ReceiverResultReg Mw: BytesPerWord * (1 + numArgs) r: SPReg]
+ 			ifFalse:
+ 				[cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
+ 				 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 				 numArgs > 0 ifTrue:
+ 					[cogit PushR: Arg0Reg.
+ 					 numArgs > 1 ifTrue:
+ 						[cogit PushR: Arg1Reg]].
+ 				cogit PushR: TempReg]] "Restore return address"!

Item was added:
+ ----- Method: CogIA32Compiler>>genSaveStackPointers (in category 'smalltalk calling convention') -----
+ genSaveStackPointers
+ 	"Save the frame and stack pointer registers to the framePointer
+ 	 and stackPointer variables.  Used to save the machine code frame
+ 	 for use by the run-time when calling into the CoInterpreter run-time."
+ 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
+ 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
+ 	^0!

Item was changed:
  ----- 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.
- 	self genSaveStackPointers.
- 	self genLoadCStackPointers.
  	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.
- 		self genLoadStackPointers.
  		backEnd hasLinkRegister ifTrue:
  			[self PopR: LinkReg].
  		self RetN: 0]!

Item was added:
+ ----- Method: Cogit>>framePointerAddress (in category 'simulation only') -----
+ framePointerAddress
+ 	"redirect for the backEnd's genSaveStackPointers"
+ 	<doNotGenerate>
+ 	^coInterpreter framePointerAddress!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 and: regArg3 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
- 	self genLoadStackPointers.
  	self PopR: regArg3.
  	self PopR: regArg2.
  	self PopR: regArg1.
  	self RetN: 0.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2 called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
- 	self genLoadStackPointers.
  	self PopR: regArg2.
  	self PopR: regArg1.
  	self RetN: 0.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:called: (in category 'initialization') -----
  genEnilopmartFor: regArg called: trampolineName
  	"An enilopmart (the reverse of a trampoline) is a piece of code that makes
  	 the system-call-like transition from the C runtime into generated machine
  	 code.  The desired arguments and entry-point are pushed on a stackPage's
  	 stack.  The enilopmart pops off the values to be loaded into registers and
  	 then executes a return instruction to pop off the entry-point and jump to it."
  	<returnTypeC: 'void (*genEnilopmartForcalled(sqInt regArg, char *trampolineName))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
- 	self genLoadStackPointers.
  	self PopR: regArg.
  	self RetN: 0.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was removed:
- ----- Method: Cogit>>genLoadCStackPointers (in category 'trampoline support') -----
- genLoadCStackPointers
- 	self MoveAw: self cStackPointerAddress R: SPReg.
- 	cFramePointerInUse ifTrue:
- 		[self MoveAw: self cFramePointerAddress R: FPReg].
- 	^0!

Item was removed:
- ----- Method: Cogit>>genLoadStackPointers (in category 'trampoline support') -----
- genLoadStackPointers
- 	"Switch back to the Smalltalk stack. Assign SPReg first
- 	 because typically it is used immediately afterwards."
- 	self MoveAw: coInterpreter stackPointerAddress R: SPReg.
- 	self MoveAw: coInterpreter framePointerAddress R: FPReg.
- 	^0!

Item was removed:
- ----- Method: Cogit>>genSaveStackPointers (in category 'trampoline support') -----
- genSaveStackPointers
- 	self MoveR: FPReg Aw: coInterpreter framePointerAddress.
- 	self MoveR: SPReg Aw: coInterpreter stackPointerAddress.
- 	^0!

Item was added:
+ ----- Method: Cogit>>genSmalltalkToCStackSwitch (in category 'trampoline support') -----
+ genSmalltalkToCStackSwitch
+ 	backEnd genSaveStackPointers.
+ 	cFramePointerInUse
+ 		ifTrue: [backEnd genLoadCStackPointers]
+ 		ifFalse: [backEnd genLoadCStackPointer].
+ 	^0!

Item was added:
+ ----- Method: Cogit>>stackPointerAddress (in category 'simulation only') -----
+ stackPointerAddress
+ 	"redirect for the backEnd's genSaveStackPointers"
+ 	<doNotGenerate>
+ 	^coInterpreter stackPointerAddress!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| flags jmp jmpSamplePrim continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  	<var: #jmp type: #'AbstractInstruction *'>
  	<var: #jmpSamplePrim type: #'AbstractInstruction *'>
  	<var: #continuePostSamplePrim type: #'AbstractInstruction *'>
  	<var: #jmpSampleNonPrim type: #'AbstractInstruction *'>
  	<var: #continuePostSampleNonPrim type: #'AbstractInstruction *'>
  
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	flags := coInterpreter primitivePropertyFlags: primitiveIndex.
  	(flags bitAnd: PrimCallCollectsProfileSamples) ~= 0 ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  		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."
  		jmpSampleNonPrim := self JumpNonZero: 0.
  		continuePostSampleNonPrim := self Label].
  
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self MoveCq: methodOrBlockNumArgs R: TempReg].
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  	(flags bitAnd: PrimCallNeedsPrimitiveFunction) ~= 0 ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	"Old full prim trace is in VMMaker-eem.550 and prior"
  	self recordPrimTrace ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  	((flags bitAnd: PrimCallNeedsNewMethod+PrimCallMayCallBack) ~= 0) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags bitAnd: PrimCallMayCallBack) ~= 0 ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags bitAnd: PrimCallMayCallBack) ~= 0
  		ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
  			[backEnd genSubstituteReturnAddress:
  				((flags bitAnd: PrimCallCollectsProfileSamples) ~= 0
  					ifTrue: [cePrimReturnEnterCogCodeProfiling]
  					ifFalse: [cePrimReturnEnterCogCode]).
  			 self JumpRT: primitiveRoutine asInteger.
  			 primInvokeLabel := self Label.
  			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  		ifFalse:
  			["Call the C primitive routine."
  			self CallRT: primitiveRoutine asInteger.
  			primInvokeLabel := self Label.
  			(flags bitAnd: PrimCallCollectsProfileSamples) ~= 0 ifTrue:
  				[self assert: (flags bitAnd: PrimCallNeedsNewMethod) ~= 0.
  				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
  				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."
  				jmpSamplePrim := self JumpNonZero: 0.
  				continuePostSamplePrim := self Label].
  			"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
  			In either case we can push the instructionPointer to reestablish the return pc"
  			self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
+ 			backEnd genLoadStackPointers.
- 			self genLoadStackPointers.
  			"Test primitive failure"
  			self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  			self PushR: ClassReg. "Restore return pc"
  			self flag: 'ask concrete code gen if move sets condition codes?'.
  			self CmpCq: 0 R: TempReg.
  			jmp := self JumpNonZero: 0.
  			"Fetch result from stack"
  			self MoveMw: BytesPerWord r: SPReg R: ReceiverResultReg.
  			self flag: 'currently caller pushes result'.
  			self RetN: BytesPerWord].
  
  	(flags bitAnd: PrimCallCollectsProfileSamples) ~= 0 ifTrue:
  		["The sample is collected by cePrimReturnEnterCogCode for external calls"
  		jmpSamplePrim notNil ifTrue:
  			["Call ceCheckProfileTick: to record sample and then continue."
  			jmpSamplePrim jmpTarget: self Label.
  			self assert: (flags bitAnd: PrimCallNeedsNewMethod) ~= 0.
  			self CallRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  							   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  			"reenter the post-primitive call flow"
  			self Jump: continuePostSamplePrim].
  		"Null newMethod and call ceCheckProfileTick: to record sample and then continue.
  		 ceCheckProfileTick will map null/0 to coInterpreter nilObject"
  		jmpSampleNonPrim jmpTarget: self Label.
  		self MoveCq: 0 R: TempReg.
  		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  		self CallRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		"reenter the post-primitive call flow"
  		self Jump: continuePostSampleNonPrim].
  
  	jmp notNil ifTrue:
  		["Jump to restore of receiver reg and proceed to frame build for failure."
  		 jmp jmpTarget: self Label.
  		 "Restore receiver reg from stack."
  		 self MoveMw: BytesPerWord * (methodOrBlockNumArgs + 1) r: SPReg R: ReceiverResultReg].
  	^0!

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."
  
  	self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
+ 	backEnd genLoadStackPointers.
- 	self genLoadStackPointers.
  	self PushR: ClassReg. "Restore return pc"
  	"Fetch result from stack"
  	self MoveMw: BytesPerWord r: SPReg R: ReceiverResultReg.
  	self flag: 'currently caller pushes result'.
  	self RetN: BytesPerWord.
  
  	"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."
  		 jmpSample jmpTarget: self Label.
  		 self CallRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		 self Jump: continuePostSample]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileOpenPIC:numArgs: (in category 'in-line cacheing') -----
  compileOpenPIC: selector numArgs: numArgs
  	"Compile the code for an open PIC.  Perform a probe of the first-level method
  	 lookup cache followed by a call of ceSendFromInLineCacheMiss: if the probe fails.
  	 Override to push the register args when calling ceSendFromInLineCacheMiss:"
  	| jumpSelectorMiss jumpClassMiss itsAHit jumpBCMethod routine |
  	<var: #jumpSelectorMiss type: #'AbstractInstruction *'>
  	<var: #jumpClassMiss type: #'AbstractInstruction *'>
  	<var: #itsAHit type: #'AbstractInstruction *'>
  	<var: #jumpBCMethod type: #'AbstractInstruction *'>
  	self compilePICProlog: numArgs.
  	self cppIf: NewspeakVM ifTrue:
  		[self Nop. "1st nop differentiates dynSuperEntry from no-check entry if using nextMethod"
  		 dynSuperEntry := self Nop].
  	entry := objectRepresentation genGetClassTagOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  
  	"Do first of three probes.  See CoInterpreter>>lookupInMethodCacheSel:classTag:"
  	self flag: #lookupInMethodCacheSel:classTag:. "so this method shows up as a sender of lookupInMethodCacheSel:class:"
  	self MoveR: ClassReg R: SendNumArgsReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: ShiftForWord R: ClassReg.
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	jumpClassMiss := self JumpNonZero: 0.
  
  	itsAHit := self Label.
  	"Fetch the method.  The interpret trampoline requires the bytecoded method in SendNumArgsReg"
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheMethod << ShiftForWord)
  		r: ClassReg
  		R: SendNumArgsReg.
  	"If the method is compiled jump to its unchecked entry-point, otherwise interpret it."
  	objectRepresentation
  		genLoadSlot: HeaderIndex sourceReg: SendNumArgsReg destReg: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	jumpBCMethod := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
  	jumpBCMethod jmpTarget: interpretCall.
  	self AddCq: cmNoCheckEntryOffset R: ClassReg.
  	self JumpR: ClassReg.
  
  	"First probe missed.  Do second of three probes.  Shift hash right one and retry."
  	jumpSelectorMiss jmpTarget: (jumpClassMiss jmpTarget: self Label).
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	self LogicalShiftLeftCq: ShiftForWord - 1 R: ClassReg.
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Second probe missed.  Do last probe.  Shift hash right two and retry."
  	jumpSelectorMiss jmpTarget: self Label.
  	self MoveR: SendNumArgsReg R: ClassReg.
  	self annotate: (self XorCw: selector R: ClassReg) objRef: selector.
  	ShiftForWord > 2 ifTrue:
  		[self LogicalShiftLeftCq: ShiftForWord - 1 R: ClassReg].
  	self AndCq: MethodCacheMask << ShiftForWord R: ClassReg.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheSelector << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self annotate: (self CmpCw: selector R: TempReg) objRef: selector.
  	jumpSelectorMiss := self JumpNonZero: 0.
  	self MoveMw: coInterpreter methodCacheAddress asUnsignedInteger + (MethodCacheClass << ShiftForWord)
  		r: ClassReg
  		R: TempReg.
  	self CmpR: SendNumArgsReg R: TempReg.
  	self JumpZero: itsAHit.
  
  	"Last probe missed.  Call ceSendFromInLineCacheMiss: to do the full lookup."
  	jumpSelectorMiss jmpTarget: self Label.
+ 	backEnd genPushRegisterArgsForNumArgs: numArgs.
+ 	self genSmalltalkToCStackSwitch.
- 	self genPushRegisterArgsForNumArgs: numArgs.
- 	self genSaveStackPointers.
- 	self genLoadCStackPointers.
  	methodLabel addDependent: (self annotateAbsolutePCRef: (self MoveCw: methodLabel asInteger R: SendNumArgsReg)).
  	cStackAlignment > BytesPerWord ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: false
  			numArgs: 1
  			wordAlignment: cStackAlignment / BytesPerWord].
  	backEnd genPassReg: SendNumArgsReg asArgument: 0.
  	routine := self cCode: '(sqInt)ceSendFromInLineCacheMiss'
  					inSmalltalk: [self simulatedAddressFor: #ceSendFromInLineCacheMiss:].
  	self annotateCall: (self Call: routine)
  	"Note that this call does not return."!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
  genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
  	"Receiver and arg in registers.
  	 Stack looks like
  		return address"
  	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
  	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
  	<var: #jumpFailClass type: #'AbstractInstruction *'>
  	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
  	<var: #jumpImmediate type: #'AbstractInstruction *'>
  	<var: #jumpNonInt type: #'AbstractInstruction *'>
  	<var: #jumpFailCheck type: #'AbstractInstruction *'>
  	<var: #doOp type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: TempReg.
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  	self MoveR: Arg0Reg R: ClassReg.
  	jumpImmediate := objectRepresentation genJumpImmediateInScratchReg: TempReg.
  	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
  	self CmpCq: objectMemory classFloatCompactIndex R: SendNumArgsReg.
  	jumpFailClass := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	doOp := self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
  	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
  	jumpFailAlloc := objectRepresentation
  						genAllocFloatValue: DPFPReg0
  						into: SendNumArgsReg
  						scratchReg: ClassReg
  						scratchReg: TempReg.
  	self MoveR: SendNumArgsReg R: ReceiverResultReg.
  	self RetN: 0.
  	"We need to push the register args on two paths; this one and the interpreter primitive path.
  	But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
  	self assert: methodOrBlockNumArgs <= self numRegArgs.
  	jumpFailClass jmpTarget: self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
+ 	backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs.
- 	self genPushRegisterArgsForNumArgs: methodOrBlockNumArgs.
  	jumpFailClass := self Jump: 0.
  	jumpImmediate jmpTarget: self Label.
  	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
  		[jumpNonInt := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg].
  	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
  	self ConvertR: ClassReg Rd: DPFPReg1.
  	self Jump: doOp.
  	jumpFailAlloc jmpTarget: self Label.
  	self compileFallbackToInterpreterPrimitive.
  	jumpFailClass jmpTarget: self Label.
  	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
  		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genEnterPICEnilopmartNumArgs: (in category 'initialization') -----
  genEnterPICEnilopmartNumArgs: numArgs
  	"Generate special versions of the ceEnterCogCodePopReceiverAndClassRegs
  	 enilopmart that also pop register args from the stack to undo the pushing of
  	 register args in the abort/miss trampolines."
  	<returnTypeC: 'void (*genEnterPICEnilopmartNumArgs(sqInt numArgs))(void)'>
  	| size endAddress enilopmart |
  	opcodeIndex := 0.
+ 	backEnd genLoadStackPointers.
- 	self genLoadStackPointers.
  	self PopR: ClassReg. "cacheTag"
  	self PopR: TempReg. "entry-point"
  	self PopR: SendNumArgsReg. "retpc"
  	numArgs > 0 ifTrue:
  		[numArgs > 1 ifTrue:
  			[self PopR: Arg1Reg.
  			 self assert: self numRegArgs = 2].
  		 self PopR: Arg0Reg].
  	self PopR: ReceiverResultReg.
  	self PushR: SendNumArgsReg. "retpc"
  	self JumpR: TempReg.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd nopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: (self trampolineName: 'ceEnterPIC' numArgs: numArgs) address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

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.
  	self compileTrampolineFor: #ceStackOverflow:
  		callJumpBar: true
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil.
  	jumpSICMiss jmpTarget: self Label.
+ 	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
- 	self 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
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPICAbortTrampolineFor: (in category 'initialization') -----
  genPICAbortTrampolineFor: numArgs
  	"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."
  	opcodeIndex := 0. 
+ 	backEnd genPushRegisterArgsForAbortMissNumArgs: numArgs.
- 	self genPushRegisterArgsForAbortMissNumArgs: numArgs.
  	^self genInnerPICAbortTrampoline: (self trampolineName: 'cePICAbort' numArgs: (numArgs <= self numRegArgs ifTrue: [numArgs] ifFalse: [-1]))!

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 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
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPushRegisterArgs (in category 'compile abstract instructions') -----
  genPushRegisterArgs
  	"Ensure that the register args are pushed before the retpc for methods with arity <= self numRegArgs."
  	"This won't be as clumsy on a RISC.  But putting the receiver and
  	 args above the return address means the CoInterpreter has a
  	 single machine-code frame format which saves us a lot of work."
  	(regArgsHaveBeenPushed
  	 or: [methodOrBlockNumArgs > self numRegArgs]) ifFalse:
+ 		[backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs.
- 		[self genPushRegisterArgsForNumArgs: methodOrBlockNumArgs.
  		regArgsHaveBeenPushed := true]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPushRegisterArgsForAbortMissNumArgs: (in category 'compile abstract instructions') -----
- genPushRegisterArgsForAbortMissNumArgs: numArgs
- 	"Ensure that the register args are pushed before the outer and
- 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
- 	 outer retpc is that of a call at a send site.  The inner is the call
- 	 from a method or PIC abort/miss to the trampoline."
- 
- 	"This won't be as clumsy on a RISC.  But putting the receiver and
- 	 args above the return address means the CoInterpreter has a
- 	 single machine-code frame format which saves us a lot of work."
- 
- 	"Iff there are register args convert
- 		base	->	outerRetpc		(send site retpc)
- 		sp		->	innerRetpc		(PIC abort/miss retpc)
- 	 to
- 		base	->	receiver
- 					(arg0)
- 					(arg1)
- 					outerRetpc
- 		sp		->	innerRetpc		(PIC abort/miss retpc)"
- 	numArgs <= self numRegArgs ifTrue:
- 		[self assert: self numRegArgs <= 2.
- 		 numArgs = 0 ifTrue:
- 			[self MoveMw: 0 r: SPReg R: TempReg.
- 			 self PushR: TempReg.
- 			 self MoveMw: BytesPerWord * 2 r: SPReg R: TempReg.
- 			 self MoveR: TempReg Mw: BytesPerWord r: SPReg.
- 			 self MoveR: ReceiverResultReg Mw: 2 * BytesPerWord r: SPReg.
- 			 ^self].
- 		 numArgs = 1 ifTrue:
- 			[self MoveMw: BytesPerWord r: SPReg R: TempReg.
- 			 self PushR: TempReg.
- 			 self MoveMw: BytesPerWord r: SPReg R: TempReg.
- 			 self PushR: TempReg.
- 			 self MoveR: ReceiverResultReg Mw: 3 * BytesPerWord r: SPReg.
- 			 self MoveR: Arg0Reg Mw: 2 * BytesPerWord r: SPReg.
- 			 ^self].
- 		 numArgs = 2 ifTrue:
- 			[self PushR: Arg1Reg.
- 			 self MoveMw: BytesPerWord * 2 r: SPReg R: TempReg.
- 			 self PushR: TempReg.
- 			 self MoveMw: BytesPerWord * 2 r: SPReg R: TempReg.
- 			 self PushR: TempReg.
- 			 self MoveR: ReceiverResultReg Mw: 4 * BytesPerWord r: SPReg.
- 			 self MoveR: Arg0Reg Mw: 3 * BytesPerWord r: SPReg.
- 			 ^self]]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genPushRegisterArgsForNumArgs: (in category 'compile abstract instructions') -----
- genPushRegisterArgsForNumArgs: numArgs
- 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
- 	"This won't be as clumsy on a RISC.  But putting the receiver and
- 	 args above the return address means the CoInterpreter has a
- 	 single machine-code frame format which saves us a lot of work."
- 	numArgs <= self numRegArgs ifTrue:
- 		[self assert: self numRegArgs <= 2.
- 		 false "these two variants show the same performance on Intel Core i7, but the second one may be shorter."
- 			ifTrue:
- 				[self MoveMw: 0 r: SPReg R: TempReg. "Save return address"
- 				 numArgs > 0 ifTrue:
- 					[self PushR: Arg0Reg.
- 					 numArgs > 1 ifTrue:
- 						[self PushR: Arg1Reg]].
- 				 self PushR: TempReg.
- 				 self MoveR: ReceiverResultReg Mw: BytesPerWord * (1 + numArgs) r: SPReg]
- 			ifFalse:
- 				[self MoveMw: 0 r: SPReg R: TempReg. "Save return address"
- 				 self MoveR: ReceiverResultReg Mw: 0 r: SPReg.
- 				 numArgs > 0 ifTrue:
- 					[self PushR: Arg0Reg.
- 					 numArgs > 1 ifTrue:
- 						[self PushR: Arg1Reg]].
- 				self PushR: TempReg]] "Restore return address"!

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 genPushRegisterArgsForNumArgs: numArgs.
  	self genTrampolineFor: aRoutine
  		called: aString
  		callJumpBar: true
  		numArgs: 3
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: nil
  		saveRegs: false
  		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 genPushRegisterArgsForNumArgs: numArgs.
  	self genTrampolineFor: aRoutine
  		called: aString
  		callJumpBar: true
  		numArgs: 4
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true.
  	^startAddress!

Item was added:
+ ----- Method: VMCompiledMethodProxy>>encoderClass (in category 'accessing') -----
+ encoderClass
+ 
+ 	^(coInterpreter headerIndicatesAlternateBytecodeSet: self header)
+ 		ifTrue: [EncoderForNewsqueakV4]
+ 		ifFalse: [EncoderForV3PlusClosures]!



More information about the Vm-dev mailing list