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

commits at source.squeak.org commits at source.squeak.org
Sun Jan 10 22:43:56 UTC 2016


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

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

Name: VMMaker.oscog-eem.1630
Author: eem
Time: 10 January 2016, 2:42:14.328141 pm
UUID: 2ed025ea-f400-4440-8e8b-5aa46d06c9ab
Ancestors: VMMaker.oscog-eem.1629

Cogit:
Fix the bug in ceCaptureStackPointers caused by pushing VarBasReg to save it offsetting the stack pointer.

Eliminate all the maybe*VarBase methods since we have hasVarBaseRegister and teh few clients can test that and hnce not have to divine if maybeSaveVarBase pushed something or not.

Remember to nuke the <inline: true> from all those accessors now we're using asSpecifiedOrIsQuick as the inlining policy for Cogit.

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

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

Item was changed:
  ----- Method: CogARMCompiler>>canMulRR (in category 'testing') -----
  canMulRR
  "we can do a MulRR be we can't simulate it correctly for some reason. More bug-fixing in the simulator one day"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogARMCompiler>>hasConditionRegister (in category 'testing') -----
  hasConditionRegister
  	"Answer if the receiver supports, e.g., JumpOverflow after a regular AddRR"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogARMCompiler>>hasDoublePrecisionFloatingPointSupport (in category 'testing') -----
  hasDoublePrecisionFloatingPointSupport
  	"might be true, but is for the forseeable future disabled"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogARMCompiler>>hasThreeAddressArithmetic (in category 'testing') -----
  hasThreeAddressArithmetic
  	"Answer if the receiver supports three-address arithmetic instructions (currently only AndCqRR)"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogARMCompiler>>hasVarBaseRegister (in category 'testing') -----
  hasVarBaseRegister
  	"Answer if the processor has a dedicated callee-saved register to point to
  	 the base of commonly-accessed variables. On ARM we use R10 for this."
- 	<inline: true>
  	^true "r10/sl"!

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

Item was removed:
- ----- Method: CogARMCompiler>>maybeEstablishVarBase (in category 'abstract instructions') -----
- maybeEstablishVarBase
- 	"The receiver has a VarBaseReg; generate the code to set it to its value."
- 	<inline: true>
- 	cogit MoveCq: cogit varBaseAddress R: VarBaseReg!

Item was removed:
- ----- Method: CogARMCompiler>>maybeRestoreVarBase (in category 'abstract instructions') -----
- maybeRestoreVarBase
- 	"The receiver has a VarBaseReg; generate the code to pop its value."
- 	<inline: true>
- 	cogit PopR: VarBaseReg!

Item was removed:
- ----- Method: CogARMCompiler>>maybeSaveVarBase (in category 'abstract instructions') -----
- maybeSaveVarBase
- 	"The receiver has a VarBaseReg; generate the code to push its value."
- 	<inline: true>
- 	cogit PushR: VarBaseReg!

Item was changed:
  ----- Method: CogAbstractInstruction>>hasPCRegister (in category 'testing') -----
  hasPCRegister
  	"Answer if the processor has a generally addressable pc register, such as the ARM.
  	 On such processors we can execute jumping to pop top of stack by popping into
  	 the pc register.  Note that this is not a generic RISC feature.  The PowerPC does not
  	 allow one to pop into the pc for example.  So by default, answer false."
- 	<inline: true>
  	^false!

Item was changed:
  ----- Method: CogAbstractInstruction>>hasVarBaseRegister (in category 'testing') -----
  hasVarBaseRegister
  	"Answer if the processor has a dedicated callee-saved register to point to
  	 the base of commonly-accessed variables. By default this is false."
- 	<inline: true>
  	^false!

Item was removed:
- ----- Method: CogAbstractInstruction>>maybeEstablishVarBase (in category 'abstract instructions') -----
- maybeEstablishVarBase
- 	"If the receiver has a VarBaseReg, generate the code to set it to its value.
- 	 By default do nothing."
- 	<inline: true>!

