VM Maker: VMMaker.oscog-eem.2696.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2696.mcz

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

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

Name: VMMaker.oscog-eem.2696
Author: eem
Time: 1 February 2020, 6:56:26.882392 pm
UUID: b56880e1-583f-431d-a595-615642cae15d
Ancestors: VMMaker.oscog-eem.2695

Cogit: Move genLoadStackPointers from Cogit to CogAbstractInstruction where it lives with the other stack load/store generartors, allowing ARMv8 to easily override to use ldp/stp if desired.

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

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."
+ cogit MoveAw: cogit stackPointerAddress R: SPReg.
+ cogit MoveAw: cogit framePointerAddress R: FPReg.
+ ^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreTrampolineNotCheckingRememberedCalled:instVarIndex: (in category 'initialization') -----
  genStoreTrampolineNotCheckingRememberedCalled: trampolineName instVarIndex: instVarIndex
  "Convention:
  - RcvrResultReg holds the object to be mutated.
  If immutability failure:
  - TempReg holds the instance variable index mutated
  if instVarIndex > numDedicatedStoreTrampoline
  - ClassReg holds the value to store
  Registers are not live across this trampoline as the
  immutability failure may need new stack frames."
 
  | jumpImmutable pushLinkReg |
  <option: #IMMUTABILITY>
  <var: #trampolineName type: #'char *'>
  <inline: true>
  "We are  going to call something, either remember: in the common case,
  or much more rarely ceCannotAssignTo:withIndex:valueToAssign:.  So
  share the stack switch between the two."
  cogit genSmalltalkToCStackSwitch: (pushLinkReg := cogit backEnd hasLinkRegister).
  "SendNumArgsReg is mutated but we don't care as registers are not live across the trampoline.
  There is no reason why registers cannot be saved over the remember: call, but since the
  immutability check is a suspension point, registers cannot remain live."
  jumpImmutable := self genJumpImmutable: ReceiverResultReg scratchReg: SendNumArgsReg.
  "Store check"
  cogit
  compileCallFor: #remember:
  numArgs: 1
  arg: ReceiverResultReg
  arg: nil
  arg: nil
  arg: nil
  resultReg: cogit returnRegForStoreCheck
  regsToSave: cogit emptyRegisterMask.
+ cogit backEnd genLoadStackPointers.
- cogit genLoadStackPointers.
  cogit genTrampolineReturn: pushLinkReg.
  jumpImmutable jmpTarget: cogit Label.
  cogit
  compileCallFor: #ceCannotAssignTo:withIndex:valueToAssign:
  numArgs: 3
  arg: ReceiverResultReg
  arg: (instVarIndex < (NumStoreTrampolines - 1)
  ifTrue: [cogit trampolineArgConstant: instVarIndex]
  ifFalse: [TempReg])
  arg: ClassReg
  arg: nil
  resultReg: NoReg
  regsToSave: cogit emptyRegisterMask.
+ cogit backEnd genLoadStackPointers.
- cogit genLoadStackPointers.
  cogit genTrampolineReturn: pushLinkReg.
  ^0!

Item was changed:
  ----- Method: Cogit>>compileTrampolineFor:numArgs:arg:arg:arg:arg:regsToSave:pushLinkReg:floatResultReg: (in category 'initialization') -----
  compileTrampolineFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 regsToSave: regMask pushLinkReg: pushLinkReg floatResultReg: resultRegOrNone
  "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 resultRegOrNone is not NoReg pass the C
  result back in resultRegOrNone.
  Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  <var: #aRoutine type: #'void *'>
  <inline: false>
  self genSmalltalkToCStackSwitch: pushLinkReg.
  self
  compileCallFor: aRoutine
  numArgs: numArgs
  arg: regOrConst0
  arg: regOrConst1
  arg: regOrConst2
  arg: regOrConst3
  floatResultReg: resultRegOrNone
  regsToSave: regMask.
+ backEnd genLoadStackPointers.
+ self genTrampolineReturn: pushLinkReg!
- self genLoadStackPointers;
- genTrampolineReturn: pushLinkReg!

Item was changed:
  ----- Method: Cogit>>compileTrampolineFor:numArgs:arg:arg:arg:arg:regsToSave:pushLinkReg:resultReg: (in category 'initialization') -----
  compileTrampolineFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 regsToSave: regMask pushLinkReg: pushLinkReg resultReg: resultRegOrNone
  "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 resultRegOrNone is not NoReg pass the C
  result back in resultRegOrNone.
  Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  <var: #aRoutine type: #'void *'>
  <inline: false>
  self genSmalltalkToCStackSwitch: pushLinkReg.
  self
  compileCallFor: aRoutine
  numArgs: numArgs
  arg: regOrConst0
  arg: regOrConst1
  arg: regOrConst2
  arg: regOrConst3
  resultReg: resultRegOrNone
  regsToSave: regMask.
