VM Maker: VMMaker.oscog-eem.2288.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.2288.mcz

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

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

Name: VMMaker.oscog-eem.2288
Author: eem
Time: 7 December 2017, 6:03:19.789714 pm
UUID: 25ebdfbd-1a60-4052-bacc-1cb49ec6f83b
Ancestors: VMMaker.oscog-eem.2287

Refactor reaping the primFailCode on method activation to pull it out of the common path and hence lay the ground for a platform error object since all failures now call a single reapAndResetErrorCodeTo:header:

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

Item was changed:
  ----- Method: CoInterpreter>>activateCoggedNewMethod: (in category 'message sending') -----
  activateCoggedNewMethod: inInterpreter
  "Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
+ | methodHeader cogMethod rcvr numTemps switched |
- | methodHeader cogMethod rcvr numTemps errorCode switched |
  <var: #cogMethod type: #'CogMethod *'>
 
  methodHeader := self rawHeaderOf: newMethod.
  self assert: (self isCogMethodReference: methodHeader).
 
  cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  methodHeader := cogMethod methodHeader.
  rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
  self push: instructionPointer.
  cogMethod stackCheckOffset = 0 ifTrue:
  ["frameless method; nothing to activate..."
  cogit numRegArgs > 0 ifTrue: "dont use and: so as to get Slang to inline cogit numRegArgs > 0"
  [cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
  [self callRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
  self push: cogMethod asInteger + cogit noCheckEntryOffset.
  self push: rcvr.
  cogit ceCallCogCodePopReceiverReg.
  self error: 'should not be reached'].
  self push: framePointer.
  framePointer := stackPointer.
  self push: cogMethod asInteger.
  self push: objectMemory nilObject. "FxThisContext field"
  self push: rcvr.
 
  "clear remaining temps to nil"
  numTemps := self temporaryCountOfMethodHeader: methodHeader.
  cogMethod cmNumArgs + 1 to: numTemps do:
  [:i | self push: objectMemory nilObject].
 
+ ((self methodHeaderHasPrimitive: methodHeader)
+ and: [primFailCode ~= 0]) ifTrue:
+ [self reapAndResetErrorCodeTo: stackPointer header: methodHeader].
- (self methodHeaderHasPrimitive: methodHeader) ifTrue:
- [| initialPC |
- "Store the error code if the method starts with a long store temp.  No instructionPointer skip because we're heading for machine code."
- initialPC := (self initialIPForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
- primFailCode ~= 0 ifTrue:
- [(objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- [errorCode := self getErrorObjectFromPrimFailCode.
- self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
- primFailCode := 0]].
 
  "Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  stackPointer >= stackLimit ifTrue:
  [self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
  self push: cogMethod asInteger + cogMethod stackCheckOffset.
  self push: rcvr.
  cogit ceEnterCogCodePopReceiverReg.
  self error: 'should not be reached'].
  instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
  switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
+ | methodHeader numArgs numTemps rcvr inInterpreter switched |
- | methodHeader numArgs numTemps rcvr errorCode inInterpreter switched |
 
  methodHeader := objectMemory methodHeaderOf: newMethod.
  numTemps := self temporaryCountOfMethodHeader: methodHeader.
  numArgs := self argumentCountOfMethodHeader: methodHeader.
 
  rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  self assert: (objectMemory isOopForwarded: rcvr) not.
 
  "Because this is an uncogged method we need to continue via the interpreter.
  We could have been reached either from the interpreter, in which case we
  should simply return, or from a machine code frame or from a compiled
  primitive.  In these latter two cases we must longjmp back to the interpreter.
  The instructionPointer tells us which path we took.
  If the sender was an interpreter frame but called through a (failing) primitive
  then make sure we restore the saved instruction pointer and avoid pushing
  ceReturnToInterpreterPC which is only valid between an interpreter caller
  frame and a machine code callee frame."
  (inInterpreter := instructionPointer >= objectMemory startOfMemory) ifFalse:
  [instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  [instructionPointer := self iframeSavedIP: framePointer]].
  self push: instructionPointer.
  self push: framePointer.
  framePointer := stackPointer.
  self push: newMethod.
  self setMethod: newMethod methodHeader: methodHeader.
  self push: objectMemory nilObject. "FxThisContext field"
  self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  self push: 0. "FoxIFSavedIP"
  self push: rcvr.
 
  "clear remaining temps to nil"
  numArgs+1 to: numTemps do:
  [:i | self push: objectMemory nilObject].
 
  instructionPointer := (self initialIPForHeader: methodHeader method: newMethod) - 1.
 
  (self methodHeaderHasPrimitive: methodHeader) ifTrue:
  ["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
   with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
  primFailCode ~= 0 ifTrue:
+ [self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
- [(objectMemory byteAt: instructionPointer + 1)
-  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- [errorCode := self getErrorObjectFromPrimFailCode.
- self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
- primFailCode := 0]].
 
  "Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  switched := true.
  stackPointer < stackLimit ifTrue:
  [switched := self handleStackOverflowOrEventAllowContextSwitch:
  (self canContextSwitchIfActivating: newMethod header: methodHeader)].
  self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was added:
+ ----- Method: CoInterpreter>>ceReapAndResetErrorCodeFor: (in category 'trampolines') -----
+ ceReapAndResetErrorCodeFor: cogMethod
+ <var: #cogMethod type: #'CogMethod *'>
+ self break.
+ self assert: primFailCode ~= 0.
+ newMethod := cogMethod methodObject.
+ self reapAndResetErrorCodeTo: stackPointer header: cogMethod methodHeader!

Item was added:
+ ----- Method: CoInterpreter>>getErrorObjectFromPrimFailCode (in category 'message sending') -----
+ getErrorObjectFromPrimFailCode
+ "Answer the errorCode object to supply to a failing primitive method that accepts one.
+ If there is a primitive error table and the primFailCode is a valid index there-in answer
+ the corresponding entry in the table, otherwise simply answer the code as an integer."
+ ^super getErrorObjectFromPrimFailCode!

Item was changed:
  ----- Method: CoInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
+ | methodHeader numTemps rcvr switched |
- | methodHeader numTemps rcvr errorCode switched |
  <inline: true>
 
  methodHeader := self rawHeaderOf: newMethod.
  self assert: (self isCogMethodReference: methodHeader) not.
  numTemps := self temporaryCountOfMethodHeader: methodHeader.
  self assert: argumentCount = (self argumentCountOfMethodHeader: methodHeader).
  rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  self assert: (objectMemory isOopForwarded: rcvr) not.
 
  self internalPush: localIP.
  self internalPush: localFP.
  localFP := localSP.
  self internalPush: newMethod.
  self setMethod: newMethod methodHeader: methodHeader.
  self internalPush: objectMemory nilObject. "FxThisContext field"
  self internalPush: (self
  encodeFrameFieldHasContext: false
  isBlock: false
  numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  self internalPush: 0. "FoxIFSavedIP"
  self internalPush: rcvr.
 
  "Initialize temps..."
  argumentCount + 1 to: numTemps do:
  [:i | self internalPush: objectMemory nilObject].
 
  "-1 to account for pre-increment in fetchNextBytecode"
  localIP := self pointerForOop: (self initialIPForHeader: methodHeader method: newMethod) - 1.
 
  (self methodHeaderHasPrimitive: methodHeader) ifTrue:
  ["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
   with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  primFailCode ~= 0 ifTrue:
+ [self reapAndResetErrorCodeTo: localSP header: methodHeader]].
- [(objectMemory byteAt: localIP + 1)
-  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- [errorCode := self getErrorObjectFromPrimFailCode.
- self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
- primFailCode := 0]].
 
  self assert: (self frameNumArgs: localFP) == argumentCount.
  self assert: (self frameIsBlockActivation: localFP) not.
  self assert: (self frameHasContext: localFP) not.
 
  "Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  localSP < stackLimit ifTrue:
  [self externalizeIPandSP.
  switched := self handleStackOverflowOrEventAllowContextSwitch:
  (self canContextSwitchIfActivating: newMethod header: methodHeader).
  self returnToExecutive: true postContextSwitch: switched.
  self internalizeIPandSP]!

Item was changed:
  ----- Method: CoInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
+ | methodHeader activateCogMethod cogMethod numArgs numTemps rcvr initialIP |
- | methodHeader activateCogMethod cogMethod numArgs numTemps rcvr errorCode initialIP |
  <var: #cogMethod type: #'CogMethod *'>
  <var: #initialIP type: #usqInt>
  <inline: true>
  methodHeader := self rawHeaderOf: newMethod.
  (activateCogMethod := self isCogMethodReference: methodHeader) ifTrue:
  [cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  methodHeader := cogMethod methodHeader].
  numTemps := self temporaryCountOfMethodHeader: methodHeader.
  numArgs := self argumentCountOfMethodHeader: methodHeader.
 
  rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  self assert: (objectMemory isOopForwarded: rcvr) not.
 
  (activateCogMethod
  and: [instructionPointer asUnsignedInteger >= objectMemory startOfMemory]) ifTrue:
  [self iframeSavedIP: framePointer put: instructionPointer.
  instructionPointer := cogit ceReturnToInterpreterPC].
  self push: instructionPointer.
  self push: framePointer.
  framePointer := stackPointer.
  initialIP := self initialIPForHeader: methodHeader method: newMethod.
  activateCogMethod
  ifTrue:
  [self push: cogMethod asUnsignedInteger.
  self push: objectMemory nilObject. "FoxThisContext field"
  instructionPointer := cogMethod asUnsignedInteger + cogMethod stackCheckOffset]
  ifFalse:
  [self push: newMethod.
  self setMethod: newMethod methodHeader: methodHeader.
  self push: objectMemory nilObject. "FoxThisContext field"
  self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  self push: 0. "FoxIFSavedIP"
  instructionPointer := initialIP - 1].
  self push: rcvr.
 
  "clear remaining temps to nil"
  numArgs+1 to: numTemps do:
  [:i | self push: objectMemory nilObject].
 
  (self methodHeaderHasPrimitive: methodHeader) ifTrue:
  ["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
   with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
- initialIP := initialIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  activateCogMethod ifFalse:
+ [instructionPointer := initialIP + (self sizeOfCallPrimitiveBytecode: methodHeader)].
- [instructionPointer := initialIP].
  primFailCode ~= 0 ifTrue:
+ [self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
- [(objectMemory byteAt: initialIP + 1)
-  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- [errorCode := self getErrorObjectFromPrimFailCode.
- self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
- primFailCode := 0]].
 
  ^methodHeader!

Item was changed:
  ----- Method: CogVMSimulator>>saneFunctionPointerForFailureOfPrimIndex: (in category 'primitive support') -----
  saneFunctionPointerForFailureOfPrimIndex: primIndex
+ "For simulation override to do the check specially when the
+ primitiveFunctionPointer is an invalid address proxy for a primitive."
  | basePrimitive |
  (instructionPointer < objectMemory nilObject asUnsignedInteger
+ and: [primitiveFunctionPointer isInteger
+ and: [self isPrimitiveFunctionPointerAnIndex not
+ and: [primIndex ~= PrimNumberExternalCall
+ and: [(self isMetaPrimitiveIndex: primIndex) not]]]]) ifTrue:
- and: [primitiveFunctionPointer isInteger]) ifTrue:
  [basePrimitive := self functionPointerFor: primIndex inClass: objectMemory nilObject.
  ^(cogit lookupAddress: primitiveFunctionPointer) endsWith: basePrimitive].
 
  ^super saneFunctionPointerForFailureOfPrimIndex: primIndex!

Item was changed:
  CogClass subclass: #Cogit
+ instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
 ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointer
 s ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex'
- instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
 ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSen
 dTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex'
  classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
  poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  category: 'VMMaker-JIT'!
  Cogit class
  instanceVariableNames: 'generatorTable primitiveTable'!
 
  !Cogit commentStamp: 'eem 2/25/2017 17:53' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
 
  StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
 
  I have concrete subclasses that implement different levels of optimization:
  SimpleStackBasedCogit is the simplest code generator.
 
  StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  to the stack until necessary and implements a register-based calling convention for low-arity sends.
 
  SistaCogit is an experimental code generator with support for counting
  conditional branches, intended to support adaptive optimization.
 
  RegisterAllocatingCogit is an experimental code generator with support for allocating temporary variables
  to registers. It is inended to serve as the superclass to SistaCogit once it is working.
 
  SistaRegisterAllocatingCogit and SistaCogitClone are temporary classes that allow testing a clone of
  SistaCogit that inherits from RegisterAllocatingCogit.  Once things work these will be merged and
  will replace SistaCogit.
 
  coInterpreter <CoInterpreterSimulator>
  the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  the object used to generate object accesses
  processor <BochsIA32Alien|?>
  the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  flags controlling debug printing and code simulation
  breakPC <Integer>
  machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  the oop of the methodObj being compiled
  methodObj <sqInt>
  the bytecode method being compiled
  initialPC endPC <Integer>
  the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  argument count of current method or block being compiled
  needsFrame <Boolean>
  whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  label for the method header
  blockEntryLabel <CogAbstractOpcode>
  label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixups has one element per byte in methodObj's bytecode; initialPC maps to fixups[0].
  abstractOpcodes <Array of <AbstractOpcode>>
  the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  the starts of blocks in the current method
  blockCount
  the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  the various trampolines (system-call-like jumps from machine code to the run-time).
  See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>numTrampolines (in category 'accessing') -----
  numTrampolines
+ ^39 "31 + 4 each for self and super sends" + (LowcodeVM ifTrue: [1] ifFalse: [0])
- ^38 "30 + 4 each for self and super sends" + (LowcodeVM ifTrue: [1] ifFalse: [0])
 
  "self withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileGetErrorCode (in category 'compile abstract instructions') -----
  compileGetErrorCode
  "After pushing the temporaries but before the stack limit check a primitive method
+ needs to fetch the error code, if any.  If the primitive has failed, call the trampoline
+ that will assign it to the last temp."
- needs to fetch the error code, if any, and replace the last temp with it."
  <inline: false>
+ | jmpNoError |
- | jmpNoError primErrorTable primErrorTableSize jmpIntError jmpGotError |
  <var: #jmpNoError type: #'AbstractInstruction *'>
- <var: #jmpIntError type: #'AbstractInstruction *'>
- <var: #jmpGotError type: #'AbstractInstruction *'>
  self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  self flag: 'ask concrete code gen if move sets condition codes?'.
  self CmpCq: 0 R: TempReg.
  jmpNoError := self JumpZero: 0.
+ methodLabel addDependent:
+ (self annotateAbsolutePCRef:
+ (self MoveCw: methodLabel asInteger R: ClassReg)).
+ self CallRT: ceReapAndResetErrorCodeTrampoline.
- primErrorTable := coInterpreter primErrTable.
- primErrorTableSize := objectMemory lengthOf: primErrorTable.
- self flag: 'use CmpCqR if pc mapping means stable contexts never contain native pcs'.
- "Can't use CmpCqR here because table could change its size.
- Assume generated code is flushed whenever primitive error table is changed."
- self CmpCw: primErrorTableSize R: TempReg.
- jmpIntError := self JumpAboveOrEqual: 0. "Filter out negative values as well"
- objectRepresentation genFetchIndexRegister: TempReg from: primErrorTable into: ClassReg.
- jmpGotError := self Jump: 0.
- jmpIntError jmpTarget: self Label.
- objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
- self MoveR: TempReg R: ClassReg.
- jmpGotError jmpTarget: (self MoveR: ClassReg Mw: 0 r: SPReg).
- "zero the error code to agree with the interpreter's (internal)ActivateNewMethod."
- self MoveCq: 0 R: TempReg.
- self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  jmpNoError jmpTarget: self Label!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>generateMissAbortTrampolines (in category 'initialization') -----
  generateMissAbortTrampolines
  "Generate the run-time entries for the various method and PIC entry misses and aborts.
  Read the class-side method trampolines for documentation on the various trampolines"
 
  ceMethodAbortTrampoline := self genMethodAbortTrampoline.
  cePICAbortTrampoline := self genPICAbortTrampoline.
  ceCPICMissTrampoline := self genTrampolineFor: #ceCPICMiss:receiver:
  called: 'ceCPICMissTrampoline'
  arg: ClassReg
+ arg: ReceiverResultReg.
+ ceReapAndResetErrorCodeTrampoline := self genTrampolineFor: #ceReapAndResetErrorCodeFor:
+ called: 'ceReapAndResetErrorCodeTrampoline'
+ arg: ClassReg!
- arg: ReceiverResultReg!

Item was changed:
  ----- Method: StackInterpreter>>getErrorObjectFromPrimFailCode (in category 'message sending') -----
  getErrorObjectFromPrimFailCode
  "Answer the errorCode object to supply to a failing primitive method that accepts one.
  If there is a primitive error table and the primFailCode is a valid index there-in answer
+ the corresponding entry in the table, otherwise simply answer the code as an integer."
- the coprresponding entry in the table, otherwise simply answer the code as an integer."
  | table |
  primFailCode > 0 ifTrue:
  [table := objectMemory splObj: PrimErrTableIndex.
  primFailCode <= (objectMemory numSlotsOf: table) ifTrue:
  [^objectMemory fetchPointer: primFailCode - 1 ofObject: table]].
  ^objectMemory integerObjectOf: primFailCode!

Item was changed:
  ----- Method: StackInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
+ | methodHeader numTemps rcvr |
- | methodHeader numTemps rcvr errorCode |
  <inline: true>
 
  methodHeader := objectMemory methodHeaderOf: newMethod.
  numTemps := self temporaryCountOfMethodHeader: methodHeader.
  self assert: argumentCount = (self argumentCountOfMethodHeader: methodHeader).
  rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  self assert: (objectMemory isOopForwarded: rcvr) not.
 
  self internalPush: localIP.
  self internalPush: localFP.
  localFP := localSP.
  self internalPush: newMethod.
  self setMethod: newMethod methodHeader: methodHeader.
  self internalPush: (self
  encodeFrameFieldHasContext: false
  isBlock: false
  numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  self internalPush: objectMemory nilObject. "FxThisContext field"
  self internalPush: rcvr.
 
  "Initialize temps..."
  argumentCount + 1 to: numTemps do:
  [:i | self internalPush: objectMemory nilObject].
 
  "-1 to account for pre-increment in fetchNextBytecode"
  localIP := self pointerForOop: (self initialIPForHeader: methodHeader method: newMethod) - 1.
 
  (self methodHeaderHasPrimitive: methodHeader) ifTrue:
  ["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
   with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  primFailCode ~= 0 ifTrue:
+ [self reapAndResetErrorCodeTo: localSP header: methodHeader]].
- [(objectMemory byteAt: localIP + 1)
-  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- [errorCode := self getErrorObjectFromPrimFailCode.
- self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
- primFailCode := 0]].
 
  self assert: (self frameNumArgs: localFP) == argumentCount.
  self assert: (self frameIsBlockActivation: localFP) not.
  self assert: (self frameHasContext: localFP) not.
 
  "Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  localSP < stackLimit ifTrue:
  [self externalizeIPandSP.
  self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  self internalizeIPandSP]!

Item was changed:
  ----- Method: StackInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
+ | methodHeader numArgs numTemps rcvr |
- | methodHeader numArgs numTemps rcvr errorCode |
  <inline: true>
  methodHeader := objectMemory methodHeaderOf: newMethod.
  numTemps := self temporaryCountOfMethodHeader: methodHeader.
  numArgs := self argumentCountOfMethodHeader: methodHeader.
 
  rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  self assert: (objectMemory isOopForwarded: rcvr) not.
 
  self push: instructionPointer.
  self push: framePointer.
  framePointer := stackPointer.
  self push: newMethod.
  self setMethod: newMethod methodHeader: methodHeader.
  self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  self push: objectMemory nilObject. "FxThisContext field"
  self push: rcvr.
 
  "clear remaining temps to nil"
  numArgs+1 to: numTemps do:
  [:i | self push: objectMemory nilObject].
 
  instructionPointer := (self initialIPForHeader: methodHeader method: newMethod) - 1.
 
  (self methodHeaderHasPrimitive: methodHeader) ifTrue:
  ["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
   with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
  primFailCode ~= 0 ifTrue:
+ [self reapAndResetErrorCodeTo: stackPointer header: methodHeader]].
- [(objectMemory byteAt: instructionPointer + 1)
-  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- [errorCode := self getErrorObjectFromPrimFailCode.
- self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
- primFailCode := 0]].
 
  ^methodHeader!

Item was added:
+ ----- Method: StackInterpreter>>reapAndResetErrorCodeTo:header: (in category 'primitive support') -----
+ reapAndResetErrorCodeTo: theSP header: methodHeader
+ "Assuming the primFailCode is non-zero, check if the method consumes the error code
+ and if so, assign it through theSP.  Then zero the primFailCode.  This is infrequent code,
+ so keep it out of the common path."
+ <inline: #never>
+ | initialPC |
+ self assert: primFailCode ~= 0.
+ initialPC := (self initialIPForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ (objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
+ [stackPages longAtPointer: theSP put: self getErrorObjectFromPrimFailCode].
+ primFailCode := 0!

Item was changed:
  ----- Method: StackInterpreter>>sizeOfCallPrimitiveBytecode: (in category 'compiled methods') -----
  sizeOfCallPrimitiveBytecode: methodHeader
+ "Answer the size of the CallPrimitive bytecode that may be used to store a method's primitive."
+ "NewsqueakV4: 249 11111001 iiiiiiii jjjjjjjj Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
+ "SistaV1: 248 11111000 iiiiiiii mssjjjjj Call Primitive #iiiiiiii + (  jjjjj * 256)"
+ "V3+Closures: 139 11101111 iiiiiiii jjjjjjjj Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
- "Answer if the method starts with a long store temp bytecode, which indicates it has a primitive error code."
- "249 11111001 i i i i i i i i jjjjjjjj Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
  <api>
  <inline: true>
  ^objectMemory hasSpurMemoryManagerAPI
  ifTrue: [3]
  ifFalse:
  [MULTIPLEBYTECODESETS
  ifTrue: [(objectMemory headerIndicatesAlternateBytecodeSet: methodHeader)
  ifTrue: [3]
  ifFalse: [0]]
  ifFalse: [0]]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateMissAbortTrampolines (in category 'initialization') -----
  generateMissAbortTrampolines
  "Generate the run-time entries for the various method and PIC entry misses and aborts.
  Read the class-side method trampolines for documentation on the various trampolines"
  0 to: self numRegArgs + 1 do:
  [:numArgs|
  methodAbortTrampolines
  at: numArgs
  put: (self genMethodAbortTrampolineFor: numArgs)].
  0 to: self numRegArgs + 1 do:
  [:numArgs|
  picAbortTrampolines
  at: numArgs
  put: (self genPICAbortTrampolineFor: numArgs)].
  0 to: self numRegArgs + 1 do:
  [:numArgs|
  picMissTrampolines
  at: numArgs
+ put: (self genPICMissTrampolineFor: numArgs)].
+ ceReapAndResetErrorCodeTrampoline := self genTrampolineFor: #ceReapAndResetErrorCodeFor:
+ called: 'ceReapAndResetErrorCodeTrampoline'
+ arg: ClassReg!
- put: (self genPICMissTrampolineFor: numArgs)]!