Item was removed:
- ----- Method: CogAbstractInstruction>>maybeRestoreVarBase (in category 'abstract instructions') -----
- maybeRestoreVarBase
- 	"If the receiver has a VarBaseReg, generate the code to pop its value.
- 	 By default do nothing."
- 	<inline: true>!

Item was removed:
- ----- Method: CogAbstractInstruction>>maybeSaveVarBase (in category 'abstract instructions') -----
- maybeSaveVarBase
- 	"If the receiver has a VarBaseReg, generate the code to push its value.
- 	 By default do nothing."
- 	<inline: true>!

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

Item was changed:
  ----- Method: CogIA32Compiler>>canMulRR (in category 'testing') -----
  canMulRR
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogIA32Compiler>>codeGranularity (in category 'accessing') -----
  codeGranularity
  	"Answer the size in bytes of a unit of machine code."
- 	<inline: true>
  	^1!

Item was changed:
  ----- Method: CogIA32Compiler>>hasConditionRegister (in category 'testing') -----
  hasConditionRegister
  	"Answer if the receiver supports, e.g., JumpOverflow after a regular AddRR"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogIA32Compiler>>hasThreeAddressArithmetic (in category 'testing') -----
  hasThreeAddressArithmetic
  	"Answer if the receiver supports three-address arithmetic instructions"
- 	<inline: true>
  	^false!

Item was changed:
  ----- Method: CogIA32Compiler>>isBigEndian (in category 'testing') -----
  isBigEndian
- 	<inline: true>
  	^false!

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

Item was changed:
  ----- Method: CogMIPSELCompiler>>canMulRR (in category 'testing') -----
  canMulRR
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogMIPSELCompiler>>hasConditionRegister (in category 'testing') -----
  hasConditionRegister
  	"Answer if the receiver supports, e.g., JumpOverflow after a regular AddRR"
- 	<inline: true>
  	^false!

Item was changed:
  ----- Method: CogMIPSELCompiler>>hasThreeAddressArithmetic (in category 'testing') -----
  hasThreeAddressArithmetic
  	"Answer if the receiver supports three-address arithmetic instructions"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogMIPSELCompiler>>hasVarBaseRegister (in category 'testing') -----
  hasVarBaseRegister
  	"Answer if the processor has a dedicated callee-saved register to point to
  	 the base of commonly-accessed variables."
- 	<inline: true>
  	^true "S6"!

Item was changed:
  ----- Method: CogMIPSELCompiler>>isBigEndian (in category 'testing') -----
  isBigEndian
- 	<inline: true>
  	^false!

Item was changed:
  ----- Method: CogMethodZone>>zoneEnd (in category 'accessing') -----
  zoneEnd
- 	<inline: true>
  	^limitAddress!

Item was changed:
  ----- Method: CogMethodZone>>zoneFree (in category 'accessing') -----
  zoneFree
- 	<inline: true>
  	^mzFreeStart!

Item was changed:
  ----- Method: CogObjectRepresentation>>canPinObjects (in category 'testing') -----
  canPinObjects
  	"Answer if the memory manager supports pinned objects."
- 	<inline: true>
  	^false!

Item was changed:
  ----- Method: CogObjectRepresentation>>maybeGenerateSelectorIndexDereferenceRoutine (in category 'initialization') -----
  maybeGenerateSelectorIndexDereferenceRoutine
  	"If required, generate the routine that converts selector indices into selector objects.
  	 If it exists, it is called from the send trampolines.
  	 If the selector index is negative, convert it into a positive index into the
  	 special selectors array and index that.  Otherwise, index the current method.
+ 	 This is only required on 64-bit platforms."!
- 	 This is only required on 64-bit platforms."
- 	<inline: true>!

Item was changed:
  ----- Method: CogObjectRepresentation>>selectorIndexDereferenceRoutine (in category 'calling convention') -----
  selectorIndexDereferenceRoutine
  	"If the object representation is 64-bits, selectors must be accessed via indices in the inline caches.
  	 Answer the routine that will map from indices to selector objects if so, otherwise nil."