+ backEnd genLoadStackPointers.
+ self genTrampolineReturn: pushLinkReg!
- self genLoadStackPointers;
- genTrampolineReturn: pushLinkReg!

Item was changed:
  ----- Method: Cogit>>compileTrampolineFor:numArgs:arg:arg:arg:arg:regsToSave:pushLinkReg:resultReg:resultReg: (in category 'initialization') -----
  compileTrampolineFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 regsToSave: regMask pushLinkReg: pushLinkReg resultReg: resultRegOrNone resultReg: resultReg2OrNone
  "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 resultRegOrNone is not NoReg pass the C
  result back in resultRegOrNone.
  Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  <var: #aRoutine type: #'void *'>
  <inline: false>
  self genSmalltalkToCStackSwitch: pushLinkReg.
  self
  compileCallFor: aRoutine
  numArgs: numArgs
  arg: regOrConst0
  arg: regOrConst1
  arg: regOrConst2
  arg: regOrConst3
  resultReg: resultRegOrNone
  resultReg: resultReg2OrNone
  regsToSave: regMask.
+ backEnd genLoadStackPointers.
+ self genTrampolineReturn: pushLinkReg!
- self genLoadStackPointers;
- genTrampolineReturn: pushLinkReg!

Item was changed:
  ----- Method: Cogit>>compileTrampolineFor:numArgs:floatArg:floatArg:floatArg:floatArg:regsToSave:pushLinkReg:resultReg: (in category 'initialization') -----
  compileTrampolineFor: aRoutine numArgs: numArgs floatArg: regOrConst0 floatArg: regOrConst1 floatArg: regOrConst2 floatArg: regOrConst3 regsToSave: regMask pushLinkReg: pushLinkReg resultReg: resultRegOrNone
  "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 resultRegOrNone is not NoReg pass the C
  result back in resultRegOrNone.
  Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  <option: #LowcodeVM>
  <var: #aRoutine type: #'void *'>
  <inline: false>
  self genSmalltalkToCStackSwitch: pushLinkReg.
  self
  compileCallFor: aRoutine
  numArgs: numArgs
  floatArg: regOrConst0
  floatArg: regOrConst1
  floatArg: regOrConst2
  floatArg: regOrConst3
  resultReg: resultRegOrNone
  regsToSave: regMask.
