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

Clément Bera bera.clement at gmail.com
Thu Mar 2 10:59:25 UTC 2017


Hi,

Since this commit, when I run this method

21 <01> pushRcvr: 1
22 <10> pushTemp: 0
23 <B2> send: <
24 <99> jumpFalse: 27
25 <20> pushConstant: 'yes'
26 <7C> returnTop
27 <21> pushConstant: 'no'
28 <7C> returnTop

the VM crashes.

I run the method using:

self assert: (cm valueWithReceiver: 2 at 2 arguments: #(1)) = 'no' .
self assert: (cm valueWithReceiver: 2 at 2  arguments: #(3)) = 'yes' .


On Fri, Feb 24, 2017 at 9:32 PM, <commits at source.squeak.org> wrote:

>
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2138.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.2138
> Author: eem
> Time: 24 February 2017, 12:31:35.781791 pm
> UUID: 8b98184c-9061-45e1-b4ce-bd9b8bc8c802
> Ancestors: VMMaker.oscog-eem.2137
>
> StackToRegisterMappingCogit:
> Reimplement mclassIsSmallInteger in terms of receiverTags, providing more
> generality at cheaper cost (receiverTags is computed during set-up for
> compiling a method).
>
> Improve special-selector comparison and arithmetic based on this if the
> receiver or argument is self and known to be a SmallInteger.  Also improve
> the tag checking to avoid the spurious copy to TempReg unless both receiver
> and argument need to be tested.  These improve code quality in methods such
> as SmallInteger>>digitLength:.
>
> Use anyMask: in ssAllocateRequiredRegMask:upThrough:upThroughNative:
> instead of bitAnd:...~= 0.
>
> RegisterAllocatingCogit:
> Override ssAllocateRequiredRegMask:upThrough:upThroughNative: to void
> optStatus and simStack entries that refer to the allocated register.
>
> Simulator:
> Aim stdio at the coInterpreter's transcript rather than Transcript.
>
> Fix some tag-related bugs in the CurrentImageCoInterpreterFacade
> hierarchy.
>
> =============== Diff against VMMaker.oscog-eem.2137 ===============
>
> Item was added:
> + ----- Method: CogObjectRepresentation>>genJumpNotSmallIntegersIn:and:scratch:
> (in category 'compile abstract instructions') -----
> + genJumpNotSmallIntegersIn: aRegister and: bRegister scratch:
> scratchRegister
> +       "Generate a compare and branch to test if aRegister and bRegister
> contains other than SmallIntegers,
> +        i.e. don't branch if both aRegister and bRegister contain
> SmallIntegers.
> +        Answer the jump.  Destroy scratchRegister if required."
> +       <returnTypeC: #'AbstractInstruction *'>
> +       ^self subclassResponsibility!
>
> Item was removed:
> - ----- Method: CogObjectRepresentation>>genJumpNotSmallIntegersIn:andScratch:scratch:
> (in category 'compile abstract instructions') -----
> - genJumpNotSmallIntegersIn: aRegister andScratch: scratchA scratch:
> scratchB
> -       "Generate a compare and branch to test if aRegister and scratchA
> contains other than SmallIntegers,
> -        i.e. don't branch if both aRegister and scratchA contain
> SmallIntegers.
> -        Answer the jump.  Destroy scratchA and scratchB if required."
> -       <returnTypeC: #'AbstractInstruction *'>
> -       ^self subclassResponsibility!
>
> Item was removed:
> - ----- Method: CogObjectRepresentationFor32BitSpur>>
> genJumpNotSmallIntegersIn:andScratch:scratch: (in category 'compile
> abstract instructions') -----
> - genJumpNotSmallIntegersIn: aRegister andScratch: scratchA scratch:
> scratchB
> -       "Generate a compare and branch to test if aRegister and scratchA
> contains other than SmallIntegers,
> -        i.e. don't branch if both aRegister and scratchA contain
> SmallIntegers.
> -        Answer the jump.  Destroy scratchA and scratchB if required."
> -       <returnTypeC: #'AbstractInstruction *'>
> -       <inline: true>
> -       cogit AndR: aRegister R: scratchA.
> -       ^self genJumpNotSmallIntegerInScratchReg: scratchA!
>
> Item was removed:
> - ----- Method: CogObjectRepresentationFor64BitSpur>>
> genJumpNotSmallIntegersIn:andScratch:scratch: (in category 'compile
> abstract instructions') -----
> - genJumpNotSmallIntegersIn: aRegister andScratch: scratchA scratch:
> scratchB
> -       "Generate a compare and branch to test if aRegister and scratchA
> contains other than SmallIntegers,
> -        i.e. don't branch if both aRegister and scratchA contain
> SmallIntegers.
> -        Answer the jump.  Destroy scratchA and scratchB if required."
> -       <returnTypeC: #'AbstractInstruction *'>
> -       <inline: true>
> -       cogit AndR: aRegister R: scratchA.
> -       ^self genJumpNotSmallIntegerInScratchReg: scratchA!
>
> Item was added:
> + ----- Method: CogObjectRepresentationForSpur>>genJumpNotSmallIntegersIn:and:scratch:
> (in category 'compile abstract instructions') -----
> + genJumpNotSmallIntegersIn: aRegister and: bRegister scratch:
> scratchRegister
> +       "Generate a compare and branch to test if aRegister and bRegister
> contains other than SmallIntegers,
> +        i.e. don't branch if both aRegister and bRegister contain
> SmallIntegers.
> +        Answer the jump.  Destroy scratchRegister if required."
> +       <returnTypeC: #'AbstractInstruction *'>
> +       <returnTypeC: #'AbstractInstruction *'>
> +       <inline: true>
> +       cogit
> +               MoveR: aRegister R: scratchRegister;
> +               AndR: bRegister R: scratchRegister.
> +       ^self genJumpNotSmallIntegerInScratchReg: scratchRegister!
>
> Item was removed:
> - ----- Method: CogObjectRepresentationForSqueakV3>>
> genJumpNotSmallIntegersIn:andScratch:scratch: (in category 'compile
> abstract instructions') -----
> - genJumpNotSmallIntegersIn: aRegister andScratch: scratchA scratch:
> scratchB
> -       "Generate a compare and branch to test if aRegister and scratchA
> contains other than SmallIntegers,
> -        i.e. don't branch if both aRegister and scratchA contain
> SmallIntegers.
> -        Answer the jump.  Destroy scratchA and scratchB if required."
> -       <returnTypeC: #'AbstractInstruction *'>
> -       <inline: true>
> -       cogit AndR: aRegister R: scratchA.
> -       ^self genJumpNotSmallIntegerInScratchReg: scratchA!
>
> Item was removed:
> - ----- Method: CogRegisterAllocatingSimStackEntry>>
> complicatedIsMergedWithTargetEntry: (in category 'comparing') -----
> - complicatedIsMergedWithTargetEntry: targetEntry
> -       "The receiver is a simStackEntry at a jump to the corresponding
> simStackEntry at the jump's target.
> -        Answer if no merge is required for the jump."
> -       <var: 'ssEntry' type: #'CogSimStackEntry *'>
> -       spilled ~= targetEntry spilled ifTrue: "push or pop required"
> -               [^false].
> -       (liveRegister = NoReg and: [targetEntry liveRegister ~= NoReg])
> ifTrue: "register load required"
> -               [^false].
> -       (liveRegister ~= NoReg
> -        and: [liveRegister = targetEntry liveRegister
> -        and: [type = targetEntry type
> -        and: [type = SSConstant or: [type = SSRegister and: [register =
> targetEntry register]]]]]) ifTrue:
> -               [^true].
> -       ((type = SSBaseOffset or: [type == SSSpill])
> -        and: [(targetEntry type = SSBaseOffset or: [targetEntry type ==
> SSSpill])
> -        and: [offset = targetEntry offset and: [register = targetEntry
> register]]]) ifTrue:
> -               [^true].
> -       "self: const =1 (16r1) (live: Extra4Reg) {172} vs reg
> ReceiverResultReg {127}"
> -       "self: reg ReceiverResultReg {95} vs reg Extra5Reg {85}"
> -       ((type = SSConstant and: [targetEntry type = SSRegister and:
> [liveRegister ~= targetEntry registerOrNone]])
> -        or: [type = SSRegister and: [targetEntry type = SSRegister and:
> [register ~= targetEntry registerOrNone]]]) ifFalse:
> -               [self halt: 'comment the incompatible pair please'].
> -       ^false!
>
> Item was removed:
> - ----- Method: CogRegisterAllocatingSimStackEntry>>isSameEntryAs: (in
> category 'comparing') -----
> - isSameEntryAs: ssEntry
> -       <var: 'ssEntry' type: #'CogSimStackEntry *'>
> -       ^type = ssEntry type
> -         and: [((type = SSBaseOffset or: [type == SSSpill]) and: [offset
> = ssEntry offset and: [register = ssEntry register]])
> -               or: [(type = SSRegister and: [register = ssEntry register])
> -               or: [(type = SSConstant and: [constant = ssEntry
> constant])]]]!
>
> Item was removed:
> - ----- Method: CogRegisterAllocatingSimStackEntry>>
> simplifiedIsMergedWithTargetEntry: (in category 'comparing') -----
> - simplifiedIsMergedWithTargetEntry: targetEntry
> -       "The receiver is a simStackEntry at a jump to the corresponding
> simStackEntry at the jump's target.
> -        Answer if no merge is required for the jump."
> -       <var: 'ssEntry' type: #'CogSimStackEntry *'>
> -       spilled ~= targetEntry spilled ifTrue: "push or pop required"
> -               [^false].
> -       (liveRegister = NoReg and: [targetEntry liveRegister ~= NoReg])
> ifTrue: "register load required"
> -               [^false].
> -       (self isSameEntryAs: targetEntry) ifTrue:
> -               [^liveRegister = targetEntry liveRegister].
> -       (type = SSConstant and: [targetEntry type = SSRegister and:
> [liveRegister = targetEntry register]]) ifTrue:
> -               [^true].
> -       "self: const =1 (16r1) (live: Extra4Reg) {172} vs reg
> ReceiverResultReg {127}"
> -       "self: reg ReceiverResultReg {95} vs reg Extra5Reg {85}"
> -       "(bo ReceiverResultReg+296 (live: Extra5Reg) {88} vs reg
> ReceiverResultReg {84}"
> -       ((type = SSConstant and: [targetEntry type = SSRegister and:
> [liveRegister ~= targetEntry registerOrNone]])
> -        or: [(type = SSRegister and: [targetEntry type = SSRegister and:
> [register ~= targetEntry registerOrNone]])
> -        or: [type = SSBaseOffset and: [register = ReceiverResultReg and:
> [targetEntry type = SSRegister]]]]) ifFalse:
> -               [self halt: 'comment the incompatible pair please'].
> -       ^false!
>
> Item was added:
> + ----- Method: CogSimStackEntry>>isSameEntryAs: (in category
> 'comparing') -----
> + isSameEntryAs: ssEntry
> +       <var: 'ssEntry' type: #'CogSimStackEntry *'>
> +       ^type = ssEntry type
> +         and: [((type = SSBaseOffset or: [type == SSSpill]) and: [offset
> = ssEntry offset and: [register = ssEntry register]])
> +               or: [(type = SSRegister and: [register = ssEntry register])
> +               or: [(type = SSConstant and: [constant = ssEntry
> constant])]]]!
>
> 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 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
> maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod
> ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline'
> -       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
> implicitReceiverSendTrampolines cogMethodSurrogateClass
> cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer
> CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel
> maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod
> ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline'
>         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 NeedsFixupFlag
> 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/9/2017 10:01' 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.
>
>         StackToRegisterMappingCogit is an experimental code generator with
> support for counting
>         conditional branches, intended to support adaptive optimization.
>
>   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>>cog:selector: (in category 'jit - api') -----
>   cog: aMethodObj selector: aSelectorOop
>         "Attempt to produce a machine code method for the bytecode method
>          object aMethodObj.  N.B. If there is no code memory available do
> *NOT*
>          attempt to reclaim the method zone.  Certain clients (e.g.
> ceSICMiss:)
>          depend on the zone remaining constant across method generation."
>         <api>
>         <returnTypeC: #'CogMethod *'>
>         | cogMethod |
>         <var: #cogMethod type: #'CogMethod *'>
>         (self exclude: aMethodObj selector: aSelectorOop) ifTrue:
>                 [^nil].
>         "In Newspeak we support anonymous accessors and hence tolerate the
> same
>          method being cogged multiple times.  But only if the method class
> association is nil."
>         NewspeakVM
>                 ifTrue:
>                         [(coInterpreter methodHasCogMethod: aMethodObj)
> ifTrue:
>                                 [cogMethod := coInterpreter cogMethodOf:
> aMethodObj.
>                                  self deny: cogMethod selector =
> aSelectorOop.
>                                  cogMethod selector = aSelectorOop ifTrue:
>                                         [^cogMethod].
>                                  (coInterpreter methodClassAssociationOf:
> aMethodObj) ~= objectMemory nilObject ifTrue:
>                                         [self cCode: 'extern void
> *firstIndexableField(sqInt)'. "Slang, au natural"
>                                          self warnMultiple: cogMethod
> selectors: aSelectorOop.
>                                         ^nil]]]
>                 ifFalse: [self deny: (coInterpreter methodHasCogMethod:
> aMethodObj)].
>         self deny: (objectMemory isOopCompiledMethod: (coInterpreter
> ultimateLiteralOf: aMethodObj)).
>         "coInterpreter stringOf: aSelectorOop"
>         coInterpreter
>                 compilationBreak: aSelectorOop
>                 point: (objectMemory lengthOf: aSelectorOop)
>                 isMNUCase: false.
>         aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of
> breakMethod'].
>         NewspeakVM ifTrue:
>                 [cogMethod := methodZone findPreviouslyCompiledVersionOf:
> aMethodObj with: aSelectorOop.
>                  cogMethod ifNotNil:
>                         [(coInterpreter methodHasCogMethod: aMethodObj)
> not ifTrue:
>                                 [self assert: (coInterpreter rawHeaderOf:
> aMethodObj) = cogMethod methodHeader.
>                                  cogMethod methodObject: aMethodObj.
>                                  coInterpreter rawHeaderOf: aMethodObj
> put: cogMethod asInteger].
>                         ^cogMethod]].
>         "If the generators for the alternate bytecode set are missing then
> interpret."
>         (coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
>                 ifTrue:
>                         [(self numElementsIn: generatorTable) <= 256
> ifTrue:
>                                 [^nil].
>                          bytecodeSetOffset := 256]
>                 ifFalse:
>                         [bytecodeSetOffset := 0].
>         objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
>         methodObj := aMethodObj.
>         methodHeader := objectMemory methodHeaderOf: aMethodObj.
> +       receiverTags := objectMemory receiverTagBitsForMethod: methodObj.
>         cogMethod := self compileCogMethod: aSelectorOop.
>         (cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
>                 [cogMethod asInteger = InsufficientCodeSpace ifTrue:
>                         [coInterpreter callForCogCompiledCodeCompaction].
>                  self maybeFreeCounters.
>                  "Right now no errors should be reported, so nothing more
> to do."
>                  "self reportError: (self cCoerceSimple: cogMethod to:
> #sqInt)."
>                  ^nil].
>         "self cCode: ''
>                 inSmalltalk:
>                         [coInterpreter printCogMethod: cogMethod.
>                          ""coInterpreter symbolicMethod: aMethodObj.""
>                          self assertValidMethodMap: cogMethod."
>                          "self disassembleMethod: cogMethod."
>                          "printInstructions := clickConfirm := true""]."
>         ^cogMethod!
>
> Item was changed:
>   ----- Method: Cogit>>cogFullBlockMethod:numCopied: (in category 'jit -
> api') -----
>   cogFullBlockMethod: aMethodObj numCopied: numCopied
>         "Attempt to produce a machine code method for the bytecode method
>          object aMethodObj.  N.B. If there is no code memory available do
> *NOT*
>          attempt to reclaim the method zone.  Certain clients (e.g.
> ceSICMiss:)
>          depend on the zone remaining constant across method generation."
>         <api>
>         <option: #SistaV1BytecodeSet>
>         <returnTypeC: #'CogMethod *'>
>         | cogMethod |
>         <var: #cogMethod type: #'CogMethod *'>
>         (self exclude: aMethodObj) ifTrue:
>                 [^nil].
>         self deny: (coInterpreter methodHasCogMethod: aMethodObj).
>         self assert: (objectMemory isOopCompiledMethod: (coInterpreter
> ultimateLiteralOf: aMethodObj)).
>         aMethodObj = breakMethod ifTrue: [self halt: 'Compilation of
> breakMethod'].
>         "If the generators for the alternate bytecode set are missing then
> interpret."
>         (coInterpreter methodUsesAlternateBytecodeSet: aMethodObj)
>                 ifTrue:
>                         [(self numElementsIn: generatorTable) <= 256
> ifTrue:
>                                 [^nil].
>                          bytecodeSetOffset := 256]
>                 ifFalse:
>                         [bytecodeSetOffset := 0].
>         objectRepresentation ensureNoForwardedLiteralsIn: aMethodObj.
>         methodObj := aMethodObj.
>         methodHeader := objectMemory methodHeaderOf: aMethodObj.
> +       receiverTags := objectMemory receiverTagBitsForMethod: methodObj.
>         cogMethod := self compileCogFullBlockMethod: numCopied.
>         (cogMethod asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
>                 [cogMethod asInteger = InsufficientCodeSpace ifTrue:
>                         [coInterpreter callForCogCompiledCodeCompaction].
>                  self maybeFreeCounters.
>                  "Right now no errors should be reported, so nothing more
> to do."
>                  "self reportError: (self cCoerceSimple: cogMethod to:
> #sqInt)."
>                  ^nil].
>         "self cCode: ''
>                 inSmalltalk:
>                         [coInterpreter printCogMethod: cogMethod.
>                          ""coInterpreter symbolicMethod: aMethodObj.""
>                          self assertValidMethodMap: cogMethod."
>                          "self disassembleMethod: cogMethod."
>                          "printInstructions := clickConfirm := true""]."
>         ^cogMethod!
>
> Item was changed:
>   ----- Method: Cogit>>mclassIsSmallInteger (in category 'initialization')
> -----
>   mclassIsSmallInteger
> +       ^objectMemory isIntegerObject: receiverTags!
> -       ^(coInterpreter methodClassOf: methodObj) = objectMemory
> classSmallInteger!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacade>>classCharacter (in
> category 'accessing') -----
> + classCharacter
> +       ^self oopForObject: Character!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacade>>lookupOrdinary:receiver:
> (in category 'cog jit support') -----
> + lookupOrdinary: selectorOop receiver: receiverOop
> +       | rcvr selector |
> +       rcvr := self objectForOop: receiverOop.
> +       selector := self objectForOop: selectorOop.
> +       (rcvr class canUnderstand: selector) ifTrue:
> +               [^self oopForObject: ((rcvr class
> whichClassIncludesSelector: selector)
> +
>  compiledMethodAt: selector)].
> +       ^SelectorDoesNotUnderstand!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacade>>maxLookupNoMNUErrorCode
> (in category 'accessing') -----
> + maxLookupNoMNUErrorCode
> +       ^coInterpreter maxLookupNoMNUErrorCode!
>
> Item was changed:
>   ----- Method: CurrentImageCoInterpreterFacade>>objectForOop: (in
> category 'private-cacheing') -----
>   objectForOop: anOop
>         "This is a keyAtValue: search and so needs speeding up either by a
> reverse map or a simple cache."
> +       self subclassResponsibility!
> -       ^(anOop bitAnd: 3) caseOf: {
> -               [0] -> [anOop = cachedOop
> -                               ifTrue: [cachedObject]
> -                               ifFalse: [cachedObject := objectMap
> keyAtValue: anOop. "may raise Error"
> -                                               cachedOop := anOop. "Dom't
> assign until accessed without error"
> -                                               cachedObject]].
> -               [1] -> [anOop signedIntFromLong >> 1].
> -               [3] -> [anOop signedIntFromLong >> 1] }!
>
> Item was changed:
>   ----- Method: CurrentImageCoInterpreterFacade>>stringOf: (in category
> 'accessing') -----
>   stringOf: anOop
> +       | thing |
> +       thing := objectMap
> +                               keyAtValue: anOop
> +                               ifAbsent:
> +                                       [variables
> +                                               keyAtValue: anOop
> +                                               ifAbsent: [^nil]].
> +       ^((thing isLiteral and: [thing isSymbol not])
> +               ifTrue: [thing storeString]
> +               ifFalse: [thing asString]) contractTo: 64!
> -       ^(self lookupAddress: anOop) asString!
>
> Item was changed:
>   ----- Method: CurrentImageCoInterpreterFacad
> eFor64BitSpurObjectRepresentation>>objectForOop: (in category
> 'private-cacheing') -----
>   objectForOop: anOop
>         "This is a keyAtValue: search and so needs speeding up either by a
> reverse map or a simple cache."
> +       ^(anOop bitAnd: 7) caseOf: {
> -       ^(anOop bitAnd: 3) caseOf: {
>                 [0] -> [anOop = cachedOop
>                                 ifTrue: [cachedObject]
>                                 ifFalse: [cachedObject := objectMap
> keyAtValue: anOop. "may raise Error"
>                                                 cachedOop := anOop. "Dom't
> assign until accessed without error"
>                                                 cachedObject]].
>                 [1] -> [anOop signedIntFromLong64 >> 3].
>                 [2] -> [Character value: anOop >> 3].
> +               [4] -> [objectMemory smallFloatValueOf: anOop] }!
> -               [3] -> [objectMemory smallFloatValueOf: anOop] }!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacad
> eForSpurObjectRepresentation>>objectForOop: (in category
> 'private-cacheing') -----
> + objectForOop: anOop
> +       "This is a keyAtValue: search and so needs speeding up either by a
> reverse map or a simple cache."
> +       ^(anOop bitAnd: 3) caseOf: {
> +               [0] -> [anOop = cachedOop
> +                               ifTrue: [cachedObject]
> +                               ifFalse: [cachedObject := objectMap
> keyAtValue: anOop. "may raise Error"
> +                                               cachedOop := anOop. "Dom't
> assign until accessed without error"
> +                                               cachedObject]].
> +               [1] -> [anOop signedIntFromLong >> 1].
> +               [2] -> [Character value: anOop >> 2].
> +               [3] -> [anOop signedIntFromLong >> 1] }!
>
> Item was added:
> + ----- Method: CurrentImageCoInterpreterFacad
> eForSqueakV3ObjectRepresentation>>objectForOop: (in category
> 'private-cacheing') -----
> + objectForOop: anOop
> +       "This is a keyAtValue: search and so needs speeding up either by a
> reverse map or a simple cache."
> +       ^(anOop bitAnd: 3) caseOf: {
> +               [0] -> [anOop = cachedOop
> +                               ifTrue: [cachedObject]
> +                               ifFalse: [cachedObject := objectMap
> keyAtValue: anOop. "may raise Error"
> +                                               cachedOop := anOop. "Dom't
> assign until accessed without error"
> +                                               cachedObject]].
> +               [1] -> [anOop signedIntFromLong >> 1].
> +               [3] -> [anOop signedIntFromLong >> 1] }!
>
> Item was changed:
>   ----- Method: FilePluginSimulator>>initialiseModule (in category
> 'initialize-release') -----
>   initialiseModule
>         "See FilePluginSimulator>>sqFileStdioHandlesInto:"
>         (openFiles := Dictionary new)
>                 at: 0 put: (FakeStdinStream for: interpreterProxy
> interpreter); "stdin"
> +               at: 1 put: interpreterProxy interpreter transcript;
> "stdout"
> +               at: 2 put: interpreterProxy interpreter transcript.
> "stderr"
> -               at: 1 put: Transcript; "stdout"
> -               at: 2 put: Transcript. "stderr"
>         states := IdentityDictionary new.
>         maxOpenFiles := VMClass initializationOptions at:
> #MaxFileDescriptors ifAbsent: [1024].
>         ^super initialiseModule!
>
> Item was added:
> + ----- Method: NewCoObjectMemory>>receiverTagBitsForMethod: (in category
> 'cog jit support') -----
> + receiverTagBitsForMethod: aMethodObj
> +       "Answer the tag bits for the receiver based on the method's
> methodClass, if any."
> +       <api>
> +       ^(coInterpreter methodClassOf: aMethodObj) = self classSmallInteger
> +               ifTrue: [self smallIntegerTag]
> +               ifFalse: [0]!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>genSpecialSelectorArithmetic (in
> category 'bytecode generators') -----
>   genSpecialSelectorArithmetic
>         | primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt
> argInt destReg
>          jumpNotSmallInts jumpContinue jumpOverflow index rcvrReg argReg
> regMask |
>         <var: #jumpOverflow type: #'AbstractInstruction *'>
>         <var: #jumpContinue type: #'AbstractInstruction *'>
>         <var: #primDescriptor type: #'BytecodeDescriptor *'>
>         <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
>         primDescriptor := self generatorAt: byte0.
>         argIsInt := (argIsConst := self ssTop type = SSConstant)
>                                  and: [objectMemory isIntegerObject:
> (argInt := self ssTop constant)].
> +       rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant)
> +                                 and: [objectMemory isIntegerObject:
> (rcvrInt := (self ssValue: 1) constant)])
> +                               or: [self mclassIsSmallInteger and: [(self
> ssValue: 1) isSameEntryAs: (self addressOf: simSelf)]].
> -       rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
> -                                and: [objectMemory isIntegerObject:
> (rcvrInt := (self ssValue: 1) constant)].
>
> +       (argIsInt and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
> -       (argIsInt and: [rcvrIsInt]) ifTrue:
>                 [| result |
>                  rcvrInt := objectMemory integerValueOf: rcvrInt.
>                  argInt := objectMemory integerValueOf: argInt.
>                  primDescriptor opcode caseOf: {
>                         [AddRR] -> [result := rcvrInt + argInt].
>                         [SubRR] -> [result := rcvrInt - argInt].
>                         [AndRR] -> [result := rcvrInt bitAnd: argInt].
>                         [OrRR]          -> [result := rcvrInt bitOr:
> argInt] }.
>                 (objectMemory isIntegerValue: result) ifTrue:
>                         ["Must annotate the bytecode for correct pc
> mapping."
>                         ^self ssPop: 2; ssPushAnnotatedConstant:
> (objectMemory integerObjectOf: result)].
>                 ^self genSpecialSelectorSend].
>
>         "If there's any constant involved other than a SmallInteger don't
> attempt to inline."
>         ((rcvrIsConst and: [rcvrIsInt not])
>          or: [argIsConst and: [argIsInt not]]) ifTrue:
>                 [^self genSpecialSelectorSend].
>
>         "If we know nothing about the types then better not to inline as
> the inline cache and
>          primitive code is not terribly slow so wasting time on
> duplicating tag tests is pointless."
>         (argIsInt or: [rcvrIsInt]) ifFalse:
>                 [^self genSpecialSelectorSend].
>
>         "Since one or other of the arguments is an integer we can very
> likely profit from inlining.
>          But if the other type is not SmallInteger or if the operation
> overflows then we will need
>          to do a send.  Since we're allocating values in registers we
> would like to keep those
>          registers live on the inlined path and reload registers along the
> non-inlined send path.
>          See reconcileRegisterStateForJoinAfterSpecialSelectorSend below."
>         argIsInt
>                 ifTrue:
>                         [rcvrReg := self allocateRegForStackEntryAt: 1.
>                          (self ssValue: 1) popToReg: rcvrReg.
> -                        self MoveR: rcvrReg R: TempReg.
>                          regMask := self registerMaskFor: rcvrReg]
>                 ifFalse:
>                         [self allocateRegForStackTopTwoEntriesInto:
> [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
>                          self ssTop popToReg: argReg.
>                          (self ssValue: 1) popToReg: rcvrReg.
> -                        self MoveR: argReg R: TempReg.
>                          regMask := self registerMaskFor: rcvrReg and:
> argReg].
>
>         "rcvrReg can be reused for the result iff the receiver is a
> constant or is an SSRegister that is not used elsewhere."
> +       destReg := ((rcvrIsInt and: [rcvrIsConst])
> -       destReg := (rcvrIsInt
>                                  or: [(self ssValue: 1) type = SSRegister
>                                          and: [(self
> anyReferencesToRegister: rcvrReg inAllButTopNItems: 2) not]])
>                                         ifTrue: [rcvrReg]
>                                         ifFalse: [self
> allocateRegNotConflictingWith: regMask].
>         self ssPop: 2.
> +       jumpNotSmallInts := (rcvrIsInt and: [argIsInt]) ifFalse:
> +                                                       [argIsInt
> +                                                               ifTrue:
> [objectRepresentation genJumpNotSmallInteger: rcvrReg]
> +                                                               ifFalse:
> +
>  [rcvrIsInt
> +
>      ifTrue: [objectRepresentation genJumpNotSmallInteger: argReg]
> +
>      ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg and:
> argReg scratch: TempReg]]].
> -       jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
> -                                                       ifTrue:
> [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
> -                                                       ifFalse:
> [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch:
> TempReg scratch: ClassReg].
>         rcvrReg ~= destReg ifTrue:
>                 [self MoveR: rcvrReg R: destReg].
>         primDescriptor opcode caseOf: {
>                 [AddRR] -> [argIsInt
>                                                 ifTrue:
>                                                         [self AddCq:
> argInt - ConstZero R: destReg.
>                                                          jumpContinue :=
> self JumpNoOverflow: 0.
>                                                          "overflow; must
> undo the damage before doing send"
>                                                          rcvrReg = destReg
> ifTrue:
>                                                                 [self
> SubCq: argInt - ConstZero R: rcvrReg]]
>                                                 ifFalse:
>
> [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: destReg.
>                                                          self AddR: argReg
> R: destReg.
>                                                          jumpContinue :=
> self JumpNoOverflow: 0.
>                                                         "overflow; must
> undo the damage before doing send"
>                                                          destReg = rcvrReg
> ifTrue:
> +
>  [(rcvrIsInt and: [rcvrIsConst])
> -                                                               [rcvrIsInt
>
> ifTrue: [self MoveCq: rcvrInt R: rcvrReg]
>
> ifFalse:
>
>       [self SubR: argReg R: rcvrReg.
>
>        objectRepresentation genSetSmallIntegerTagsIn: rcvrReg]]]].
>                 [SubRR] -> [argIsInt
>                                                 ifTrue:
>                                                         [self SubCq:
> argInt - ConstZero R: destReg.
>                                                          jumpContinue :=
> self JumpNoOverflow: 0.
>                                                          "overflow; must
> undo the damage before doing send"
>                                                          rcvrReg = destReg
> ifTrue:
>                                                                 [self
> AddCq: argInt - ConstZero R: rcvrReg]]
>                                                 ifFalse:
>                                                         [(self
> anyReferencesToRegister: argReg inAllButTopNItems: 0)
>                                                                 ifTrue:
> "argReg is live; cannot strip tags and continue on no overflow without
> restoring tags"
>
> [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
>
>  self SubR: argReg R: destReg.
>
>  jumpOverflow := self JumpOverflow: 0.
>
>  "no overflow; must undo the damage before continuing"
>
>  objectRepresentation genSetSmallIntegerTagsIn: argReg.
>
>  jumpContinue := self Jump: 0.
>
>  jumpOverflow jmpTarget: self Label.
>
>  "overflow; must undo the damage before doing send"
> +
> ((rcvrIsInt and: [rcvrIsConst]) or: [destReg ~= rcvrReg]) ifFalse:
> -
> (rcvrIsInt or: [destReg ~= rcvrReg]) ifFalse:
>
>       [self AddR: argReg R: destReg].
>
>  objectRepresentation genSetSmallIntegerTagsIn: argReg]
>                                                                 ifFalse:
>
> [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
>
>  self SubR: argReg R: destReg.
>
>  jumpContinue := self JumpNoOverflow: 0.
>
>  "overflow; must undo the damage before doing send"
> +
> ((rcvrIsInt and: [rcvrIsConst]) or: [destReg ~= rcvrReg]) ifFalse:
> -
> (rcvrIsInt or: [destReg ~= rcvrReg]) ifFalse:
>
>       [self AddR: argReg R: rcvrReg].
>
>  objectRepresentation genSetSmallIntegerTagsIn: argReg]]].
>                 [AndRR] -> [argIsInt
>                                                 ifTrue: [self AndCq:
> argInt R: destReg]
>                                                 ifFalse: [self AndR:
> argReg R: destReg].
>                                         jumpContinue := self Jump: 0].
>                 [OrRR]  -> [argIsInt
>                                                 ifTrue: [self OrCq: argInt
> R: destReg]
>                                                 ifFalse: [self OrR: argReg
> R: destReg].
>                                         jumpContinue := self Jump: 0] }.
>         jumpNotSmallInts jmpTarget: self Label.
>         self ssPushRegister: destReg.
>         self copySimStackToScratch: (simSpillBase min: simStackPtr - 1).
>         self ssPop: 1.
>         self ssFlushTo: simStackPtr.
> +       rcvrReg = Arg0Reg
> +               ifTrue:
> +                       [argReg = ReceiverResultReg
> +                               ifTrue: [self SwapR: Arg0Reg R: Arg0Reg
> Scratch: TempReg. argReg := Arg0Reg]
> +                               ifFalse: [self MoveR: rcvrReg R:
> ReceiverResultReg].
> +                        rcvrReg := ReceiverResultReg].
> -       self deny: rcvrReg = Arg0Reg.
>         argIsInt
>                 ifTrue: [self MoveCq: argInt R: Arg0Reg]
>                 ifFalse: [argReg ~= Arg0Reg ifTrue: [self MoveR: argReg R:
> Arg0Reg]].
>         rcvrReg ~= ReceiverResultReg ifTrue: [self MoveR: rcvrReg R:
> ReceiverResultReg].
>         index := byte0 - self firstSpecialSelectorBytecodeOffset.
>         self genMarshalledSend: index negated - 1 numArgs: 1 sendTable:
> ordinarySendTrampolines.
>         self reconcileRegisterStateForJoinAfterSpecialSelectorSend.
>         jumpContinue jmpTarget: self Label.
>         ^0!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>genSpecialSelectorComparison (in
> category 'bytecode generators') -----
>   genSpecialSelectorComparison
>         | nextPC postBranchPC targetPC primDescriptor branchDescriptor
> +         rcvrIsInt rcvrIsConst argIsIntConst argInt jumpNotSmallInts
> inlineCAB index rcvrReg argReg branchToTarget needMergeToContinue
> needMergeToTarget |
> -         rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index
> rcvrReg argReg branchToTarget needMergeToContinue needMergeToTarget |
>         <var: #primDescriptor type: #'BytecodeDescriptor *'>
>         <var: #branchDescriptor type: #'BytecodeDescriptor *'>
>         <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
>         primDescriptor := self generatorAt: byte0.
> +       argIsIntConst := self ssTop type = SSConstant
> -       argIsInt := self ssTop type = SSConstant
>                                  and: [objectMemory isIntegerObject:
> (argInt := self ssTop constant)].
> +       rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant)
> +                                 and: [objectMemory isIntegerObject:
> (self ssValue: 1) constant])
> +                               or: [self mclassIsSmallInteger and: [(self
> ssValue: 1) isSameEntryAs: (self addressOf: simSelf)]].
> -       rcvrIsInt := (self ssValue: 1) type = SSConstant
> -                                and: [objectMemory isIntegerObject: (self
> ssValue: 1) constant].
>
> +       (argIsIntConst and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
> -       (argIsInt and: [rcvrIsInt]) ifTrue:
>                 [^self genStaticallyResolvedSpecialSelectorComparison].
>
>         self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch
> :target |
>                 branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetPC := target ].
>
>         "Only interested in inlining if followed by a conditional branch."
>         inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor
> isBranchFalse].
>         "Further, only interested in inlining = and ~= if there's a
> SmallInteger constant involved.
>          The relational operators successfully statically predict
> SmallIntegers; the equality operators do not."
>         (inlineCAB and: [primDescriptor opcode = JumpZero or:
> [primDescriptor opcode = JumpNonZero]]) ifTrue:
> +               [inlineCAB := argIsIntConst or: [rcvrIsInt]].
> -               [inlineCAB := argIsInt or: [rcvrIsInt]].
>         inlineCAB ifFalse:
>                 [^self genSpecialSelectorSend].
>
>         "In-line the comparison and the jump, but if the types are not
> SmallInteger then we will need
>          to do a send and fall through to the following conditional
> branch.  Since we're allocating values
>          in registers we would like to keep those registers live on the
> inlined path and reload registers
>          along the non-inlined send path.  The merge logic at the branch
> destinations handles this."
> +       argIsIntConst
> -       argIsInt
>                 ifTrue:
>                         [rcvrReg := self allocateRegForStackEntryAt: 1.
> +                        (self ssValue: 1) popToReg: rcvrReg.
> +                        argReg := NoReg]
> -                        (self ssValue: 1) popToReg: rcvrReg]
>                 ifFalse:
>                         [self allocateRegForStackTopTwoEntriesInto:
> [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
>                          rcvrReg = Arg0Reg ifTrue:
>                                 [rcvrReg := argReg. argReg := Arg0Reg].
>                          self ssTop popToReg: argReg.
> +                        (self ssValue: 1) popToReg: rcvrReg].
> -                        (self ssValue: 1) popToReg: rcvrReg.
> -                        rcvrIsInt ifFalse:
> -                               [self MoveR: argReg R: TempReg]].
>         self ssPop: 2.
> +       jumpNotSmallInts := (rcvrIsInt and: [argIsIntConst]) ifFalse:
> +                                                       [argIsIntConst
> +                                                               ifTrue:
> [objectRepresentation genJumpNotSmallInteger: rcvrReg]
> +                                                               ifFalse:
> +
>  [rcvrIsInt
> +
>      ifTrue: [objectRepresentation genJumpNotSmallInteger: argReg]
> +
>      ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg and:
> argReg scratch: TempReg]]].
> +       argIsIntConst
> -       jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
> -                                                       ifFalse: "Neither
> known to be ints; and them together for the test..."
> -
>  [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch:
> TempReg scratch: ClassReg]
> -                                                       ifTrue: "One
> known; in-place single-bit test for the other"
> -
>  [objectRepresentation genJumpNotSmallInteger: (rcvrIsInt ifTrue: [argReg]
> ifFalse: [rcvrReg])].
> -       argIsInt
>                 ifTrue: [self CmpCq: argInt R: rcvrReg]
>                 ifFalse: [self CmpR: argReg R: rcvrReg].
>
>         "self printSimStack; printSimStack: (self fixupAt: postBranchPC)
> mergeSimStack; printSimStack: (self fixupAt: targetPC) mergeSimStack"
>         "If there are merges to be performed on the forward branches we
> have to execute
>          the merge code only along the path requiring that merge, and
> exactly once."
>         needMergeToTarget := self mergeRequiredForJumpTo: targetPC.
>         needMergeToContinue := self mergeRequiredForJumpTo: postBranchPC.
>         "Cmp is weird/backwards so invert the comparison."
>         (needMergeToTarget and: [needMergeToContinue]) ifTrue:
>                 [branchToTarget := self genConditionalBranch:
> (branchDescriptor isBranchTrue
>
>       ifTrue: [primDescriptor opcode]
>
>       ifFalse: [self inverseBranchFor: primDescriptor opcode])
>                                                                 operand: 0.
>                  self Jump: (self ensureFixupAt: postBranchPC).
>                  branchToTarget jmpTarget: self Label.
>                  self Jump: (self ensureFixupAt: targetPC)].
>         (needMergeToTarget and: [needMergeToContinue not]) ifTrue:
>                 [self genConditionalBranch: (branchDescriptor isBranchFalse
>
>       ifTrue: [primDescriptor opcode]
>
>       ifFalse: [self inverseBranchFor: primDescriptor opcode])
>                         operand: (self ensureFixupAt: postBranchPC)
> asUnsignedInteger.
>                  self Jump: (self ensureFixupAt: targetPC)].
>         (needMergeToTarget not and: [needMergeToContinue]) ifTrue:
>                 [self genConditionalBranch: (branchDescriptor isBranchTrue
>
>       ifTrue: [primDescriptor opcode]
>
>       ifFalse: [self inverseBranchFor: primDescriptor opcode])
>                         operand: (self ensureFixupAt: targetPC)
> asUnsignedInteger.
>                  self Jump: (self ensureFixupAt: postBranchPC)].
>         (needMergeToTarget or: [needMergeToContinue]) ifFalse:
>                 [self genConditionalBranch: (branchDescriptor isBranchTrue
>
>       ifTrue: [primDescriptor opcode]
>
>       ifFalse: [self inverseBranchFor: primDescriptor opcode])
>                         operand: (self ensureFixupAt: targetPC)
> asUnsignedInteger.
>                  self Jump: (self ensureFixupAt: postBranchPC)].
> +       jumpNotSmallInts ifNil:
> +               [self annotateInstructionForBytecode.
> +                deadCode := true.
> +                ^0].
>         jumpNotSmallInts jmpTarget: self Label.
>         self ssFlushTo: simStackPtr.
> +       rcvrReg = Arg0Reg
> +               ifTrue:
> +                       [argReg = ReceiverResultReg
> +                               ifTrue: [self SwapR: Arg0Reg R: Arg0Reg
> Scratch: TempReg. argReg := Arg0Reg]
> +                               ifFalse: [self MoveR: rcvrReg R:
> ReceiverResultReg].
> +                        rcvrReg := ReceiverResultReg].
> +       argIsIntConst
> -       self deny: rcvrReg = Arg0Reg.
> -       argIsInt
>                 ifTrue: [self MoveCq: argInt R: Arg0Reg]
>                 ifFalse: [argReg ~= Arg0Reg ifTrue: [self MoveR: argReg R:
> Arg0Reg]].
>         rcvrReg ~= ReceiverResultReg ifTrue: [self MoveR: rcvrReg R:
> ReceiverResultReg].
>         index := byte0 - self firstSpecialSelectorBytecodeOffset.
>         ^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable:
> ordinarySendTrampolines!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith:forwards:
> (in category 'bytecode generator support') -----
>   mergeCurrentSimStackWith: fixup forwards: forwards
>         "At a merge point the cogit expects the stack to be in the same
> state as mergeSimStack.
>          mergeSimStack is the state as of some jump forward or backward to
> this point.  So make simStack agree
>          with mergeSimStack (it is, um, problematic to plant code at the
> jump).
>          Values may have to be assigned to registers.  Registers may have
> to be swapped.
>          The state of optStatus must agree.
>          Generate code to merge the current simStack with that of the
> target fixup,
>          the goal being to keep as many registers live as possible.  If
> the merge is forwards
>          registers can be deassigned (since registers are always written
> to temp vars).
>          But if backwards, nothing can be deassigned, and the state /must/
> reflect the target."
>         "self printSimStack; printSimStack: fixup mergeSimStack"
> +       "abstractOpcodes object copyFrom: startIndex to: opcodeIndex"
>         <var: #fixup type: #'BytecodeFixup *'>
>         | startIndex mergeSimStack currentEntry targetEntry
> writtenToRegisters |
>         <var: #mergeSimStack type: #'SimStackEntry *'>
>         <var: #targetEntry type: #'SimStackEntry *'>
>         <var: #currentEntry type: #'SimStackEntry *'>
>         (mergeSimStack := fixup mergeSimStack) ifNil: [^self].
>         startIndex := opcodeIndex. "for debugging"
>         "Assignments amongst the registers must be made in order to avoid
> overwriting.
>          If necessary exchange registers amongst simStack's entries to
> resolve any conflicts."
>         self resolveRegisterOrderConflictsBetweenCurrentSimStackAnd:
> mergeSimStack.
>         (self asserta: (self conflictsResolvedBetweenSimStackAnd:
> mergeSimStack)) ifFalse:
>                 [Notification new tag: #failedMerge; signal].
>         writtenToRegisters := 0.
>         (self pushForMergeWith: mergeSimStack)
>                 ifTrue:
>                         [methodOrBlockNumArgs to: simStackPtr do:
>                                 [:i|
>                                  currentEntry := self simStack: simStack
> at: i.
>                                  targetEntry := self simStack:
> mergeSimStack at: i.
>                                  writtenToRegisters := writtenToRegisters
> bitOr: targetEntry registerMask.
>                                  (currentEntry reconcileForwardsWith:
> targetEntry) ifTrue:
>                                         [self assert: i >=
> methodOrBlockNumArgs.
>                                          self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack].
>                                  "Note, we could update the simStack and
> spillBase here but that is done in restoreSimStackAtMergePoint:
>                                  spilled ifFalse:
>                                         [simSpillBase := i - 1].
>                                  simStack
>                                         at: i
>                                         put: (self
>                                                         cCode:
> [mergeSimStack at: i]
>                                                         inSmalltalk:
> [(mergeSimStack at: i) copy])"]]
>                 ifFalse:
>                         [simStackPtr to: methodOrBlockNumArgs by: -1 do:
>                                 [:i|
>                                  currentEntry := self simStack: simStack
> at: i.
>                                  targetEntry := self simStack:
> mergeSimStack at: i.
>                                  writtenToRegisters := writtenToRegisters
> bitOr: targetEntry registerMask.
>                                  (currentEntry reconcileForwardsWith:
> targetEntry) ifTrue:
>                                         [self assert: i >=
> methodOrBlockNumArgs.
>                                          self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack].
>                                  "Note, we could update the simStack and
> spillBase here but that is done in restoreSimStackAtMergePoint:
>                                  spilled ifFalse:
>                                         [simSpillBase := i - 1].
>                                  simStack
>                                         at: i
>                                         put: (self
>                                                         cCode:
> [mergeSimStack at: i]
>                                                         inSmalltalk:
> [(mergeSimStack at: i) copy])"]].
>         methodOrBlockNumArgs - 1 to: 0 by: -1 do:
>                 [:i|
>                  targetEntry := self simStack: mergeSimStack at: i.
>                  (targetEntry registerMask noMask: writtenToRegisters)
> ifTrue:
>                         [currentEntry := self simStack: simStack at: i.
>                          writtenToRegisters := writtenToRegisters bitOr:
> targetEntry registerMask.
>                          (currentEntry reconcileForwardsWith: targetEntry)
> ifTrue:
>                                 [self assert: i >= methodOrBlockNumArgs.
>                                  self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack]]].
>         optStatus isReceiverResultRegLive ifFalse:
>                 [forwards
>                         ifTrue: "a.k.a. fixup isReceiverResultRegSelf:
> (fixup isReceiverResultRegSelf and: [optStatus isReceiverResultRegLive])"
>                                 [fixup isReceiverResultRegSelf: false]
>                         ifFalse:
>                                 [fixup isReceiverResultRegSelf ifTrue:
>                                         [self
> putSelfInReceiverResultReg]]]!
>
> Item was added:
> + ----- Method: RegisterAllocatingCogit>>ssAllocateRequiredRegMask:upThrough:upThroughNative:
> (in category 'simulation stack') -----
> + ssAllocateRequiredRegMask: requiredRegsMask upThrough: stackPtr
> upThroughNative: nativeStackPtr
> +       "Override to void any required registers in temp vars."
> +       (requiredRegsMask anyMask: (self registerMaskFor:
> ReceiverResultReg)) ifTrue:
> +               [optStatus isReceiverResultRegLive: false.
> +                optStatus ssEntry liveRegister: NoReg].
> +       0 to: methodOrBlockNumTemps - 1 do:
> +               [:i|
> +               ((self simStackAt: i) registerMask anyMask:
> requiredRegsMask) ifTrue:
> +                       [(self simStackAt: i) liveRegister: 0]].
> +       super ssAllocateRequiredRegMask: requiredRegsMask upThrough:
> stackPtr upThroughNative: nativeStackPtr!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genLongUnconditionalBackwardJump
> (in category 'bytecode generators') -----
>   genLongUnconditionalBackwardJump
> +       | distance |
> -       | distance targetpc |
>         distance := self v3: (self generatorAt: byte0)
>                                         Long: bytecodePC
>                                         Branch: 0
>                                         Distance: methodObj.
>         self assert: distance < 0.
> +       ^self genJumpBackTo: distance + 2 + bytecodePC!
> -       targetpc := distance + 2 + bytecodePC.
> -       ^self genJumpBackTo: targetpc!
>
> Item was changed:
>   ----- Method: SistaCogit>>genSpecialSelectorComparison (in category
> 'bytecode generators') -----
>   genSpecialSelectorComparison
>         "Override to count inlined branches if followed by a conditional
> branch.
>          We borrow the following conditional branch's counter and when
> about to
>          inline the comparison we decrement the counter (without writing
> it back)
>          and if it trips simply abort the inlining, falling back to the
> normal send which
>          will then continue to the conditional branch which will trip and
> enter the abort."
> +       | nextPC postBranchPC targetPC primDescriptor branchDescriptor
> +         rcvrIsInt rcvrIsConst argIsIntConst argInt jumpNotSmallInts
> inlineCAB
> -       | nextPC postBranchPC targetBytecodePC primDescriptor
> branchDescriptor
> -         rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB
>           counterAddress countTripped counterReg index |
>         <var: #countTripped type: #'AbstractInstruction *'>
>         <var: #primDescriptor type: #'BytecodeDescriptor *'>
>         <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
>         <var: #branchDescriptor type: #'BytecodeDescriptor *'>
>
>         (coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self
> genSpecialSelectorComparisonWithoutCounters ].
>
>         self ssFlushTo: simStackPtr - 2.
>         primDescriptor := self generatorAt: byte0.
> +       argIsIntConst := self ssTop type = SSConstant
> -       argIsInt := self ssTop type = SSConstant
>                                  and: [objectMemory isIntegerObject:
> (argInt := self ssTop constant)].
> +       rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant)
> +                                 and: [objectMemory isIntegerObject:(self
> ssValue: 1) constant])
> +                               or: [self mclassIsSmallInteger and: [(self
> ssValue: 1) isSameEntryAs: simSelf]].
> -       rcvrIsInt := (self ssValue: 1) type = SSConstant
> -                                and: [objectMemory isIntegerObject: (self
> ssValue: 1) constant].
>
>         "short-cut the jump if operands are SmallInteger constants."
> +       (argIsIntConst and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
> -       (argIsInt and: [rcvrIsInt]) ifTrue:
>                 [^ self genStaticallyResolvedSpecialSelectorComparison].
>
>         self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch
> :target |
> +               branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetPC := target ].
> -               branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetBytecodePC := target ].
>
>         "Only interested in inlining if followed by a conditional branch."
>         inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor
> isBranchFalse].
>         "Further, only interested in inlining = and ~= if there's a
> SmallInteger constant involved.
>          The relational operators successfully statically predict
> SmallIntegers; the equality operators do not."
>         (inlineCAB and: [primDescriptor opcode = JumpZero or:
> [primDescriptor opcode = JumpNonZero]]) ifTrue:
> +               [inlineCAB := argIsIntConst or: [rcvrIsInt]].
> -               [inlineCAB := argIsInt or: [rcvrIsInt]].
>         inlineCAB ifFalse:
>                 [^self genSpecialSelectorSend].
>
> +       argIsIntConst
> -       argIsInt
>                 ifTrue:
>                         [(self ssValue: 1) popToReg: ReceiverResultReg.
> +                        self ssPop: 2]
> -                        self ssPop: 2.
> -                        self MoveR: ReceiverResultReg R: TempReg]
>                 ifFalse:
> +                       [self marshallSendArguments: 1].
> +       jumpNotSmallInts := (rcvrIsInt and: [argIsIntConst]) ifFalse:
> +                                                       [argIsIntConst
> +                                                               ifTrue:
> [objectRepresentation genJumpNotSmallInteger: ReceiverResultReg]
> +                                                               ifFalse:
> +
>  [rcvrIsInt
> +
>      ifTrue: [objectRepresentation genJumpNotSmallInteger: Arg0Reg]
> +
>      ifFalse: [objectRepresentation genJumpNotSmallIntegersIn:
> ReceiverResultReg and: Arg0Reg scratch: TempReg]]].
> -                       [self marshallSendArguments: 1.
> -                        self MoveR: Arg0Reg R: TempReg].
> -       jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
> -                                                       ifTrue:
> [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
> -                                                       ifFalse:
> [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg
> andScratch: TempReg scratch: ClassReg].
>
>         counterReg := self allocateRegNotConflictingWith: (self
> registerMaskFor: ReceiverResultReg and: Arg0Reg).
>         self
>                 genExecutionCountLogicInto: [ :cAddress :countTripBranch |
>                         counterAddress := cAddress.
>                         countTripped := countTripBranch ]
>                 counterReg: counterReg.
>
> +       argIsIntConst
> -       argIsInt
>                 ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
>                 ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
>         "Cmp is weird/backwards so invert the comparison.  Further since
> there is a following conditional
>          jump bytecode define non-merge fixups and leave the cond bytecode
> to set the mergeness."
>         self genConditionalBranch: (branchDescriptor isBranchTrue
>                                 ifTrue: [primDescriptor opcode]
>                                 ifFalse: [self inverseBranchFor:
> primDescriptor opcode])
> +               operand: (self ensureNonMergeFixupAt: targetPC)
> asUnsignedInteger.
> -               operand: (self ensureNonMergeFixupAt: targetBytecodePC)
> asUnsignedInteger.
>
>         self genFallsThroughCountLogicCounterReg: counterReg
> counterAddress: counterAddress.
>
>         self Jump: (self ensureNonMergeFixupAt: postBranchPC).
> +       countTripped jmpTarget: self Label.
> +       jumpNotSmallInts ifNil:
> +               [self annotateInstructionForBytecode.
> +                self ensureFixupAt: postBranchPC.
> +                self ensureFixupAt: targetPC.
> +                deadCode := true.
> +                ^0].
> +       jumpNotSmallInts jmpTarget: countTripped getJmpTarget.
> -       countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
>
> +       argIsIntConst ifTrue:
> -       argIsInt ifTrue:
>                 [self MoveCq: argInt R: Arg0Reg].
>         index := byte0 - self firstSpecialSelectorBytecodeOffset.
>         ^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable:
> ordinarySendTrampolines!
>
> Item was changed:
>   ----- Method: SistaRegisterAllocatingCogit>>genSpecialSelectorComparison
> (in category 'bytecode generators') -----
>   genSpecialSelectorComparison
>         "Override to count inlined branches if followed by a conditional
> branch.
>          We borrow the following conditional branch's counter and when
> about to
>          inline the comparison we decrement the counter (without writing
> it back)
>          and if it trips simply abort the inlining, falling back to the
> normal send which
>          will then continue to the conditional branch which will trip and
> enter the abort."
> +       | nextPC postBranchPC targetPC primDescriptor branchDescriptor
> +         rcvrIsInt rcvrIsConst argIsIntConst argInt jumpNotSmallInts
> inlineCAB
> -       | nextPC postBranchPC targetBytecodePC primDescriptor
> branchDescriptor
> -         rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB
>           counterAddress countTripped counterReg index rcvrReg argReg |
>         <var: #countTripped type: #'AbstractInstruction *'>
>         <var: #primDescriptor type: #'BytecodeDescriptor *'>
>         <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
>         <var: #branchDescriptor type: #'BytecodeDescriptor *'>
>
>         (coInterpreter isOptimizedMethod: methodObj) ifTrue:
>                 [^self genSpecialSelectorComparisonWithoutCounters].
>
>         primDescriptor := self generatorAt: byte0.
> +       argIsIntConst := self ssTop type = SSConstant
> -       argIsInt := self ssTop type = SSConstant
>                                  and: [objectMemory isIntegerObject:
> (argInt := self ssTop constant)].
> +       rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant)
> +                                 and: [objectMemory isIntegerObject:
> (self ssValue: 1) constant])
> +                               or: [self mclassIsSmallInteger and: [(self
> ssValue: 1) isSameEntryAs: (self addressOf: simSelf)]].
> -       rcvrIsInt := (self ssValue: 1) type = SSConstant
> -                                and: [objectMemory isIntegerObject: (self
> ssValue: 1) constant].
>
>         "short-cut the jump if operands are SmallInteger constants."
> +       (argIsIntConst and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
> -       (argIsInt and: [rcvrIsInt]) ifTrue:
>                 [^ self genStaticallyResolvedSpecialSelectorComparison].
>
>         self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch
> :target |
> +               branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetPC := target ].
> -               branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetBytecodePC := target ].
>
>         "Only interested in inlining if followed by a conditional branch."
>         inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor
> isBranchFalse].
>         "Further, only interested in inlining = and ~= if there's a
> SmallInteger constant involved.
>          The relational operators successfully statically predict
> SmallIntegers; the equality operators do not."
>         (inlineCAB and: [primDescriptor opcode = JumpZero or:
> [primDescriptor opcode = JumpNonZero]]) ifTrue:
> +               [inlineCAB := argIsIntConst or: [rcvrIsInt]].
> -               [inlineCAB := argIsInt or: [rcvrIsInt]].
>         inlineCAB ifFalse:
>                 [^self genSpecialSelectorSend].
>
>         "In-line the comparison and the jump, but if the types are not
> SmallInteger then we will need
>          to do a send and fall through to the following conditional
> branch.  Since we're allocating values
>          in registers we would like to keep those registers live on the
> inlined path and reload registers
>          along the non-inlined send path.  The merge logic at the branch
> destinations handles this."
> +       argIsIntConst
> -       argIsInt
>                 ifTrue:
>                         [rcvrReg := self allocateRegForStackEntryAt: 1.
>                          (self ssValue: 1) popToReg: rcvrReg.
> -                        self MoveR: rcvrReg R: TempReg.
>                          counterReg := self allocateRegNotConflictingWith:
> (self registerMaskFor: rcvrReg)]
>                 ifFalse:
>                         [self allocateRegForStackTopTwoEntriesInto:
> [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
>                          rcvrReg = Arg0Reg ifTrue:
>                                 [rcvrReg := argReg. argReg := Arg0Reg].
>                          self ssTop popToReg: argReg.
>                          (self ssValue: 1) popToReg: rcvrReg.
> -                        self MoveR: argReg R: TempReg.
>                          counterReg := self allocateRegNotConflictingWith:
> (self registerMaskFor: rcvrReg and: argReg)].
> +       jumpNotSmallInts := (rcvrIsInt and: [argIsIntConst]) ifFalse:
> +                                                       [argIsIntConst
> +                                                               ifTrue:
> [objectRepresentation genJumpNotSmallInteger: ReceiverResultReg]
> +                                                               ifFalse:
> +
>  [rcvrIsInt
> +
>      ifTrue: [objectRepresentation genJumpNotSmallInteger: Arg0Reg]
> +
>      ifFalse: [objectRepresentation genJumpNotSmallIntegersIn:
> ReceiverResultReg and: Arg0Reg scratch: TempReg]]].
> -       jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
> -                                                       ifTrue:
> [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
> -                                                       ifFalse:
> [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch:
> TempReg scratch: ClassReg].
>
>         self
>                 genExecutionCountLogicInto: [ :cAddress :countTripBranch |
>                         counterAddress := cAddress.
>                         countTripped := countTripBranch ]
>                 counterReg: counterReg.
>
> +       argIsIntConst
> -       argIsInt
>                 ifTrue: [self CmpCq: argInt R: rcvrReg]
>                 ifFalse: [self CmpR: argReg R: rcvrReg].
>         "Cmp is weird/backwards so invert the comparison.  Further since
> there is a following conditional
>          jump bytecode define non-merge fixups and leave the cond bytecode
> to set the mergeness."
>         self genConditionalBranch: (branchDescriptor isBranchTrue
>                                 ifTrue: [primDescriptor opcode]
>                                 ifFalse: [self inverseBranchFor:
> primDescriptor opcode])
> +               operand: (self ensureFixupAt: targetPC) asUnsignedInteger.
> -               operand: (self ensureFixupAt: targetBytecodePC)
> asUnsignedInteger.
>
>         self genFallsThroughCountLogicCounterReg: counterReg
> counterAddress: counterAddress.
>
>         self Jump: (self ensureFixupAt: postBranchPC).
> +       countTripped jmpTarget: self Label.
> +       jumpNotSmallInts ifNil:
> +               [self annotateInstructionForBytecode.
> +                deadCode := true.
> +                ^0].
> +       jumpNotSmallInts jmpTarget: countTripped getJmpTarget.
> -       countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
>
>         self ssFlushTo: simStackPtr.
>         self deny: rcvrReg = Arg0Reg.
> +       argIsIntConst
> -       argIsInt
>                 ifTrue: [self MoveCq: argInt R: Arg0Reg]
>                 ifFalse: [argReg ~= Arg0Reg ifTrue: [self MoveR: argReg R:
> Arg0Reg]].
>         rcvrReg ~= ReceiverResultReg ifTrue: [self MoveR: rcvrReg R:
> ReceiverResultReg].
>         index := byte0 - self firstSpecialSelectorBytecodeOffset.
>         ^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable:
> ordinarySendTrampolines!
>
> Item was added:
> + ----- Method: Spur32BitCoMemoryManager>>receiverTagBitsForMethod: (in
> category 'cog jit support') -----
> + receiverTagBitsForMethod: aMethodObj
> +       "Answer the tag bits for the receiver based on the method's
> methodClass, if any."
> +       <api>
> +       | methodClass |
> +       methodClass := coInterpreter methodClassOf: aMethodObj.
> +       (self instSpecOfClass: methodClass) ~= self forwardedFormat ifTrue:
> +               [^0].
> +       ^methodClass = (self fetchPointer: self smallIntegerTag ofObject:
> classTableFirstPage)
> +               ifTrue: [self smallIntegerTag]
> +               ifFalse: [self assert: methodClass = (self fetchPointer:
> self characterTag ofObject: classTableFirstPage).
> +                               self characterTag]!
>
> Item was added:
> + ----- Method: Spur64BitCoMemoryManager>>classSmallFloat (in category
> 'accessing') -----
> + classSmallFloat
> +       <api>
> +       ^self fetchPointer: self smallFloatTag ofObject:
> classTableFirstPage!
>
> Item was added:
> + ----- Method: Spur64BitCoMemoryManager>>receiverTagBitsForMethod: (in
> category 'cog jit support') -----
> + receiverTagBitsForMethod: aMethodObj
> +       "Answer the tag bits for the receiver based on the method's
> methodClass, if any."
> +       <api>
> +       | methodClass |
> +       methodClass := coInterpreter methodClassOf: aMethodObj.
> +       (self instSpecOfClass: methodClass) ~= self forwardedFormat ifTrue:
> +               [^0].
> +       methodClass = (self fetchPointer: self smallIntegerTag ofObject:
> classTableFirstPage) ifTrue:
> +               [^self smallIntegerTag].
> +       methodClass = (self fetchPointer: self characterTag ofObject:
> classTableFirstPage) ifTrue:
> +               [^self characterTag].
> +       self assert: methodClass = (self fetchPointer: self smallFloatTag
> ofObject: classTableFirstPage).
> +       ^self smallFloatTag!
>
> Item was removed:
> - ----- Method: Spur64BitCoMemoryManager>>smallIntegerTag (in category
> 'cog jit support') -----
> - smallIntegerTag
> -       <api>
> -       <cmacro>
> -       ^1!
>
> Item was removed:
> - ----- Method: Spur64BitMemoryManager>>smallIntegerTag (in category 'cog
> jit support') -----
> - smallIntegerTag
> -       <cmacro>
> -       ^1!
>
> Item was changed:
>   ----- Method: SpurMemoryManager>>smallIntegerTag (in category 'cog jit
> support') -----
>   smallIntegerTag
> +       <api>
> +       <cmacro>
> +       ^1!
> -       ^self subclassResponsibility!
>
> Item was changed:
>   ----- Method: StackInterpreter>>lookupSelector:inClass: (in category
> 'debug support') -----
>   lookupSelector: selector inClass: class
> +       "Lookup selector in class.  Answer the method or nil.  This is a
> debugging routine.
> +        It does /not/ side-effect lookupClass or newMethod."
> -       "Lookup selector in class.  Answer the method or nil.  This is a
> debugging routine."
>         | currentClass dictionary |
>         <api>
>
>         currentClass := class.
>         [currentClass ~= objectMemory nilObject] whileTrue:
>                 [dictionary := objectMemory followObjField:
> MethodDictionaryIndex ofObject: currentClass.
>                  dictionary = objectMemory nilObject ifTrue:
>                         [^nil].
>                  (self lookupMethodFor: selector InDictionary: dictionary)
> ifNotNil:
>                         [:meth| ^meth].
>                 currentClass := self superclassOf: currentClass].
>         ^nil!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorArithmetic
> (in category 'bytecode generators') -----
>   genSpecialSelectorArithmetic
>         | primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt
> argInt result
>          jumpNotSmallInts jumpContinue index |
>         <var: #jumpContinue type: #'AbstractInstruction *'>
>         <var: #primDescriptor type: #'BytecodeDescriptor *'>
>         <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
>         primDescriptor := self generatorAt: byte0.
>         argIsInt := (argIsConst := self ssTop type = SSConstant)
>                                  and: [objectMemory isIntegerObject:
> (argInt := self ssTop constant)].
> +       rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant)
> +                                 and: [objectMemory isIntegerObject:
> (rcvrInt := (self ssValue: 1) constant)])
> +                               or: [self mclassIsSmallInteger and: [(self
> ssValue: 1) isSameEntryAs: (self addressOf: simSelf)]].
> -       rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
> -                                and: [objectMemory isIntegerObject:
> (rcvrInt := (self ssValue: 1) constant)].
>
> +       (argIsInt and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
> -       (argIsInt and: [rcvrIsInt]) ifTrue:
>                 [rcvrInt := objectMemory integerValueOf: rcvrInt.
>                  argInt := objectMemory integerValueOf: argInt.
>                  primDescriptor opcode caseOf: {
>                         [AddRR] -> [result := rcvrInt + argInt].
>                         [SubRR] -> [result := rcvrInt - argInt].
>                         [AndRR] -> [result := rcvrInt bitAnd: argInt].
>                         [OrRR]  -> [result := rcvrInt bitOr: argInt] }.
>                 (objectMemory isIntegerValue: result) ifTrue:
>                         ["Must annotate the bytecode for correct pc
> mapping."
>                         ^self ssPop: 2; ssPushAnnotatedConstant:
> (objectMemory integerObjectOf: result)].
>                 ^self genSpecialSelectorSend].
>
>         "If there's any constant involved other than a SmallInteger don't
> attempt to inline."
>         ((rcvrIsConst and: [rcvrIsInt not])
>          or: [argIsConst and: [argIsInt not]]) ifTrue:
>                 [^self genSpecialSelectorSend].
>
>         "If we know nothing about the types then better not to inline as
> the inline cache and
>          primitive code is not terribly slow so wasting time on
> duplicating tag tests is pointless."
>         (argIsInt or: [rcvrIsInt]) ifFalse:
>                 [^self genSpecialSelectorSend].
>
>         argIsInt
>                 ifTrue:
>                         [self ssFlushTo: simStackPtr - 2.
>                          (self ssValue: 1) popToReg: ReceiverResultReg.
> +                        self ssPop: 2]
> -                        self ssPop: 2.
> -                        self MoveR: ReceiverResultReg R: TempReg]
>                 ifFalse:
> +                       [self marshallSendArguments: 1].
> +       jumpNotSmallInts := (rcvrIsInt and: [argIsInt]) ifFalse:
> +                                                       [argIsInt
> +                                                               ifTrue:
> [objectRepresentation genJumpNotSmallInteger: ReceiverResultReg]
> +                                                               ifFalse:
> +
>  [rcvrIsInt
> +
>      ifTrue: [objectRepresentation genJumpNotSmallInteger: Arg0Reg]
> +
>      ifFalse: [objectRepresentation genJumpNotSmallIntegersIn:
> ReceiverResultReg and: Arg0Reg scratch: TempReg]]].
> -                       [self marshallSendArguments: 1.
> -                        self MoveR: Arg0Reg R: TempReg].
> -       jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
> -                                                       ifTrue:
> [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
> -                                                       ifFalse:
> [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg
> andScratch: TempReg scratch: ClassReg].
>         primDescriptor opcode caseOf: {
>                 [AddRR] -> [argIsInt
>                                                 ifTrue:
>                                                         [self AddCq:
> argInt - ConstZero R: ReceiverResultReg.
>                                                          jumpContinue :=
> self JumpNoOverflow: 0.
>                                                          "overflow; must
> undo the damage before continuing"
>                                                          self SubCq:
> argInt - ConstZero R: ReceiverResultReg]
>                                                 ifFalse:
>
> [objectRepresentation genRemoveSmallIntegerTagsInScratchReg:
> ReceiverResultReg.
>                                                          self AddR:
> Arg0Reg R: ReceiverResultReg.
>                                                         jumpContinue :=
> self JumpNoOverflow: 0.
>                                                         "overflow; must
> undo the damage before continuing"
> +                                                        (rcvrIsInt and:
> [rcvrIsConst])
> -                                                        rcvrIsInt
>                                                                 ifTrue:
> [self MoveCq: rcvrInt R: ReceiverResultReg]
>                                                                 ifFalse:
>
> [self SubR: Arg0Reg R: ReceiverResultReg.
>
>  objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
>                 [SubRR] -> [argIsInt
>                                                 ifTrue:
>                                                         [self SubCq:
> argInt - ConstZero R: ReceiverResultReg.
>                                                          jumpContinue :=
> self JumpNoOverflow: 0.
>                                                          "overflow; must
> undo the damage before continuing"
>                                                          self AddCq:
> argInt - ConstZero R: ReceiverResultReg]
>                                                 ifFalse:
>
> [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
>                                                          self SubR:
> Arg0Reg R: ReceiverResultReg.
>                                                          jumpContinue :=
> self JumpNoOverflow: 0.
>                                                          "overflow; must
> undo the damage before continuing"
>                                                          self AddR:
> Arg0Reg R: ReceiverResultReg.
>
>  objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
>                 [AndRR] -> [argIsInt
>                                                 ifTrue: [self AndCq:
> argInt R: ReceiverResultReg]
>                                                 ifFalse: [self AndR:
> Arg0Reg R: ReceiverResultReg].
> +                                       jumpContinue := jumpNotSmallInts
> ifNotNil: [self Jump: 0]].
> -                                       jumpContinue := self Jump: 0].
>                 [OrRR]  -> [argIsInt
>                                                 ifTrue: [self OrCq: argInt
> R: ReceiverResultReg]
>                                                 ifFalse: [self OrR:
> Arg0Reg R: ReceiverResultReg].
> +                                       jumpContinue := jumpNotSmallInts
> ifNotNil: [self Jump: 0]] }.
> +       jumpNotSmallInts
> +               ifNil: [jumpContinue ifNil: "overflow cannot happen"
> +                               [self annotateInstructionForBytecode.
> +                                self ssPushRegister: ReceiverResultReg.
> +                                ^0]]
> +               ifNotNil:
> +                       [jumpNotSmallInts jmpTarget: self Label].
> -                                       jumpContinue := self Jump: 0] }.
> -       jumpNotSmallInts jmpTarget: self Label.
>         argIsInt ifTrue:
>                 [self MoveCq: argInt R: Arg0Reg].
>         index := byte0 - self firstSpecialSelectorBytecodeOffset.
>         self genMarshalledSend: index negated - 1 numArgs: 1 sendTable:
> ordinarySendTrampolines.
>         jumpContinue jmpTarget: self Label.
>         ^0!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison
> (in category 'bytecode generators') -----
>   genSpecialSelectorComparison
> +       | nextPC postBranchPC targetPC primDescriptor branchDescriptor
> +         rcvrIsInt rcvrIsConst argIsIntConst argInt jumpNotSmallInts
> inlineCAB index |
> -       | nextPC postBranchPC targetBytecodePC primDescriptor
> branchDescriptor
> -         rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index |
>         <var: #primDescriptor type: #'BytecodeDescriptor *'>
>         <var: #branchDescriptor type: #'BytecodeDescriptor *'>
>         <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
>         self ssFlushTo: simStackPtr - 2.
>         primDescriptor := self generatorAt: byte0.
> +       argIsIntConst := self ssTop type = SSConstant
> -       argIsInt := self ssTop type = SSConstant
>                                  and: [objectMemory isIntegerObject:
> (argInt := self ssTop constant)].
> +       rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant)
> +                                 and: [objectMemory isIntegerObject:
> (self ssValue: 1) constant])
> +                               or: [self mclassIsSmallInteger and: [(self
> ssValue: 1) isSameEntryAs: (self addressOf: simSelf)]].
> -       rcvrIsInt := (self ssValue: 1) type = SSConstant
> -                                and: [objectMemory isIntegerObject: (self
> ssValue: 1) constant].
>
> +       (argIsIntConst and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue:
> -       (argIsInt and: [rcvrIsInt]) ifTrue:
>                 [^ self genStaticallyResolvedSpecialSelectorComparison].
>
>         self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch
> :target |
> +               branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetPC := target ].
> -               branchDescriptor := descr. nextPC := next. postBranchPC :=
> postBranch. targetBytecodePC := target ].
>
>         "Only interested in inlining if followed by a conditional branch."
>         inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor
> isBranchFalse].
>         "Further, only interested in inlining = and ~= if there's a
> SmallInteger constant involved.
>          The relational operators successfully statically predict
> SmallIntegers; the equality operators do not."
>         (inlineCAB and: [primDescriptor opcode = JumpZero or:
> [primDescriptor opcode = JumpNonZero]]) ifTrue:
> +               [inlineCAB := argIsIntConst or: [rcvrIsInt]].
> -               [inlineCAB := argIsInt or: [rcvrIsInt]].
>         inlineCAB ifFalse:
>                 [^self genSpecialSelectorSend].
>
> +       argIsIntConst
> -       argIsInt
>                 ifTrue:
>                         [(self ssValue: 1) popToReg: ReceiverResultReg.
>                          self ssPop: 2]
>                 ifFalse:
> +                       [self marshallSendArguments: 1].
> +       jumpNotSmallInts := (rcvrIsInt and: [argIsIntConst]) ifFalse:
> +                                                       [argIsIntConst
> +                                                               ifTrue:
> [objectRepresentation genJumpNotSmallInteger: ReceiverResultReg]
> +                                                               ifFalse:
> +
>  [rcvrIsInt
> +
>      ifTrue: [objectRepresentation genJumpNotSmallInteger: Arg0Reg]
> +
>      ifFalse: [objectRepresentation genJumpNotSmallIntegersIn:
> ReceiverResultReg and: Arg0Reg scratch: TempReg]]].
> +       argIsIntConst
> -                       [self marshallSendArguments: 1.
> -                        rcvrIsInt ifFalse:
> -                               [self MoveR: Arg0Reg R: TempReg]].
> -       jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
> -                                                       ifFalse: "Neither
> known to be ints; and them together for the test..."
> -
>  [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg
> andScratch: TempReg scratch: ClassReg]
> -                                                       ifTrue: "One
> known; in-place single-bit test for the other"
> -
>  [objectRepresentation genJumpNotSmallInteger: (rcvrIsInt ifTrue: [Arg0Reg]
> ifFalse: [ReceiverResultReg])].
> -       argIsInt
>                 ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
>                 ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
>         "Cmp is weird/backwards so invert the comparison.  Further since
> there is a following conditional
>          jump bytecode define non-merge fixups and leave the cond bytecode
> to set the mergeness."
>         self genConditionalBranch: (branchDescriptor isBranchTrue
>                                 ifTrue: [primDescriptor opcode]
>                                 ifFalse: [self inverseBranchFor:
> primDescriptor opcode])
> +               operand: (self ensureNonMergeFixupAt: targetPC)
> asUnsignedInteger.
> -               operand: (self ensureNonMergeFixupAt: targetBytecodePC)
> asUnsignedInteger.
>         self Jump: (self ensureNonMergeFixupAt: postBranchPC).
> +       jumpNotSmallInts ifNil:
> +               [self annotateInstructionForBytecode.
> +                self ensureFixupAt: postBranchPC.
> +                self ensureFixupAt: targetPC.
> +                deadCode := true.
> +                ^0].
>         jumpNotSmallInts jmpTarget: self Label.
> +       argIsIntConst ifTrue:
> -       argIsInt ifTrue:
>                 [self MoveCq: argInt R: Arg0Reg].
>         index := byte0 - self firstSpecialSelectorBytecodeOffset.
>         ^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable:
> ordinarySendTrampolines!
>
> Item was added:
> + ----- Method: StackToRegisterMappingCogit>>simSelf (in category
> 'accessing') -----
> + simSelf
> +       ^simSelf!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredRegMask:upThrough:upThroughNative:
> (in category 'simulation stack') -----
>   ssAllocateRequiredRegMask: requiredRegsMask upThrough: stackPtr
> upThroughNative: nativeStackPtr
>         | lastRequired lastRequiredNative liveRegs |
>         lastRequired := -1.
>         lastRequiredNative := -1.
>         "compute live regs while noting the last occurrence of required
> regs.
>          If these are not free we must spill from simSpillBase to last
> occurrence.
>          Note we are conservative here; we could allocate FPReg in
> frameless methods."
>         liveRegs := self registerMaskFor: FPReg and: SPReg.
>         (simSpillBase max: 0) to: stackPtr do:
>                 [:i|
>                 liveRegs := liveRegs bitOr: (self simStackAt: i)
> registerMask.
>                 ((self simStackAt: i) registerMask bitAnd:
> requiredRegsMask) ~= 0 ifTrue:
>                         [lastRequired := i]].
> +       LowcodeVM ifTrue:
> +               [(simNativeSpillBase max: 0) to: nativeStackPtr do:
> -       LowcodeVM ifTrue: [
> -               (simNativeSpillBase max: 0) to: nativeStackPtr do:
>                         [:i|
>                         liveRegs := liveRegs bitOr: (self
> simNativeStackAt: i) nativeRegisterMask.
> +                       ((self simNativeStackAt: i) nativeRegisterMask
> anyMask: requiredRegsMask) ifTrue:
> +                               [lastRequiredNative := i]]].
> -                       ((self simNativeStackAt: i) nativeRegisterMask
> bitAnd: requiredRegsMask) ~= 0 ifTrue:
> -                               [lastRequiredNative := i]].
> -       ].
>         "If any of requiredRegsMask are live we must spill."
> +       (liveRegs anyMask: requiredRegsMask) ifTrue:
> +               [self ssFlushTo: lastRequired nativeFlushTo:
> lastRequiredNative.
> -       (liveRegs bitAnd: requiredRegsMask) = 0 ifFalse:
> -               ["Some live, must spill"
> -               self ssFlushTo: lastRequired nativeFlushTo:
> lastRequiredNative.
>                 self assert: (self liveRegisters bitAnd: requiredRegsMask)
> = 0]!
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20170302/11317351/attachment-0001.html>


More information about the Vm-dev mailing list