- 	<inline: true>
  	^nil!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>illegalClassTag (in category 'in-line cacheing') -----
  illegalClassTag
- 	<inline: true>
  	^2!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>illegalClassTag (in category 'in-line cacheing') -----
  illegalClassTag
- 	<inline: true>
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>selectorIndexDereferenceRoutine (in category 'calling convention') -----
  selectorIndexDereferenceRoutine
  	"If the object representation is 64-bits, selectors must be accessed via indices in the inline caches.
  	 Answer the routine that will map from indices to selector objects if so, otherwise nil."
- 	<inline: true>
  	^ceDereferenceSelectorIndex!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>canPinObjects (in category 'testing') -----
  canPinObjects
  	"Answer if the memory manager supports pinned objects."
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>inlineCacheTagsMayBeObjects (in category 'in-line cacheing') -----
  inlineCacheTagsMayBeObjects
- 	<inline: true>
  	^false!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>numRegArgs (in category 'calling convention') -----
  numRegArgs
  	"Define how many register arguments a StackToRegisterMappingCogit can
  	 and should use with the receiver.  The value must be 0, 1 or 2.  Note that a
  	 SimpleStackBasedCogit always has 0 register args (although the receiver is
  	 passed in a register).  The Spur object representation is simple enough that
  	 implementing at:put: is straight-forward and hence 2 register args are worth
  	 while.  The method must be inlined in CoInterpreter, and dead code eliminated
  	 so that the register-popping enilopmarts such as enterRegisterArgCogMethod:-
  	 at:receiver: do not have to be implemented in SimpleStackBasedCogit."
  	<api>
  	<option: #StackToRegisterMappingCogit>
- 	<inline: true>
  	^2!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>illegalClassTag (in category 'in-line cacheing') -----
  illegalClassTag
- 	<inline: true>
  	^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>inlineCacheTagsMayBeObjects (in category 'in-line cacheing') -----
  inlineCacheTagsMayBeObjects
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>numRegArgs (in category 'calling convention') -----
  numRegArgs
  	"Define how many register arguments a StackToRegisterMappingCogit can
  	 and should use with the receiver.  The value must be 0, 1 or 2.  Note that a
  	 SimpleStackBasedCogit always has 0 register args (although the receiver is
  	 passed in a register).  CogObjectRepresentationForSqueakV3 only implements
  	 at most 1-arg primitives, because the complexity of the object representation
  	 makes it difficult to implement at:put:, the most performance-critical 2-argument
  	 primitive..  The method must be inlined in CoInterpreter, and dead code eliminated
  	 so that the register-popping enilopmarts such as enterRegisterArgCogMethod:-
  	 at:receiver: do not have to be implemented in SimpleStackBasedCogit."
  	<api>
  	<option: #StackToRegisterMappingCogit>
- 	<inline: true>
  	^1!

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

Item was changed:
  ----- Method: CogX64Compiler>>canMulRR (in category 'testing') -----
  canMulRR
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogX64Compiler>>hasConditionRegister (in category 'testing') -----
  hasConditionRegister
  	"Answer if the receiver supports, e.g., JumpOverflow after a regular AddRR"
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogX64Compiler>>hasDoublePrecisionFloatingPointSupport (in category 'testing') -----
  hasDoublePrecisionFloatingPointSupport
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: CogX64Compiler>>hasThreeAddressArithmetic (in category 'testing') -----
  hasThreeAddressArithmetic
  	"Answer if the receiver supports three-address arithmetic instructions"
- 	<inline: true>
  	^false!

Item was added:
+ ----- Method: CogX64Compiler>>hasVarBaseRegister (in category 'testing') -----
+ hasVarBaseRegister
+ 	"Answer if the processor has a dedicated callee-saved register to point to
+ 	 the base of commonly-accessed variables."
+ 	^true "RBX"!

Item was changed:
  ----- Method: CogX64Compiler>>isBigEndian (in category 'testing') -----
  isBigEndian
- 	<inline: true>
  	^false!