+ backEnd genLoadStackPointers.
+ self genTrampolineReturn: pushLinkReg!
- self genLoadStackPointers;
- genTrampolineReturn: pushLinkReg!

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 genLoadStackPointers.
- self 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 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 changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine flags: flags
  "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)'>
  | jmp jmpSamplePrim continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  <var: #jmp type: #'AbstractInstruction *'>
  <var: #jmpSamplePrim type: #'AbstractInstruction *'>
  <var: #jmpSampleNonPrim type: #'AbstractInstruction *'>
  <var: #continuePostSamplePrim 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 anyMask: PrimCallCollectsProfileSamples) ifTrue:
  ["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  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."
  jmpSampleNonPrim := self JumpNonZero: 0.
  continuePostSampleNonPrim := self Label].
 
  "Old full prim trace is in VMMaker-eem.550 and prior"
  self recordPrimTrace ifTrue:
  [self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
 
  "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.
 
  "If required, set primitiveFunctionPointer and newMethod"
  (flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  [self MoveCw: primitiveRoutine asInteger R: TempReg.
  primSetFunctionLabel :=
  self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  (flags anyMask: PrimCallNeedsNewMethod+PrimCallMayCallBack) ifTrue:
  ["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  (flags anyMask: PrimCallMayCallBack) 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].
 
  "Invoke the primitive"
  self PrefetchAw: coInterpreter primFailCodeAddress.
  (flags anyMask: PrimCallMayCallBack)
  ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
  ["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
   are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
  self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction).
  backEnd
  genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0;
  genSubstituteReturnAddress:
  ((flags anyMask: PrimCallCollectsProfileSamples)
  ifTrue: [cePrimReturnEnterCogCodeProfiling]
  ifFalse: [cePrimReturnEnterCogCode]).
  primInvokeInstruction := self JumpFullRT: primitiveRoutine asInteger.
  jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  ifFalse:
  ["Call the C primitive routine."
  backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  primInvokeInstruction := self CallFullRT: primitiveRoutine asInteger.
  backEnd genRemoveNArgsFromStack: 0.
  (flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  [self assert: (flags anyMask: PrimCallNeedsNewMethod).
  "Test nextProfileTick for being non-zero and call checkProfileTick if so"
  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."
  jmpSamplePrim := self JumpNonZero: 0.
  continuePostSamplePrim := self Label].
  objectRepresentation maybeCompileRetryOnPrimitiveFail: primitiveIndex.
  self maybeCompileAllocFillerCheck.
  "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 or load it into the LinkRegister to reestablish the return pc"
  self MoveAw: coInterpreter instructionPointerAddress
  R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
+ backEnd genLoadStackPointers.
- self genLoadStackPointers.
  "Test primitive failure"
  self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  backEnd hasLinkRegister ifFalse: [self PushR: ClassReg]. "Restore return pc on CISCs"
  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: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  r: SPReg
  R: ReceiverResultReg.
  self RetN: objectMemory wordSize]. "return to caller, popping receiver"
 
  (flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  ["The sample is collected by cePrimReturnEnterCogCode for external calls"
  jmpSamplePrim ifNotNil:
  ["Call ceCheckProfileTick: to record sample and then continue."
  jmpSamplePrim jmpTarget: self Label.
  self assert: (flags anyMask: PrimCallNeedsNewMethod).
  self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
    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 CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
    inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  "reenter the post-primitive call flow"
  self Jump: continuePostSampleNonPrim].
 
  jmp ifNotNil:
  ["Jump to restore of receiver reg and proceed to frame build for failure."
  jmp jmpTarget: self Label.
  "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [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 *'>
  self zeroOpcodeIndex.
  backEnd hasVarBaseRegister ifTrue:
  [self MoveCq: self varBaseAddress R: VarBaseReg]. "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."
- [self 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 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
  regsToSave: self emptyRegisterMask.
 
  "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.
- self 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: '(usqIntptr_t)ceCheckProfileTick'
  inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick])].
  self Jump: continuePostSample]!

Item was changed:
  ----- Method: SistaCogit>>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>
  self zeroOpcodeIndex.
  self CmpCq: 0 R: SendNumArgsReg.
  jumpMBB := self JumpZero: 0.
  "Open-code self compileTrampolineFor: #ceCounterTripped: numArgs: 1 arg: TempReg ...
  so we can restore ResultReceiverReg."
  self genSmalltalkToCStackSwitch: true.
  self
  compileCallFor: #ceCounterTripped:
  numArgs: 1
  arg: TempReg
  arg: nil
  arg: nil
  arg: nil
  resultReg: TempReg "(*)"
  regsToSave: self emptyRegisterMask.
  "(*) 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 genLoadStackPointers.
- self genLoadStackPointers.
  backEnd hasLinkRegister ifTrue:
  [self PopR: LinkReg].
  "To keep ResultReceiverReg live if optStatus thought it was, simply reload it
  from the frame pointer.  This avoids having to reload it in the common case
  (counter does not trip) if it was live.  Note we can't use putSelfInReceiverResultReg
  when generating trampolines because simSelf has not yet been initialized."
  self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  self RetN: 0.
  "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
  numArgs: 1
  arg: TempReg
  arg: nil
  arg: nil
  arg: nil
  regsToSave: self emptyRegisterMask
  pushLinkReg: true
  resultReg: NoReg
  appendOpcodes: true!

Item was changed:
  ----- Method: SistaCogitClone>>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>
  self zeroOpcodeIndex.
  self CmpCq: 0 R: SendNumArgsReg.
  jumpMBB := self JumpZero: 0.
  "Open-code self compileTrampolineFor: #ceCounterTripped: numArgs: 1 arg: TempReg ...
  so we can restore ResultReceiverReg."
  self genSmalltalkToCStackSwitch: true.
  self
  compileCallFor: #ceCounterTripped:
  numArgs: 1
  arg: TempReg
  arg: nil
  arg: nil
  arg: nil
  resultReg: TempReg "(*)"
  regsToSave: self emptyRegisterMask.
  "(*) 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 genLoadStackPointers.
- self genLoadStackPointers.
  backEnd hasLinkRegister ifTrue:
  [self PopR: LinkReg].
  "To keep ResultReceiverReg live if optStatus thought it was, simply reload it
  from the frame pointer.  This avoids having to reload it in the common case
  (counter does not trip) if it was live.  Note we can't use putSelfInReceiverResultReg
  when generating trampolines because simSelf has not yet been initialized."
  self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  self RetN: 0.
  "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
  numArgs: 1
  arg: TempReg
  arg: nil
  arg: nil
  arg: nil
  regsToSave: self emptyRegisterMask
  pushLinkReg: true
  resultReg: NoReg
  appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>callSwitchToSmalltalkStack (in category 'inline ffi') -----
  callSwitchToSmalltalkStack
  <option: #LowcodeVM>
  "Restore the link register"
  backEnd hasVarBaseRegister ifTrue:
  [self MoveCq: self varBaseAddress R: VarBaseReg].
  backEnd hasLinkRegister ifTrue:
  [self MoveAw: coInterpreter instructionPointerAddress R: LinkReg].
+ backEnd genLoadStackPointers!
- self genLoadStackPointers!

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 genLoadStackPointers.
- self 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)'!