Item was removed:
- ----- Method: CogX64Compiler>>maybeEstablishVarBase (in category 'abstract instructions') -----
- maybeEstablishVarBase
- 	"The receiver has a VarBaseReg; generate the code to set it to its value."
- 	<inline: true>
- 	cogit MoveCq: cogit varBaseAddress R: VarBaseReg!

Item was removed:
- ----- Method: CogX64Compiler>>maybeRestoreVarBase (in category 'abstract instructions') -----
- maybeRestoreVarBase
- 	"The receiver has a VarBaseReg; generate the code to pop its value."
- 	<inline: true>
- 	cogit PopR: VarBaseReg!

Item was removed:
- ----- Method: CogX64Compiler>>maybeSaveVarBase (in category 'abstract instructions') -----
- maybeSaveVarBase
- 	"The receiver has a VarBaseReg; generate the code to push its value."
- 	<inline: true>
- 	cogit PushR: VarBaseReg!

Item was changed:
  ----- Method: Cogit>>genEnilopmartFor:and:and:forCall:called: (in category 'initialization') -----
  genEnilopmartFor: regArg1 and: regArg2OrNone and: regArg3OrNone forCall: forCall 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.
  
  						BEFORE				AFTER			(stacks grow down)
  						whatever			stackPointer ->	whatever
  						target address =>	reg1 = reg1val, etc
  						reg1val				pc = target address
  						reg2val
  		stackPointer ->	reg3val"
  
  	<var: #trampolineName type: #'char *'>
  	<returnTypeC: #'void (*genEnilopmartForandandforCallcalled(sqInt regArg1, sqInt regArg2OrNone, sqInt regArg3OrNone, sqInt forCall, char *trampolineName))(void)'>
  
  	| size endAddress enilopmart |
  	self zeroOpcodeIndex.
+ 	backEnd hasVarBaseRegister ifTrue:
+ 		[self MoveCq: self varBaseAddress R: VarBaseReg]. "Must happen first; value may be used in genLoadStackPointers"
- 	backEnd maybeEstablishVarBase. "Must happen first; value may be used in genLoadStackPointers"
  	backEnd genLoadStackPointers.
  	regArg3OrNone ~= NoReg ifTrue: [self PopR: regArg3OrNone].
  	regArg2OrNone ~= NoReg ifTrue: [self PopR: regArg2OrNone].
  	self PopR: regArg1.
  	self genEnilopmartReturn: forCall.
  	self computeMaximumSizes.
  	size := self generateInstructionsAt: methodZoneBase.
  	endAddress := self outputInstructionsAt: methodZoneBase.
  	self assert: methodZoneBase + size = endAddress.
  	enilopmart := methodZoneBase.
  	methodZoneBase := self alignUptoRoutineBoundary: endAddress.
  	backEnd stopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: trampolineName address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>generateCaptureCStackPointers: (in category 'initialization') -----
  generateCaptureCStackPointers: captureFramePointer
  	"Generate the routine that writes the current values of the C frame and stack pointers into
  	 variables.  These are used to establish the C stack in trampolines back into the C run-time.
  
  	 This is a presumptuous quick hack for x86.  It is presumptuous for two reasons.  Firstly
  	 the system's frame and stack pointers may differ from those we use in generated code,
  	 e.g. on register-rich RISCs.  Secondly the ABI may not support a simple frameless call
  	 as written here (for example 128-bit stack alignment on Mac OS X)."
  	| startAddress |
  	<inline: false>
  	self allocateOpcodes: 32 bytecodes: 0.
  	startAddress := methodZoneBase.
+ 	 "Must happen first; value may be used in accessing any of the following addresses"
+ 	backEnd hasVarBaseRegister ifTrue:
+ 		[self
+ 			PushR: VarBaseReg;
+ 			MoveCq: self varBaseAddress R: VarBaseReg].
- 	backEnd
- 		maybeSaveVarBase;
- 		maybeEstablishVarBase. "Must happen first; value may be used in accessing any of the following addresses"
  	captureFramePointer ifTrue:
  		[self MoveR: FPReg Aw: self cFramePointerAddress].
+ 	"Capture the stack pointer prior to the call.  If we've pushed VarBaseReg take that into account."
+ 	(backEnd leafCallStackPointerDelta ~= 0
+ 	 or: [backEnd hasVarBaseRegister])
+ 		ifTrue:
+ 			[self MoveR: SPReg R: TempReg.
+ 			 self AddCq: (backEnd hasVarBaseRegister
+ 							ifTrue: [backEnd leafCallStackPointerDelta + objectMemory wordSize]
+ 							ifFalse: [backEnd leafCallStackPointerDelta]) R: TempReg.
+ 			 self MoveR: TempReg Aw: self cStackPointerAddress]
+ 		ifFalse: [self MoveR: SPReg Aw: self cStackPointerAddress].
+ 	backEnd hasVarBaseRegister ifTrue:
+ 		[self PopR: VarBaseReg].
- 	"Capture the stack pointer prior to the call."
- 	backEnd leafCallStackPointerDelta = 0
- 		ifTrue: [self MoveR: SPReg Aw: self cStackPointerAddress]
- 		ifFalse: [self MoveR: SPReg R: TempReg.
- 				self AddCq: backEnd leafCallStackPointerDelta R: TempReg.
- 				self MoveR: TempReg Aw: self cStackPointerAddress].
- 	backEnd
- 		maybeRestoreVarBase.
  	self RetN: 0.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
  	processor flushICacheFrom: startAddress asUnsignedInteger to: methodZoneBase asUnsignedInteger.
  	self recordGeneratedRunTime: 'ceCaptureCStackPointers' address: startAddress.
  	ceCaptureCStackPointers := self cCoerceSimple: startAddress to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>getOpcodeIndex (in category 'accessing') -----
  getOpcodeIndex
  	"Access for the literal manager."
- 	<inline: true>
  	^opcodeIndex!

Item was changed:
  ----- Method: Cogit>>maybeAllocAndInitCounters (in category 'compile abstract instructions') -----
  maybeAllocAndInitCounters
  	"No-op in the non-Sista Cogits..."
- 	<inline: true>
  	^true!

Item was changed:
  ----- Method: Cogit>>maybeFreeCounters (in category 'compile abstract instructions') -----
  maybeFreeCounters
+ 	"No-op in the non-Sista Cogits..."!
- 	"No-op in the non-Sista Cogits..."
- 	<inline: true>!

Item was changed:
  ----- Method: Cogit>>picAbortDiscriminatorValue (in category 'accessing') -----
  picAbortDiscriminatorValue
  	"This value is used to decide between MNU processing
  	 or interpretation in the closed PIC aborts."
- 	<inline: true>
  	^0!

Item was changed:
  ----- Method: Cogit>>varBaseAddress (in category 'accessing') -----
  varBaseAddress
+ 	"This is for disassembly decoration by the processor aliens.  they don't know aboud objectMemory hence forward..."
- 	"We expect simulatedAddresses to have around 40 entries.  48 is hopefully a good maximum."
  	<doNotGenerate>
  	^coInterpreter varBaseAddress!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>isLabelRelativeToCogitVarBaseReg: (in category 'labels') -----
- isLabelRelativeToCogitVarBaseReg: l
- 	coInterpreter class
- 		instVarIndexFor: l
- 		ifAbsent:
- 			[objectMemory class
- 				instVarIndexFor: l
- 				ifAbsent: [^false]].
- 	^true!

Item was changed:
  ----- Method: InLineLiteralsManager>>literalBytesFollowingBranchInClosedPIC (in category 'garbage collection') -----
  literalBytesFollowingBranchInClosedPIC
- 	<inline: true>
  	^0!

Item was changed:
  ----- Method: InLineLiteralsManager>>literalBytesFollowingJumpInClosedPIC (in category 'garbage collection') -----
  literalBytesFollowingJumpInClosedPIC
- 	<inline: true>
  	^0!

Item was changed:
  ----- Method: InLineLiteralsManager>>resetForBlockCompile (in category 'compile abstract instructions') -----
+ resetForBlockCompile!
- resetForBlockCompile
- 	<inline: true>!

Item was changed:
  ----- Method: InLineLiteralsManager>>resetLiterals (in category 'initialization') -----
+ resetLiterals!
- resetLiterals
- 	<inline: true>!

Item was changed:
  ----- Method: InLineLiteralsManager>>saveForBlockCompile (in category 'compile abstract instructions') -----
+ saveForBlockCompile!
- saveForBlockCompile
- 	<inline: 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 *'>
  	self zeroOpcodeIndex.
+ 	backEnd hasVarBaseRegister ifTrue:
+ 		[self MoveCq: self varBaseAddress R: VarBaseReg]. "Must happen sometime"
- 	backEnd maybeEstablishVarBase. "Must happen sometime"
  
  	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."
  		objectMemory wordSize = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize 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].
  
  	self maybeCompileAllocFillerCheck.
  
  	"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."
  			 backEnd hasPCRegister
  				ifTrue:
  					[self PopR: ReceiverResultReg.										"Pop result from stack"
  					 self MoveAw: coInterpreter instructionPointerAddress R: PCReg]	"Return"
  				ifFalse:
  					[self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  					 self MoveAw: coInterpreter instructionPointerAddress R: LinkReg.	"Get ret pc"
  					 self RetN: objectMemory wordSize]]								"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.
  	self 
  		compileCallFor: #ceActivateFailingPrimitiveMethod:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: NoReg
  		saveRegs: false.
  
  	"On Spur ceActivateFailingPrimitiveMethod: may retry the primitive and return if successful.
  	 So continue by returning to the caller.
  	 Switch back to the Smalltalk stack.  Stack should be in this state:
  				success:	stackPointer ->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  	 We can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  	self MoveAw: coInterpreter instructionPointerAddress
  		R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  	backEnd genLoadStackPointers.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveMw: 0 r: SPReg R: ReceiverResultReg]	"Fetch result from stack"
  		ifFalse:
  			[self MoveMw: objectMemory wordSize r: SPReg R: ReceiverResultReg.	"Fetch result from stack"
  			 self PushR: ClassReg].											"Restore return pc on CISCs"
  	self RetN: objectMemory wordSize.	"return to caller, popping receiver"
  
  	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."
  		 jmpSample jmpTarget: self Label.
  		 backEnd saveAndRestoreLinkRegAround:
  			[self CallFullRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick])].
  		 self Jump: continuePostSample]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genCallPICEnilopmartNumArgs: (in category 'initialization') -----
  genCallPICEnilopmartNumArgs: numArgs
  	"Generate special versions of the ceCallCogCodePopReceiverAndClassRegs
  	 enilopmart that also pop register args from the stack to undo the pushing of
  	 register args in the abort/miss trampolines."
  	<returnTypeC: 'void (*genCallPICEnilopmartNumArgs(sqInt numArgs))(void)'>
  	| size endAddress enilopmart |
  	self zeroOpcodeIndex.
+ 	backEnd hasVarBaseRegister ifTrue:
+ 		[self MoveCq: self varBaseAddress R: VarBaseReg]. "Must happen first; value may be used in genLoadStackPointers"
- 	backEnd maybeEstablishVarBase. "Must happen first; value may be used in genLoadStackPointers"
  	backEnd genLoadStackPointers.
  	self PopR: ClassReg. "cacheTag"
  	self PopR: TempReg. "entry-point"
  	self PopR: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [SendNumArgsReg]). "retpc"
  	numArgs > 0 ifTrue:
  		[numArgs > 1 ifTrue:
  			[self PopR: Arg1Reg.
  			 self assert: self numRegArgs = 2].
  		 self PopR: Arg0Reg].
  	self PopR: ReceiverResultReg.
  	backEnd hasLinkRegister ifFalse: [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 stopsFrom: endAddress to: methodZoneBase - 1.
  	self recordGeneratedRunTime: (self trampolineName: 'ceCallPIC' numRegArgs: numArgs) address: enilopmart.
  	^self cCoerceSimple: enilopmart to: #'void (*)(void)'!



More information about the Vm-dev mailing list