[Vm-dev] VM Maker: VMMaker.oscog-rsf.2077.mcz

Ronie Salgado roniesalg at gmail.com
Sun Jan 8 22:48:43 UTC 2017


Hello,

This time I applied the suggestion made by Nicolas Cellier for this bug. I
also tested with the Newspeak bootstrapping system and tests in 32 bits
Linux. I got the same number of successful, failing and passing tests as
the CI log available at:
https://travis-ci.org/newspeaklanguage/bootimage-ci/jobs/189887252 .
Hopefully this is not breaking Newspeak again.

However, similar changes are required to EncoderForNewsqueakV4 >>
#extensionsAt:in:into: and EncoderFoSistaV1 >> #extensionsAt:in:into:, for
these methods to correctly decode the extB extensions.

2017-01-08 19:40 GMT-03:00 <commits at source.squeak.org>:

>
> Ronie Salgado Faila uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-rsf.2077.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-rsf.2077
> Author: rsf
> Time: 8 January 2017, 5:41:56.129158 pm
> UUID: d009eb6f-01c9-4fb4-b022-2f73c6e8ca5c
> Ancestors: VMMaker.oscog-eem.2076
>
> ExtB 00000000 1xxxxxxx constant decoding bug fix.
>
> =============== Diff against VMMaker.oscog-eem.2076 ===============
>
> 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
> 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 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 4/6/2015 15:56' 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.  fixup shas one element per byte in methodObj's
> bytecode
>   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>>assertExtsAreConsumed: (in category 'compile
> abstract instructions') -----
>   assertExtsAreConsumed: descriptor
>          "extended bytecodes must consume their extensions"
>          <inline: true>
>          descriptor isExtension ifFalse:
> +               [self assert: (extA = 0 and: [extB = 0 and: [numExtB =
> 0]])].!
> -               [self assert: (extA = 0 and: [extB = 0])].!
>
> Item was changed:
>   ----- Method: Cogit>>extBBytecode (in category 'bytecode generators')
> -----
>   extBBytecode
>         "225            11100001        sbbbbbbb        Extend B (Ext B =
> Ext B prev * 256 + Ext B)"
> +       extB := (numExtB = 0 and: [byte1 > 127])
> -       extB := (extB = 0 and: [byte1 > 127])
>                                 ifTrue: [byte1 - 256]
>                                 ifFalse: [(extB bitShift: 8) + byte1].
> +       numExtB := numExtB + 1.
>         ^0!
>
> Item was changed:
>   ----- Method: Cogit>>nextDescriptorAndExtensionsInto: (in category
> 'bytecode generator support') -----
>   nextDescriptorAndExtensionsInto: aTrinaryBlock
>         "Peek ahead and deliver the next descriptor plus extension bytes."
>         <inline: true>
> +       | savedB0 savedB1 savedB2 savedB3 savedEA savedEB savedNEB
> descriptor bcpc |
> -       | savedB0 savedB1 savedB2 savedB3 savedEA savedEB descriptor bcpc |
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         descriptor := self generatorAt: byte0.
>         savedB0 := byte0. savedB1 := byte1. savedB2 := byte2. savedB3 :=
> byte3.
> +       savedEA := extA. savedEB := extB. savedNEB := numExtB.
> -       savedEA := extA. savedEB := extB.
>         bcpc := bytecodePC + descriptor numBytes.
>         [bcpc > endPC ifTrue:
>                 [^aTrinaryBlock value: nil value: 0 value: 0].
>          byte0 := (objectMemory fetchByte: bcpc ofObject: methodObj)  +
> bytecodeSetOffset.
>          descriptor := self generatorAt: byte0.
>          self loadSubsequentBytesForDescriptor: descriptor at: bcpc.
>          descriptor isExtension ifFalse:
>                 [| eA eB |
>                  eA := extA. eB := extB.
> +                extA := savedEA. extB := savedEB. numExtB := savedNEB.
> -                extA := savedEA. extB := savedEB.
>                  byte0 := savedB0. byte1 := savedB1. byte2 := savedB2.
> byte3 := savedB3.
>                  ^aTrinaryBlock value: descriptor value: eA value: eB].
>          self perform: descriptor generator.
>          bcpc := bcpc + descriptor numBytes.
>          true] whileTrue!
>
> Item was changed:
>   ----- Method: Cogit>>scanBlock: (in category 'compile abstract
> instructions') -----
>   scanBlock: blockStart
>         "Scan the block to determine if the block needs a frame or not"
>         | descriptor pc end framelessStackDelta nExts |
>         <var: #blockStart type: #'BlockStart *'>
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         needsFrame := false.
>         methodOrBlockNumArgs := blockStart numArgs.
>         inBlock := InVanillaBlock.
>         pc := blockStart startpc.
>         end := blockStart startpc + blockStart span.
> +       framelessStackDelta := nExts := extA := numExtB := extB := 0.
> -       framelessStackDelta := nExts := extA := extB := 0.
>         [pc < end] whileTrue:
>                 [byte0 := (objectMemory fetchByte: pc ofObject: methodObj)
> + bytecodeSetOffset.
>                  descriptor := self generatorAt: byte0.
>                  descriptor isExtension ifTrue:
>                         [self loadSubsequentBytesForDescriptor:
> descriptor at: pc.
>                          self perform: descriptor generator].
>                  needsFrame ifFalse:
>                         [(descriptor needsFrameFunction isNil
>                           or: [self perform: descriptor needsFrameFunction
> with: framelessStackDelta])
>                                 ifTrue: [needsFrame := true]
>                                 ifFalse: [framelessStackDelta :=
> framelessStackDelta + descriptor stackDelta]].
>                  objectRepresentation maybeNoteDescriptor: descriptor
> blockStart: blockStart.
>                  pc := self nextBytecodePCFor: descriptor at: pc exts:
> nExts in: methodObj.
>                  descriptor isExtension
>                         ifTrue: [nExts := nExts + 1]
> +                       ifFalse: [nExts := extA := numExtB := 0. extB :=
> 0]].
> -                       ifFalse: [nExts := extA := extB := 0]].
>         needsFrame ifFalse:
>                 [framelessStackDelta < 0 ifTrue:
>                         [self error: 'negative stack delta in block; block
> contains bogus code or internal error'].
>                  [framelessStackDelta > 0] whileTrue:
>                         [descriptor := self generatorAt: (objectMemory
> fetchByte: blockStart startpc ofObject: methodObj) + bytecodeSetOffset.
>                          descriptor generator ~~
> #genPushConstantNilBytecode ifTrue:
>                                 [self error: 'frameless block doesn''t
> start with enough pushNils'].
>                          blockStart
>                                 startpc: blockStart startpc + descriptor
> numBytes;
>                                 span: blockStart span - descriptor
> numBytes.
>                          framelessStackDelta := framelessStackDelta - 1]].
>         ^0!
>
> Item was changed:
>   ----- Method: Cogit>>scanMethod (in category 'compile abstract
> instructions') -----
>   scanMethod
>         "Scan the method (and all embedded blocks) to determine
>                 - what the last bytecode is; extra bytes at the end of a
> method are used to encode things like source pointers or temp names
>                 - if the method needs a frame or not
>                 - what are the targets of any backward branches.
>                 - how many blocks it creates
>                 - if it contans an unknown bytecode
>          Answer the block count or on error a negative error code"
>         | latestContinuation nExts descriptor pc numBlocks distance
> targetPC framelessStackDelta |
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         needsFrame := false.
>         NewspeakVM ifTrue:
>                 [numIRCs := 0].
>         (primitiveIndex > 0
>          and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex])
> ifTrue:
>                 [^0].
>         pc := latestContinuation := initialPC.
> +       numBlocks := framelessStackDelta := nExts := extA := numExtB :=
> extB := 0.
> -       numBlocks := framelessStackDelta := nExts := extA := extB := 0.
>         [pc <= endPC] whileTrue:
>                 [byte0 := (objectMemory fetchByte: pc ofObject: methodObj)
> + bytecodeSetOffset.
>                  descriptor := self generatorAt: byte0.
>                  descriptor isExtension ifTrue:
>                         [descriptor opcode = Nop ifTrue: "unknown bytecode
> tag; see Cogit class>>#generatorTableFrom:"
>                                 [^EncounteredUnknownBytecode].
>                          self loadSubsequentBytesForDescriptor:
> descriptor at: pc.
>                          self perform: descriptor generator].
>                  (descriptor isReturn
>                   and: [pc >= latestContinuation]) ifTrue:
>                         [endPC := pc].
>                  needsFrame ifFalse:
>                         [(descriptor needsFrameFunction isNil
>                           or: [self perform: descriptor needsFrameFunction
> with: framelessStackDelta])
>                                 ifTrue: [needsFrame := true]
>                                 ifFalse: [framelessStackDelta :=
> framelessStackDelta + descriptor stackDelta]].
>                  descriptor isBranch ifTrue:
>                         [distance := self spanFor: descriptor at: pc exts:
> nExts in: methodObj.
>                          targetPC := pc + descriptor numBytes + distance.
>                          (self isBackwardBranch: descriptor at: pc exts:
> nExts in: methodObj)
>                                 ifTrue: [self initializeFixupAt: targetPC
> - initialPC]
>                                 ifFalse: [latestContinuation :=
> latestContinuation max: targetPC]].
>                  descriptor isBlockCreation ifTrue:
>                         [numBlocks := numBlocks + 1.
>                          distance := self spanFor: descriptor at: pc exts:
> nExts in: methodObj.
>                          targetPC := pc + descriptor numBytes + distance.
>                          latestContinuation := latestContinuation max:
> targetPC].
>                  NewspeakVM ifTrue:
>                         [descriptor hasIRC ifTrue:
>                                 [numIRCs := numIRCs + 1]].
>                  pc := pc + descriptor numBytes.
>                  descriptor isExtension
>                         ifTrue: [nExts := nExts + 1]
> +                       ifFalse: [nExts := extA := numExtB := extB := 0]].
> -                       ifFalse: [nExts := extA := extB := 0]].
>         ^numBlocks!
>
> Item was changed:
>   ----- Method: Cogit>>setInterpreter: (in category 'initialization') -----
>   setInterpreter: aCoInterpreter
>         "Initialization of the code generator in the simulator.
>          These objects already exist in the generated C VM
>          or are used only in the simulation."
>         <doNotGenerate>
>         coInterpreter := aCoInterpreter.
>         objectMemory := aCoInterpreter objectMemory.
>         threadManager := aCoInterpreter threadManager. "N.B. may be nil"
>         methodZone := CogMethodZone new.
>         objectRepresentation := objectMemory objectRepresentationClass
>                                                                 forCogit:
> self methodZone: methodZone.
>         methodZone setInterpreter: aCoInterpreter
>                                 objectRepresentation: objectRepresentation
>                                 cogit: self.
>         generatorTable := self class generatorTable.
>         processor := ProcessorClass new.
>         simulatedAddresses := Dictionary new.
>         simulatedTrampolines := Dictionary new.
>         simulatedVariableGetters := Dictionary new.
>         simulatedVariableSetters := Dictionary new.
>         traceStores := 0.
>         traceFlags := (self class initializationOptions at:
> #recordPrimTrace ifAbsent: [true])
>                                         ifTrue: [8] "record prim trace on
> by default (see Cogit class>>decareCVarsIn:)"
>                                         ifFalse: [0].
>         debugPrimCallStackOffset := 0.
>         singleStep := printRegisters := printInstructions := clickConfirm
> := false.
>         backEnd := CogCompilerClass for: self.
>         methodLabel := CogCompilerClass for: self.
>         (literalsManager := backEnd class literalsManagerClass new) cogit:
> self.
>         ordinarySendTrampolines := CArrayAccessor on: (Array new:
> NumSendTrampolines).
>         superSendTrampolines := CArrayAccessor on: (Array new:
> NumSendTrampolines).
>         BytecodeSetHasDirectedSuperSend ifTrue:
>                 [directedSuperSendTrampolines := CArrayAccessor on: (Array
> new: NumSendTrampolines)].
>         NewspeakVM ifTrue:
>                 [selfSendTrampolines := CArrayAccessor on: (Array new:
> NumSendTrampolines).
>                 dynamicSuperSendTrampolines := CArrayAccessor on: (Array
> new: NumSendTrampolines).
>                 implicitReceiverSendTrampolines := CArrayAccessor on:
> (Array new: NumSendTrampolines).
>                 outerSendTrampolines := CArrayAccessor on: (Array new:
> NumSendTrampolines)].
>         "debug metadata"
>         objectReferencesInRuntime := CArrayAccessor on: (Array new:
> NumObjRefsInRuntime).
>         runtimeObjectRefIndex := 0.
>         "debug metadata"
>         trampolineAddresses := CArrayAccessor on: (Array new:
> NumTrampolines * 2).
>         trampolineTableIndex := 0.
>
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>
>         compilationTrace ifNil: [compilationTrace := self class
> initializationOptions at: #compilationTrace ifAbsent: [0]].
>         debugOpcodeIndices := self class initializationOptions at:
> #debugOpcodeIndices ifAbsent: [Set new].
>         debugBytecodePointers := self class initializationOptions at:
> #debugBytecodePointers ifAbsent: [Set new]!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtJumpIfFalse (in category
> 'bytecode generators') -----
>   genExtJumpIfFalse
>         "244            11110100        i i i i i i i i Pop and Jump 0n
> False i i i i i i i i (+ Extend B * 256, where Extend B >= 0)"
>         | distance target |
>         distance := byte1 + (extB << 8).
>         self assert: distance = (self v4: (self generatorAt: byte0)
>
> LongForward: bytecodePC
>                                                                 Branch:
> (extA ~= 0 ifTrue: [1] ifFalse: [0]) + (extB ~= 0 ifTrue: [1] ifFalse: [0])
>                                                                 Distance:
> methodObj).
>         extB := 0.
> +       numExtB := 0.
>         target := distance + 2 + bytecodePC.
>         ^self genJumpIf: objectMemory falseObject to: target!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtJumpIfTrue (in category
> 'bytecode generators') -----
>   genExtJumpIfTrue
>         "243            11110011        i i i i i i i i Pop and Jump 0n
> True i i i i i i i i (+ Extend B * 256, where Extend B >= 0)"
>         | distance target |
>         distance := byte1 + (extB << 8).
>         self assert: distance = (self v4: (self generatorAt: byte0)
>
> LongForward: bytecodePC
>                                                                 Branch:
> (extA ~= 0 ifTrue: [1] ifFalse: [0]) + (extB ~= 0 ifTrue: [1] ifFalse: [0])
>                                                                 Distance:
> methodObj).
>         extB := 0.
> +       numExtB := 0.
>         target := distance + 2 + bytecodePC.
>         ^self genJumpIf: objectMemory trueObject to: target!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtNopBytecode (in category
> 'bytecode generators') -----
>   genExtNopBytecode
>         "NewspeakV4: 221                11011101                Nop"
>         "SistaV1:                91             01011011'
>  Nop"
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>         ^0!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtPushCharacterBytecode (in
> category 'bytecode generators') -----
>   genExtPushCharacterBytecode
>         "SistaV1:               233             11101001        iiiiiiii
>               Push Character #iiiiiiii (+ Extend B * 256)"
>         | value |
>         value := byte1 + (extB << 8).
>         extB := 0.
> +       numExtB := 0.
>         ^self genPushLiteral: (objectMemory characterObjectOf: value)!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtPushClosureBytecode (in
> category 'bytecode generators') -----
>   genExtPushClosureBytecode
>         "Block compilation.  At this point in the method create the
> block.  Note its start
>          and defer generating code for it until after the method and any
> other preceding
>          blocks.  The block's actual code will be compiled later."
>         "253            11111101 eei i i kkk    jjjjjjjj
> Push Closure Num Copied iii (+ Ext A // 16 * 8) Num Args kkk (+ Ext A \\ 16
> * 8) BlockSize jjjjjjjj (+ Ext B * 256). ee = num extensions"
>         | numArgs numCopied |
>         self assert: needsFrame.
>         self addBlockStartAt: bytecodePC + 3 "0 relative"
>                 numArgs: (numArgs := (byte1 bitAnd: 16r7) + (extA \\ 16 *
> 8))
>                 numCopied: (numCopied := ((byte1 >> 3) bitAnd: 7) + (extA
> // 16 * 8))
>                 span: byte2 + (extB << 8).
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>         objectRepresentation
>                 genCreateClosureAt: bytecodePC + 4 "1 relative"
>                 numArgs: numArgs
>                 numCopied: numCopied
>                 contextNumArgs: methodOrBlockNumArgs
>                 large: (coInterpreter methodNeedsLargeContext: methodObj)
>                 inBlock: inBlock.
>         self PushR: ReceiverResultReg.
>         ^0!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtPushIntegerBytecode (in
> category 'bytecode generators') -----
>   genExtPushIntegerBytecode
>         "NewsqueakV4:   229             11100101        iiiiiiii
> Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g.
> -32768 = i=0, a=0, s=1)
>         SistaV1:                232             11101000        iiiiiiii
>       Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd,
> e.g. -32768 = i=0, a=0, s=1)"
>         | value |
>         value := byte1 + (extB << 8).
>         extB := 0.
> +       numExtB := 0.
>         ^self genPushLiteral: (objectMemory integerObjectOf: value)!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtPushPseudoVariable (in
> category 'bytecode generators') -----
>   genExtPushPseudoVariable
>         "SistaV1: *     82                      01010010
>       Push thisContext, (then Extend B = 1 => push thisProcess)"
>         | ext |
>         ext := extB.
>         extB := 0.
> +       numExtB := 0.
>         ext caseOf: {
>                 [0]     ->      [^self genPushActiveContextBytecode].
>                 }
>                 otherwise:
>                         [^self unknownBytecode].
>         ^0!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtPushPseudoVariableOrOuterBytecode
> (in category 'bytecode generators') -----
>   genExtPushPseudoVariableOrOuterBytecode
>         "77                     01001101                Push false [*
> 1:true, 2:nil, 3:thisContext, ..., -N: pushEnclosingObjectAt: N, N = Extend
> B]"
>         | ext |
>         ext := extB.
>         extB := 0.
> +       numExtB := 0.
>         ext caseOf: {
>                 [0]     ->      [^self genPushLiteral: objectMemory
> falseObject].
>                 [1]     ->      [^self genPushLiteral: objectMemory
> trueObject].
>                 [2]     ->      [^self genPushLiteral: objectMemory
> nilObject].
>                 [3]     ->      [^self genPushActiveContextBytecode]
>                 }
>                 otherwise:
>                         [ext < 0 ifTrue:
>                                 [^self genPushEnclosingObjectAt: 0 - ext].
>                          self warning: 'undefined extension for
> extPushPseudoVariableOrOuter'.
>                          ^self unknownBytecode].
>         ^0!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtPushRemoteTempOrInstVarLongBytecode
> (in category 'bytecode generators') -----
>   genExtPushRemoteTempOrInstVarLongBytecode
>         | index |
>         ^ (byte2 noMask: coInterpreter remoteIsInstVarAccess)
>                 ifTrue: [ self genPushRemoteTempLongBytecode ]
>                 ifFalse:
>                         [ index := byte1 + (extA << 8).
>                         extA := 0.
>                         extB := 0. "don't use flags in the simple cogit"
> +                       numExtB := 0.
>                         (coInterpreter isReadMediatedContextInstVarIndex:
> index)
>                                 ifTrue: [self
>
> genPushMaybeContextRemoteInstVar: index
>                                                         inObjectAt: byte2
> - coInterpreter remoteIsInstVarAccess]
>                                 ifFalse: [self
>
> genPushRemoteInstVar: index
>                                                         inObjectAt: byte2
> - coInterpreter remoteIsInstVarAccess]]!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtSendAbsentDynamicSuperBytecode
> (in category 'bytecode generators') -----
>   genExtSendAbsentDynamicSuperBytecode
>         "241            11110001        i i i i i j j j Send To Absent
> Dynamic Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+
> Extend B * 8) Arguments"
>         | litIndex nArgs |
>         litIndex := (byte1 >> 3) + (extA << 5).
>         extA := 0.
>         nArgs := (byte1 bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         ^self genSendAbsentDynamicSuper: litIndex numArgs: nArgs!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtSendAbsentImplicitBytecode
> (in category 'bytecode generators') -----
>   genExtSendAbsentImplicitBytecode
>         "240            11110000        i i i i i j j j Send To Absent
> Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+
> Extend B * 8) Arguments"
>         | litIndex nArgs |
>         litIndex := (byte1 >> 3) + (extA << 5).
>         extA := 0.
>         nArgs := (byte1 bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         ^self genSendAbsentImplicit: litIndex numArgs: nArgs!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtSendAbsentOuterBytecode (in
> category 'bytecode generators') -----
>   genExtSendAbsentOuterBytecode
>         "254             11111110       i i i i i j j j kkkkkkkk
> Send To Absent Outer Literal Selector #iiiii (+ Extend A * 32) with jjj (+
> Extend B * 8) Arguments at Depth kkkkkkkk "
>         | litIndex nArgs depth |
>         litIndex := (byte1 >> 3) + (extA << 5).
>         extA := 0.
>         nArgs := (byte1 bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         depth := byte2.
>         ^self genSendAbsentOuter: litIndex numArgs: nArgs depth: depth
>   !
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtSendAbsentSelfBytecode (in
> category 'bytecode generators') -----
>   genExtSendAbsentSelfBytecode
>         "245            11110101        i i i i i j j j Send To Absent
> Self Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8)
> Arguments"
>         | litIndex nArgs |
>         litIndex := (byte1 >> 3) + (extA << 5).
>         extA := 0.
>         nArgs := (byte1 bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         ^self genSendAbsentSelf: litIndex numArgs: nArgs!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtSendBytecode (in category
> 'bytecode generators') -----
>   genExtSendBytecode
>         "238            11101110        i i i i i j j j Send Literal
> Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
>         | litIndex nArgs |
>         litIndex := (byte1 >> 3) + (extA << 5).
>         extA := 0.
>         nArgs := (byte1 bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         ^self genSend: litIndex numArgs: nArgs!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtSendSuperBytecode (in
> category 'bytecode generators') -----
>   genExtSendSuperBytecode
>         "239            11101111        i i i i i j j j Send To Superclass
> Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8)
> Arguments"
>         | isDirected litIndex nArgs |
>         (isDirected := extB >= 64) ifTrue:
>                 [extB := extB bitAnd: 63].
>         litIndex := (byte1 >> 3) + (extA << 5).
>         extA := 0.
>         nArgs := (byte1 bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         ^isDirected
>                 ifTrue: [self genSendDirectedSuper: litIndex numArgs:
> nArgs]
>                 ifFalse: [self genSendSuper: litIndex numArgs: nArgs]!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean:
> (in category 'bytecode generators') -----
>   genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: popBoolean
>         | index |
>         extB := 0. "simple cogit don't use the extra flag"
> +       numExtB := 0.
>         (byte2 noMask: coInterpreter remoteIsInstVarAccess)
>                 ifTrue:
>                         [ self genStorePop: popBoolean RemoteTemp: byte1
> At: byte2.
>                         self cppIf: IMMUTABILITY ifTrue: [ self
> annotateBytecode: self Label ] ]
>                 ifFalse:
>                         [ index := byte1 + (extA << 8).
>                         extA := 0.
>                         (coInterpreter isWriteMediatedContextInstVarIndex:
> index)
>                                 ifTrue: [ self
>                                                 genStorePop: popBoolean
>                                                 MaybeContextRemoteInstVar:
> index
>                                                 ofObjectAt: byte2 -
> coInterpreter remoteIsInstVarAccess ]
>                                 ifFalse: [ self
>                                                 genStorePop: popBoolean
>                                                 RemoteInstVar: index
>                                                 ofObjectAt: byte2 -
> coInterpreter remoteIsInstVarAccess  ] ].
>         ^ 0!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genExtUnconditionalJump (in
> category 'bytecode generators') -----
>   genExtUnconditionalJump
>         "242            11110010        i i i i i i i i Jump i i i i i i i
> i (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0,
> s=1)"
>         | distance target |
>         distance := byte1 + (extB << 8).
>         self assert: distance = (self v4: (self generatorAt: byte0)
>                                                                 Long:
> bytecodePC
>                                                                 Branch:
> (extA ~= 0 ifTrue: [1] ifFalse: [0]) + (extB ~= 0 ifTrue: [1] ifFalse: [0])
>                                                                 Distance:
> methodObj).
>         extB := 0.
> +       numExtB := 0.
>         target := distance + 2 + bytecodePC.
>         distance < 0 ifTrue:
>                 [^self genJumpBackTo: target].
>         self genJumpTo: target.
>         "The bytecode must be mapped since it can be either forward or
> backward, and
>           backwards branches must be mapped. So if forward, we need to
> map."
>         self annotateBytecode: self lastOpcode.
>         ^0!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean:
> (in category 'bytecode generators') -----
>   genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean: boolean
>         | index |
>         extB := 0. "Simple cogit don't use the extra flags"
> +       numExtB := 0.
>         index := byte1 + (extA << 8).
>         extA := 0.
>         ^(coInterpreter isWriteMediatedContextInstVarIndex: index)
>                 ifTrue: [self genStorePop: boolean
> MaybeContextReceiverVariable: index ]
>                 ifFalse: [self genStorePop: boolean ReceiverVariable:
> index ]!
>
> Item was changed:
>   ----- Method: SimpleStackBasedCogit>>genSistaExtStoreLiteralVariableBytecodePopBoolean:
> (in category 'bytecode generators') -----
>   genSistaExtStoreLiteralVariableBytecodePopBoolean: boolean
>         | index |
>         extB := 0. "SimpleCogit don't use the extra flags"
> +       numExtB := 0.
>         index := byte1 + (extA << 8).
>         extA := 0.
>         ^ self genStorePop: boolean LiteralVariable: index!
>
> Item was changed:
>   ----- Method: SistaCogit>>genExtJumpIfNotInstanceOfBehaviorsBytecode
> (in category 'bytecode generators') -----
>   genExtJumpIfNotInstanceOfBehaviorsBytecode
>         "SistaV1: *     254             11111110        kkkkkkkk
> jjjjjjjj                branch If Not Instance Of Behavior/Array Of
> Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj
> (+ Extend B * 256, where Extend B >= 0)"
>
>         | reg literal distance targetFixUp inverse |
>
>         "We loose the information of in which register is stack top
>         when jitting the branch target so we need to flush everything.
>         We could use a fixed register here...."
>         reg := self allocateRegForStackEntryAt: 0.
>         self ssTop popToReg: reg.
>         self ssFlushTo: simStackPtr. "flushed but the value is still in
> reg"
>
>         self genPopStackBytecode.
>
>         literal := self getLiteral: (extA * 256 + byte1).
>         extA := 0.
>         extB < 0
>                 ifTrue: [extB := extB + 128. inverse := true]
>                 ifFalse: [inverse := false].
>         distance := extB * 256 + byte2.
>         extB := 0.
> +       numExtB := 0.
>
>         targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC
> + 3 + distance - initialPC) to: #'AbstractInstruction *'.
>         inverse
>                 ifFalse:
>                         [(objectMemory isArrayNonImm: literal)
>                                 ifTrue: [objectRepresentation branchIf:
> reg notInstanceOfBehaviors: literal target: targetFixUp]
>                                 ifFalse: [objectRepresentation branchIf:
> reg notInstanceOfBehavior: literal target: targetFixUp] ]
>                 ifTrue:
>                         [(objectMemory isArrayNonImm: literal)
>                                 ifTrue: [objectRepresentation branchIf:
> reg instanceOfBehaviors: literal target: targetFixUp]
>                                 ifFalse: [objectRepresentation branchIf:
> reg instanceOfBehavior: literal target: targetFixUp]].
>
>
>
>         ^0!
>
> Item was changed:
>   ----- Method: SistaCogit>>genUnaryInlinePrimitive: (in category 'inline
> primitive generators') -----
>   genUnaryInlinePrimitive: prim
>         "Unary inline primitives."
>         "SistaV1: 248           11111000        iiiiiiii
> mjjjjjjj                Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1
> means inlined primitive, no hard return after execution.
>          See EncoderForSistaV1's class comment and StackInterpreter>>#
> unaryInlinePrimitive:"
>         | rcvrReg resultReg |
>         rcvrReg := self allocateRegForStackEntryAt: 0.
>         resultReg := self allocateRegNotConflictingWith: (self
> registerMaskFor: rcvrReg).
>         prim
>                 caseOf: {
>                                         "00             unchecked class"
>                         [1] ->  "01             unchecked pointer numSlots"
>                                 [self ssTop popToReg: rcvrReg.
>                                  self ssPop: 1.
>                                  objectRepresentation
>                                         genGetNumSlotsOf: rcvrReg into:
> resultReg;
>                                         genConvertIntegerToSmallIntegerInReg:
> resultReg].
>                                         "02             unchecked pointer
> basicSize"
>                         [3] ->  "03             unchecked byte numBytes"
>                                 [self ssTop popToReg: rcvrReg.
>                                  self ssPop: 1.
>                                  objectRepresentation
>                                         genGetNumBytesOf: rcvrReg into:
> resultReg;
>                                         genConvertIntegerToSmallIntegerInReg:
> resultReg].
>                                         "04             unchecked
> short16Type format numShorts"
>                                         "05             unchecked
> word32Type format numWords"
>                                         "06             unchecked
> doubleWord64Type format numDoubleWords"
>                         [11] -> "11             unchecked fixed pointer
> basicNew"
>                                 [self ssTop type ~= SSConstant ifTrue:
>                                         [^EncounteredUnknownBytecode].
>                                  (objectRepresentation
>                                         genGetInstanceOf: self ssTop
> constant
>                                                 into: resultReg
>                                                         initializingIf:
> self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
>                                         [^ShouldNotJIT]. "e.g. bad class"
>                                  self ssPop: 1] .
>                         [20] -> "20     identityHash"
>                                 [self ssTop popToReg: rcvrReg.
>                                  objectRepresentation
> genGetHashFieldNonImmOf: rcvrReg asSmallIntegerInto: resultReg.
>                                  self ssPop: 1]
>                                         "21             identityHash
> (SmallInteger)"
>                                         "22             identityHash
> (Character)"
>                                         "23             identityHash
> (SmallFloat64)"
>                                         "24             identityHash
> (Behavior)"
>                                   }
>                 otherwise:
>                         [^EncounteredUnknownBytecode].
>         extB := 0.
> +       numExtB := 0.
>         self ssPushRegister: resultReg.
>         ^0!
>
> Item was changed:
>   ----- Method: SistaCogitClone>>genExtJumpIfNotInstanceOfBehaviorsBytecode
> (in category 'bytecode generators') -----
>   genExtJumpIfNotInstanceOfBehaviorsBytecode
>         "SistaV1: *     254             11111110        kkkkkkkk
> jjjjjjjj                branch If Not Instance Of Behavior/Array Of
> Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj
> (+ Extend B * 256, where Extend B >= 0)"
>
>         | reg literal distance targetFixUp inverse |
>
>         "We loose the information of in which register is stack top
>         when jitting the branch target so we need to flush everything.
>         We could use a fixed register here...."
>         reg := self allocateRegForStackEntryAt: 0.
>         self ssTop popToReg: reg.
>         self ssFlushTo: simStackPtr. "flushed but the value is still in
> reg"
>
>         self genPopStackBytecode.
>
>         literal := self getLiteral: (extA * 256 + byte1).
>         extA := 0.
>         extB < 0
>                 ifTrue: [extB := extB + 128. inverse := true]
>                 ifFalse: [inverse := false].
>         distance := extB * 256 + byte2.
>         extB := 0.
> +       numExtB := 0.
>
>         targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC
> + 3 + distance - initialPC) to: #'AbstractInstruction *'.
>         inverse
>                 ifFalse:
>                         [(objectMemory isArrayNonImm: literal)
>                                 ifTrue: [objectRepresentation branchIf:
> reg notInstanceOfBehaviors: literal target: targetFixUp]
>                                 ifFalse: [objectRepresentation branchIf:
> reg notInstanceOfBehavior: literal target: targetFixUp] ]
>                 ifTrue:
>                         [(objectMemory isArrayNonImm: literal)
>                                 ifTrue: [objectRepresentation branchIf:
> reg instanceOfBehaviors: literal target: targetFixUp]
>                                 ifFalse: [objectRepresentation branchIf:
> reg instanceOfBehavior: literal target: targetFixUp]].
>
>
>
>         ^0!
>
> Item was changed:
>   ----- Method: SistaCogitClone>>genUnaryInlinePrimitive: (in category
> 'inline primitive generators') -----
>   genUnaryInlinePrimitive: prim
>         "Unary inline primitives."
>         "SistaV1: 248           11111000        iiiiiiii
> mjjjjjjj                Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1
> means inlined primitive, no hard return after execution.
>          See EncoderForSistaV1's class comment and StackInterpreter>>#
> unaryInlinePrimitive:"
>         | rcvrReg resultReg |
>         rcvrReg := self allocateRegForStackEntryAt: 0.
>         resultReg := self allocateRegNotConflictingWith: (self
> registerMaskFor: rcvrReg).
>         prim
>                 caseOf: {
>                                         "00             unchecked class"
>                         [1] ->  "01             unchecked pointer numSlots"
>                                 [self ssTop popToReg: rcvrReg.
>                                  self ssPop: 1.
>                                  objectRepresentation
>                                         genGetNumSlotsOf: rcvrReg into:
> resultReg;
>                                         genConvertIntegerToSmallIntegerInReg:
> resultReg].
>                                         "02             unchecked pointer
> basicSize"
>                         [3] ->  "03             unchecked byte numBytes"
>                                 [self ssTop popToReg: rcvrReg.
>                                  self ssPop: 1.
>                                  objectRepresentation
>                                         genGetNumBytesOf: rcvrReg into:
> resultReg;
>                                         genConvertIntegerToSmallIntegerInReg:
> resultReg].
>                                         "04             unchecked
> short16Type format numShorts"
>                                         "05             unchecked
> word32Type format numWords"
>                                         "06             unchecked
> doubleWord64Type format numDoubleWords"
>                         [11] -> "11             unchecked fixed pointer
> basicNew"
>                                 [self ssTop type ~= SSConstant ifTrue:
>                                         [^EncounteredUnknownBytecode].
>                                  (objectRepresentation
>                                         genGetInstanceOf: self ssTop
> constant
>                                                 into: resultReg
>                                                         initializingIf:
> self extBSpecifiesInitializeInstance) ~= 0 ifTrue:
>                                         [^ShouldNotJIT]. "e.g. bad class"
>                                  self ssPop: 1]
>                                   }
>                 otherwise:
>                         [^EncounteredUnknownBytecode].
>         extB := 0.
> +       numExtB := 0.
>         self ssPushRegister: resultReg.
>         ^0!
>
> Item was changed:
>   InterpreterPrimitives subclass: #StackInterpreter
> +       instanceVariableNames: 'currentBytecode bytecodeSetSelector
> localFP localIP localSP stackLimit stackPage stackPages method
> instructionPointer stackPointer framePointer localReturnValue
> localAbsentReceiver localAbsentReceiverOrZero extA extB numExtB
> primitiveFunctionPointer methodCache nsMethodCache atCache lkupClassTag
> lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority
> nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode
> interruptPending savedWindowSize imageHeaderFlags fullScreenFlag
> deferDisplayUpdates pendingFinalizationSignals extraVMMemory
> interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable
> externalPrimitiveTable externalPrimitiveTableFirstFreeIndex
> overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth
> suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages
> desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots
> interruptCheckChain suppressHeartbeatFlag breakSelector breakSelector
>  Length longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore
> longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
> longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber
> longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2
> tempOop3 theUnknownShort the2ndUnknownShort imageFloatsBigEndian
> maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex
> classByteArrayCompactIndex checkedPluginName statForceInterruptCheck
> statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch
> statIOProcessEvents statPendingFinalizationSignals nativeSP
> nativeStackPointer lowcodeCalloutState shadowCallStackPointer'
> -       instanceVariableNames: 'currentBytecode bytecodeSetSelector
> localFP localIP localSP stackLimit stackPage stackPages method
> instructionPointer stackPointer framePointer localReturnValue
> localAbsentReceiver localAbsentReceiverOrZero extA extB
> primitiveFunctionPointer methodCache nsMethodCache atCache lkupClassTag
> lkupClass methodDictLinearSearchLimit highestRunnableProcessPriority
> nextWakeupUsecs nextPollUsecs inIOProcessEvents interruptKeycode
> interruptPending savedWindowSize imageHeaderFlags fullScreenFlag
> deferDisplayUpdates pendingFinalizationSignals extraVMMemory
> interpreterProxy showSurfaceFn primitiveTable primitiveAccessorDepthTable
> externalPrimitiveTable externalPrimitiveTableFirstFreeIndex
> overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth
> suspendedCallbacks suspendedMethods numStackPages desiredNumStackPages
> desiredEdenBytes classNameIndex thisClassIndex metaclassNumSlots
> interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength
> l
>  ongRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore
> longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs
> longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber
> longRunningPrimitiveSignalUndelivered checkAllocFiller tempOop tempOop2
> tempOop3 theUnknownShort the2ndUnknownShort imageFloatsBigEndian
> maxExtSemTabSizeSet lastMethodCacheProbeWrite gcSemaphoreIndex
> classByteArrayCompactIndex checkedPluginName statForceInterruptCheck
> statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch
> statIOProcessEvents statPendingFinalizationSignals nativeSP
> nativeStackPointer lowcodeCalloutState shadowCallStackPointer'
>         classVariableNames: 'AccessModifierPrivate AccessModifierProtected
> AccessModifierPublic AltBytecodeEncoderClassName AltLongStoreBytecode
> AlternateHeaderHasPrimFlag AlternateHeaderIsOptimizedFlag
> AlternateHeaderNumLiteralsMask AtCacheFixedFields AtCacheFmt AtCacheMask
> AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeEncoderClassName
> BytecodeTable CacheProbeMax DirBadPath DirEntryFound DirNoMoreEntries
> DumpStackOnLowSpace EnclosingMixinIndex EnclosingObjectIndex
> EnforceAccessControl FailImbalancedPrimitives LongStoreBytecode
> MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex
> MaxQuickPrimitiveIndex MethodHeaderArgCountShift
> MethodHeaderFlagBitPosition MethodHeaderTempCountShift MixinIndex
> PrimNumberDoExternalCall PrimNumberExternalCall PrimNumberFFICall
> PrimitiveExternalCallIndex PrimitiveTable StackPageReachedButUntraced
> StackPageTraceInvalid StackPageTraced StackPageUnreached
> V3PrimitiveBitsMask'
>         poolDictionaries: 'VMBasicConstants VMBytecodeConstants
> VMMethodCacheConstants VMObjectIndices VMSpurObjectRepresentationConstants
> VMSqueakClassIndices VMStackFrameOffsets'
>         category: 'VMMaker-Interpreter'!
>
>   !StackInterpreter commentStamp: 'eem 12/5/2014 11:32' prior: 0!
>   This class is a complete implementation of the Smalltalk-80 virtual
> machine, derived originally from the Blue Book specification but quite
> different in some areas.  This VM supports Closures but *not* old-style
> BlockContexts.
>
>   It has been modernized with 32-bit pointers, better management of
> Contexts (see next item), and attention to variable use that allows the
> CCodeGenerator (qv) to keep, eg, the instruction pointer and stack pointer
> in registers as well as keeping most simple variables in a global array
> that seems to improve performance for most platforms.
>
>   The VM does not use Contexts directly.  Instead Contexts serve as
> proxies for a more conventional stack format that is invisible to the
> image.  There is considerable explanation at http://www.mirandabanda.org/
> cogblog/2009/01/14/under-cover-contexts-and-the-big-frame-up.  The VM
> maintains a fixed-size stack zone divided into pages, each page being
> capable of holding several method/block activations.  A send establishes a
> new frame in the current stack page, a return returns to the previous
> frame.  This eliminates allocation/deallocation of contexts and the moving
> of receiver and arguments from caller to callee on each send/return.
> Contexts are created lazily when an activation needs a context (creating a
> block, explicit use of thisContext, access to sender when sender is a
> frame, or linking of stack pages together).  Contexts are either
> conventional and heap-resident ("single") or "married" and serve as proxies
> for their corresponding frame or "widowed", meaning that their spouse f
>  rame has been returned from (died).  A married context is specially
> marked (more details in the code) and refers to its frame.  Likewise a
> married frame is specially marked and refers to its context.
>
>   In addition to SmallInteger arithmetic and Floats, the VM supports logic
> on 32-bit PositiveLargeIntegers, thus allowing it to simulate itself much
> more effectively than would otherwise be the case.
>
>   StackInterpreter and subclasses support multiple memory managers.
> Currently there are two.  NewMemoryManager is a slightly refined version of
> ObjectMemory, and is the memory manager and garbage collector for the
> original Squeak object representation as described in "Back to the Future
> The Story of Squeak, A Practical Smalltalk Written in Itself", see
> http://ftp.squeak.org/docs/OOPSLA.Squeak.html.  Spur is a faster, more
> regular object representation that is designed for more performance and
> functionality, and to have a common header format for both 32-bit and
> 64-bit versions.  You can read about it in SpurMemoryManager's class
> comment.  There is also a video of a presentation at ESUG 2014 (
> https://www.youtube.com/watch?v=k0nBNS1aHZ4), along with slides (
> http://www.slideshare.net/esug/spur-a-new-object-representation-for-cog?
> related=1).!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extBBytecode (in category 'miscellaneous
> bytecodes') -----
>   extBBytecode
>         "225            11100001        sbbbbbbb        Extend B (Ext B =
> Ext B prev * 256 + Ext B)"
>         | byte |
>         byte := self fetchByte.
>         self fetchNextBytecode.
> +       extB := (numExtB = 0 and: [byte > 127])
> -       extB := (extB = 0 and: [byte > 127])
>                                 ifTrue: [byte - 256]
> +                               ifFalse: [(extB bitShift: 8) + byte].
> +       numExtB := numExtB + 1!
> -                               ifFalse: [(extB bitShift: 8) + byte]!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extJumpIfFalse (in category 'jump
> bytecodes') -----
>   extJumpIfFalse
>         "244            11110100        i i i i i i i i Pop and Jump 0n
> False i i i i i i i i (+ Extend B * 256, where Extend B >= 0)"
>         | byte offset |
>         byte := self fetchByte.
>         offset := byte + (extB << 8).
> +       numExtB := extB := extA := 0.
> -       extB := extA := 0.
>         self jumplfFalseBy: offset!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extJumpIfNotInstanceOfBehaviorsBytecode
> (in category 'sista bytecodes') -----
>   extJumpIfNotInstanceOfBehaviorsBytecode
>         "254            11111110        kkkkkkkk        jjjjjjjj
>       branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+
> Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256,
> where Extend B >= 0)"
>         | tosClassTag literal distance inverse |
>         SistaVM ifFalse: [^self respondToUnknownBytecode].
>         extB < 0
>                 ifTrue: [extB := extB + 128. inverse := true]
>                 ifFalse: [inverse := false].
>         tosClassTag := objectMemory fetchClassTagOf: self internalPopStack.
>         literal := self literal: extA << 8 + self fetchByte.
>         distance := extB << 8 + self fetchByte.
>         extA := 0.
>         extB := 0.
> +       numExtB := 0.
>         (objectMemory isArrayNonImm: literal)
>                 ifTrue:
>                         [0 to: (objectMemory numSlotsOf: literal)
> asInteger - 1 do: [:i |
>                                 tosClassTag = (objectMemory
> rawClassTagForClass: (objectMemory fetchPointer: i ofObject: literal))
>                                         ifTrue: [
>                                                 inverse ifTrue: [ localIP
> := localIP + distance ].
>                                                 ^ self fetchNextBytecode ]
> ].
>                          inverse ifFalse: [localIP := localIP + distance].
>                          ^ self fetchNextBytecode]
>                 ifFalse:
>                         [tosClassTag ~= (objectMemory rawClassTagForClass:
> literal) ifTrue:
>                                 [inverse ifFalse: [localIP := localIP +
> distance].
>                                 ^ self fetchNextBytecode]].
>         inverse ifTrue: [localIP := localIP + distance].
>         self fetchNextBytecode!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extJumpIfTrue (in category 'jump
> bytecodes') -----
>   extJumpIfTrue
>         "243            11110011        i i i i i i i i Pop and Jump 0n
> True i i i i i i i i (+ Extend B * 256, where Extend B >= 0)"
>         | byte offset |
>         byte := self fetchByte.
>         offset := byte + (extB << 8).
> +       numExtB := extB := extA := 0.
> -       extB := extA := 0.
>         self jumplfTrueBy: offset!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extNopBytecode (in category
> 'miscellaneous bytecodes') -----
>   extNopBytecode
>         "SistaV1                94              01011111
> Nop"
>         "NewspeakV4: 221                11011101                Nop"
>         self fetchNextBytecode.
> +       numExtB := extA := extB := 0!
> -       extA := extB := 0!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extPushCharacterBytecode (in category
> 'stack bytecodes') -----
>   extPushCharacterBytecode
>         "SistaV1:       *       233             11101001        iiiiiiii
>               Push Character #iiiiiiii (+ Extend B * 256)"
>         | value |
>         value := self fetchByte + (extB << 8).
>         self fetchNextBytecode.
>         self internalPush: (objectMemory characterObjectOf: value).
> +       numExtB := extB := 0!
> -       extB := 0!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extPushClosureBytecode (in category
> 'stack bytecodes') -----
>   extPushClosureBytecode
>         "253            11111101 eei i i kkk    jjjjjjjj
> Push Closure Num Copied iii (+ Ext A // 16 * 8) Num Args kkk (+ Ext A \\ 16
> * 8) BlockSize jjjjjjjj (+ Ext B * 256). ee = num extensions.
>          The compiler has pushed the values to be copied, if any.  Find
> numArgs and numCopied in the byte following.
>          Create a Closure with space for the copiedValues and pop
> numCopied values off the stack into the closure.
>          Set numArgs as specified, and set startpc to the pc following the
> block size and jump over that code."
>         | byte numArgs numCopied blockSize |
>         byte := self fetchByte.
>         numArgs := (byte bitAnd: 7) + (extA \\ 16 * 8).
>         numCopied := ((byte >> 3) bitAnd: 7) + (extA // 16 * 8).
>         extA := 0.
>         blockSize := self fetchByte + (extB << 8).
> +       numExtB := extB := 0.
> -       extB := 0.
>         self pushClosureNumArgs: numArgs copiedValues: numCopied
> blockSize: blockSize!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extPushIntegerBytecode (in category
> 'stack bytecodes') -----
>   extPushIntegerBytecode
>         "229            11100101        i i i i i i i i Push Integer
> #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0,
> a=0, s=1)"
>         | value |
>         value := self fetchByte + (extB << 8).
>         self fetchNextBytecode.
>         extB := 0.
> +       numExtB := 0.
>         self internalPush: (objectMemory integerObjectOf: value)!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extPushPseudoVariable (in category
> 'stack bytecodes') -----
>   extPushPseudoVariable
>         "SistaV1:       *       82                      01010010
>               Push thisContext, (then e.g. Extend B 1 = push thisProcess)"
>         | theThingToPush |
>         extB
>                 caseOf: {
>                         [0]     ->      [theThingToPush := self
> ensureFrameIsMarried: localFP SP: localSP].
>                         [1]     ->      [theThingToPush := self
> activeProcess] }
>                 otherwise:
>                         [self respondToUnknownBytecode].
>         self fetchNextBytecode.
>         self internalPush: theThingToPush.
> +       extB := 0.
> +       numExtB := 0.!
> -       extB := 0!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extPushPseudoVariableOrOuterBytecode
> (in category 'stack bytecodes') -----
>   extPushPseudoVariableOrOuterBytecode
>         "77                     01001101                Push false [*
> 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
>         | thing |
>         self fetchNextBytecode.
>         thing := extB
>                                 caseOf: {
>                                         [0]     ->      [^self
> internalPush: objectMemory falseObject].
>                                         [1]     ->      [objectMemory
> trueObject].
>                                         [2]     ->      [objectMemory
> nilObject].
>                                         [3]     ->      [| context |
>                                                          context := self
> ensureFrameIsMarried: localFP SP: localSP.
>                                                          context]
>                                 }
>                                 otherwise:
>                                         [extB < 0
>                                                 ifTrue:
>                                                         [self
>
> enclosingObjectAt: 0 - extB
>
> withObject: self receiver
>                                                                 withMixin:
> (self methodClassOf: method)]
>                                                 ifFalse:
>                                                         [self error:
> 'undefined extension for extPushPseudoVariableOrOuter'.
>                                                          objectMemory
> nilObject]].
>         extB := 0.
> +       numExtB := 0.
>         self internalPush: thing!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extPushRemoteTempOrInstVarLongBytecode
> (in category 'stack bytecodes') -----
>   extPushRemoteTempOrInstVarLongBytecode
>         | slotIndex tempIndex object |
>         slotIndex := self fetchByte.
>         tempIndex := self fetchByte.
>         self fetchNextBytecode.
>         (tempIndex noMask: self remoteIsInstVarAccess)
>                 ifTrue: [self pushRemoteTemp: slotIndex inVectorAt:
> tempIndex]
>                 ifFalse:
>                         [ slotIndex := slotIndex + (extA << 8).
>                         tempIndex := tempIndex - self
> remoteIsInstVarAccess.
> +                       numExtB := extA := extB := 0.
> -                       extA := extB := 0.
>                         object := self temporary: tempIndex in: localFP.
>                         self pushMaybeContext: object receiverVariable:
> slotIndex ]!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSendAbsentDynamicSuperBytecode (in
> category 'send bytecodes') -----
>   extSendAbsentDynamicSuperBytecode
>         "241            11110001        i i i i i j j j Send To Dynamic
> Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B *
> 8) Arguments"
>         | byte |
>         byte := self fetchByte.
>         messageSelector := self literal: (byte >> 3) + (extA << 5).
>         extA := 0.
>         argumentCount := (byte bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         self commonSendDynamicSuper!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSendAbsentImplicitBytecode (in
> category 'send bytecodes') -----
>   extSendAbsentImplicitBytecode
>         "240            11110000        i i i i i j j j Send To Absent
> Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+
> Extend B * 8) Arguments"
>         | byte |
>         byte := self fetchByte.
>         messageSelector := self literal: (byte >> 3) + (extA << 5).
>         extA := 0.
>         argumentCount := (byte bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         self commonSendImplicitReceiver.!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSendAbsentOuterBytecode (in category
> 'send bytecodes') -----
>   extSendAbsentOuterBytecode
>         "254              11111110      i i i i i j j j kkkkkkkk Send To
> Enclosing Object at Depth kkkkkkkk Literal Selector #iiiii (+ Extend A *
> 32) with jjj (+ Extend B * 8) Arguments"
>         | byte depth |
>         byte := self fetchByte.
>         messageSelector := self literal: (byte >> 3) + (extA << 5).
>         extA := 0.
>         argumentCount := (byte bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         depth := self fetchByte.
>         self commonSendOuter: depth!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSendAbsentSelfBytecode (in category
> 'send bytecodes') -----
>   extSendAbsentSelfBytecode
>         "245             11110101       i i i i i j j j Send To Self
> Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8)
> Arguments"
>         | byte |
>         byte := self fetchByte.
>         messageSelector := self literal: (byte >> 3) + (extA << 5).
>         extA := 0.
>         argumentCount := (byte bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         self commonSendOuter: 0!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSendBytecode (in category 'send
> bytecodes') -----
>   extSendBytecode
>         "238            11101110        i i i i i j j j Send Literal
> Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
>         | byte rcvr |
>         byte := self fetchByte.
>         messageSelector := self literal: (byte >> 3) + (extA << 5).
>         extA := 0.
>         argumentCount := (byte bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         rcvr := self internalStackValue: argumentCount.
>         lkupClassTag := objectMemory fetchClassTagOf: rcvr.
>         self commonSendOrdinary!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSendSuperBytecode (in category 'send
> bytecodes') -----
>   extSendSuperBytecode
>         "239            11101111        i i i i i j j j
>                 ExtendB < 64
>                         ifTrue: [Send To Superclass Literal Selector
> #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments]
>                         ifFalse: [Send To Superclass of Stacked Class
> Literal Selector #iiiii (+ Extend A * 32) with jjj (+ (Extend B bitAnd: 63)
> * 8) Arguments]"
>         | byte |
>         byte := self fetchByte.
>         messageSelector := self literal: (byte >> 3) + (extA << 5).
>         extA := 0.
>         BytecodeSetHasDirectedSuperSend ifTrue:
>                 [extB >= 64 ifTrue:
>                         [argumentCount := (byte bitAnd: 7) + (extB - 64 <<
> 3).
>                          extB := 0.
>                          ^self directedSuperclassSend]].
>         argumentCount := (byte bitAnd: 7) + (extB << 3).
>         extB := 0.
> +       numExtB := 0.
>         self superclassSend!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSistaStoreAndPopLiteralVariableBytecode
> (in category 'stack bytecodes') -----
>   extSistaStoreAndPopLiteralVariableBytecode
>         "236            11101100        i i i i i i i i Pop and Store
> Literal Variable #iiiiiiii (+ Extend A * 256)
>         (3) ExtB lowest bit implies no store check is needed, ExtB next
> bit implies the object may be a context, other bits in the extension are
> unused."
>         | variableIndex value |
>         variableIndex := self fetchByte + (extA << 8).
>         value := self internalStackTop.
>         self internalPop: 1.
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0..
>         self storeLiteralVariable: variableIndex withValue: value.
>         self fetchNextBytecode.!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSistaStoreAndPopReceiverVariableBytecode
> (in category 'stack bytecodes') -----
>   extSistaStoreAndPopReceiverVariableBytecode
>         "235            11101011        i i i i i i i i Pop and Store
> Receiver Variable #iiiiiii (+ Extend A * 256)
>         (3) ExtB lowest bit implies no store check is needed, ExtB next
> bit implies the object may be a context, other bits in the extension are
> unused."
>         | variableIndex value |
>         variableIndex := self fetchByte + (extA << 8).
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>         value := self internalStackTop.
>         self internalPop: 1.
>         self storeMaybeContextReceiverVariable: variableIndex withValue:
> value.
>         self fetchNextBytecode.!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSistaStoreLiteralVariableBytecode
> (in category 'stack bytecodes') -----
>   extSistaStoreLiteralVariableBytecode
>         "233            11101001        i i i i i i i i Store Literal
> Variable #iiiiiiii (+ Extend A * 256)
>         (3) ExtB lowest bit implies no store check is needed, ExtB next
> bit implies the object may be a context, other bits in the extension are
> unused."
>         | variableIndex |
>         variableIndex := self fetchByte + (extA << 8).
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>         self storeLiteralVariable: variableIndex withValue: self
> internalStackTop.
>         self fetchNextBytecode.!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extSistaStoreReceiverVariableBytecode
> (in category 'stack bytecodes') -----
>   extSistaStoreReceiverVariableBytecode
>         "232            11101000        i i i i i i i i Store Receiver
> Variable #iiiiiii (+ Extend A * 256)
>         (3) ExtB lowest bit implies no store check is needed, ExtB next
> bit implies the object may be a context, other bits in the extension are
> unused."
>         | variableIndex |
>         variableIndex := self fetchByte + (extA << 8).
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>         self storeMaybeContextReceiverVariable: variableIndex withValue:
> self internalStackTop.
>         self fetchNextBytecode.!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extStoreRemoteTempOrInstVarLongBytecode
> (in category 'stack bytecodes') -----
>   extStoreRemoteTempOrInstVarLongBytecode
>         <inline: true>
>         | slotIndex tempIndex object |
>         slotIndex := self fetchByte.
>         tempIndex := self fetchByte.
>         self fetchNextBytecode.
>         (tempIndex noMask: self remoteIsInstVarAccess)
>                 ifTrue: [self storeRemoteTemp: slotIndex inVectorAt:
> tempIndex]
>                 ifFalse:
>                         [ slotIndex := slotIndex + (extA << 8).
>                         tempIndex := tempIndex - self
> remoteIsInstVarAccess.
> +                       extA := numExtB := extB := 0.
> -                       extA := extB := 0.
>                         object := self temporary: tempIndex in: localFP.
>                         self storeMaybeContext: object receiverVariable:
> slotIndex withValue: self internalStackTop ]!
>
> Item was changed:
>   ----- Method: StackInterpreter>>extUnconditionalJump (in category 'jump
> bytecodes') -----
>   extUnconditionalJump
>         "242            11110010        i i i i i i i i Jump i i i i i i i
> i (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0,
> s=1)"
>         | byte offset |
>         byte := self fetchByte.
>         offset := byte + (extB << 8).
>         extB := 0.
> +       numExtB := 0.
>         localIP := localIP + offset.
>         self ifBackwardsCheckForEvents: offset.
>         self fetchNextBytecode!
>
> Item was changed:
>   ----- Method: StackInterpreter>>initExtensions (in category 'simulation
> support') -----
>   initExtensions
>         <inline: true>
> +       BytecodeSetHasExtensions ifTrue: [extA := numExtB := extB := 0]!
> -       BytecodeSetHasExtensions ifTrue: [extA := extB := 0]!
>
> Item was changed:
>   ----- Method: StackInterpreter>>lowcodePrimitivePerformCallStructure
> (in category 'inline primitive generated code') -----
>   lowcodePrimitivePerformCallStructure
>         <option: #LowcodeVM>    "Lowcode instruction generator"
>         | resultPointer result function structureSize |
>         <var: #resultPointer type: #'char*' >
>         <var: #result type: #'char*' >
>         function := extA.
>         structureSize := extB.
>         result := self internalPopStackPointer.
>
>         self internalPushShadowCallStackPointer: result.
>         resultPointer := self lowcodeCalloutPointerResult: (self cCoerce:
> function to: #'char*').
>
>         self internalPushPointer: resultPointer.
>         extA := 0.
>         extB := 0.
> +       numExtB := 0.
> -
>   !
>
> Item was changed:
>   ----- Method: StackInterpreter>>lowcodePrimitivePointerAddConstantOffset
> (in category 'inline primitive generated code') -----
>   lowcodePrimitivePointerAddConstantOffset
>         <option: #LowcodeVM>    "Lowcode instruction generator"
>         | base offset result |
>         <var: #base type: #'char*' >
>         <var: #result type: #'char*' >
>         offset := extB.
>         base := self internalPopStackPointer.
>
>         result := base + offset.
>
>         self internalPushPointer: result.
>         extB := 0.
> +       numExtB := 0.
>
>   !
>
> Item was changed:
>   ----- Method: StackInterpreter>>unaryInlinePrimitive: (in category
> 'miscellaneous bytecodes') -----
>   unaryInlinePrimitive: primIndex
>         "SistaV1:       248             11111000        iiiiiiii
>       mjjjjjjj                Call Primitive #iiiiiiii + (jjjjjjj * 256)
> m=1 means inlined primitive, no hard return after execution."
>         <option: #SistaVM>
>         | result |
>         primIndex caseOf: {
>                 "1000   unchecked class"
>                 [0]     ->      [result := objectMemory fetchClassOf: self
> internalStackTop.
>                                  self internalStackTopPut: result].
>                 "1001   unchecked pointer numSlots"
>                 [1]     ->      [result := objectMemory numSlotsOf: self
> internalStackTop.
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)].
>                 "1002   unchecked pointer basicSize"
>                 [2]     ->      [result := (objectMemory numSlotsOf: self
> internalStackTop)
>                                                 - (objectMemory
> fixedFieldsOfClass: (objectMemory fetchClassOfNonImm: self
> internalStackTop)).
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)].
>                 "1003   unchecked byte8Type format numBytes (includes
> CompiledMethod)"
>                 [3]     ->      [result := objectMemory numBytesOf: self
> internalStackTop.
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)].
>                 "1004   unchecked short16Type format numShorts"
>                 [4]     ->      [result := objectMemory num16BitUnitsOf:
> self internalStackTop.
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)].
>                 "1005   unchecked word32Type format numWords"
>                 [5]     ->      [result := objectMemory num32BitUnitsOf:
> self internalStackTop.
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)].
>                 "1006   unchecked doubleWord64Type format numDoubleWords"
>                 [6]     ->      [result := objectMemory num64BitUnitsOf:
> self internalStackTop.
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)].
>
>                 "1011   unchecked fixed pointer basicNew"
>                 [11] -> [| classObj numSlots |
>                                  classObj := self internalStackTop.
>                                  numSlots := objectMemory instanceSizeOf:
> classObj.
>                                  result := objectMemory
> eeInstantiateSmallClass: classObj numSlots: numSlots.
>                                  (extB noMask: 1) ifTrue:
>                                         [0 to: numSlots - 1 do:
>                                                 [:i| objectMemory
> storePointerUnchecked: i ofObject: result withValue: objectMemory
> nilObject]].
>                                  extB := 0.
> +                               numExtB := 0.
>                                  self internalStackTopPut: result].
>                 "1020   identityHash"
>                 [20] -> [result := objectMemory hashBitsOf: self
> internalStackTop.
>                                  self internalStackTopPut: (objectMemory
> integerObjectOf: result)]
>                 "1021           identityHash (SmallInteger)"
>                 "1022           identityHash (Character)"
>                 "1023           identityHash (SmallFloat64)"
>                 "1024           identityHash (Behavior)"
>                  }
>         otherwise:
>                 [localIP := localIP - 3.
>                  self respondToUnknownBytecode]!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode
> generators') -----
>   genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode
>         "SistaV1: *     254             11111110        kkkkkkkk
> jjjjjjjj                branch If Not Instance Of Behavior/Array Of
> Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj
> (+ Extend B * 256, where Extend B >= 0)"
>
>         | reg literal distance targetFixUp |
>
>         "We loose the information of in which register is stack top
>         when jitting the branch target so we need to flush everything.
>         We could use a fixed register here...."
>         reg := self allocateRegForStackEntryAt: 0.
>         self ssTop popToReg: reg.
>         self ssFlushTo: simStackPtr. "flushed but the value is still in
> reg"
>
>         literal := self getLiteral: (extA * 256 + byte1).
>         extA := 0.
>         distance := extB * 256 + byte2.
>         extB := 0.
> +       numExtB := 0.
>
>         targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC
> + 3 + distance - initialPC) to: #'AbstractInstruction *'.
>
>         (objectMemory isArrayNonImm: literal)
>                 ifTrue: [objectRepresentation branchIf: reg
> notInstanceOfBehaviors: literal target: targetFixUp]
>                 ifFalse: [objectRepresentation branchIf: reg
> notInstanceOfBehavior: literal target: targetFixUp].
>
>         self genPopStackBytecode.
>
>         ^0!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>genExtPushClosureBytecode
> (in category 'bytecode generators') -----
>   genExtPushClosureBytecode
>         "Block compilation.  At this point in the method create the
> block.  Note its start
>          and defer generating code for it until after the method and any
> other preceding
>          blocks.  The block's actual code will be compiled later."
>         "253            11111101 eei i i kkk    jjjjjjjj
> Push Closure Num Copied iii (+ Ext A // 16 * 8) Num Args kkk (+ Ext A \\ 16
> * 8) BlockSize jjjjjjjj (+ Ext B * 256). ee = num extensions"
>         | startpc numArgs numCopied |
>         self assert: needsFrame.
>         startpc := bytecodePC + (self generatorAt: byte0) numBytes.
>         self addBlockStartAt: startpc "0 relative"
>                 numArgs: (numArgs := (byte1 bitAnd: 16r7) + (extA \\ 16 *
> 8))
>                 numCopied: (numCopied := ((byte1 >> 3) bitAnd: 7) + (extA
> // 16 * 8))
>                 span: byte2 + (extB << 8).
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>
>         objectRepresentation createsClosuresInline
>                 ifTrue: [ self genInlineClosure: startpc numArgs: numArgs
> numCopied: numCopied ]
>                 ifFalse: [ self genOutlineClosure: startpc numArgs:
> numArgs numCopied: numCopied ].
>
>         ^ 0!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> genExtPushRemoteTempOrInstVarLongBytecode (in category 'bytecode
> generators') -----
>   genExtPushRemoteTempOrInstVarLongBytecode
>         | index maybeContext |
>         ^ (byte2 noMask: coInterpreter remoteIsInstVarAccess)
>                 ifTrue: [ self genPushRemoteTempLongBytecode ]
>                 ifFalse:
>                         [ maybeContext := self extBSpecifiesMaybeContext.
>                         index := byte1 + (extA << 8).
>                         extA := 0.
>                         extB := 0.
> +                       numExtB := 0.
>                         ((coInterpreter isReadMediatedContextInstVarIndex:
> index) and: [ maybeContext ])
>                                 ifTrue: [ self
> genPushMaybeContextRemoteInstVar: index inObjectAt: byte2 - coInterpreter
> remoteIsInstVarAccess ]
>                                 ifFalse: [ self genPushRemoteInstVar:
> index inObjectAt: byte2 - coInterpreter remoteIsInstVarAccess ] ]!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: (in category
> 'bytecode generators') -----
>   genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: boolean
>         | index maybeContext needsStoreCheck needsImmCheck |
>         needsStoreCheck := self sistaNeedsStoreCheck.
>         maybeContext := self extBSpecifiesMaybeContext.
>         needsImmCheck := self extBSpecifiesImmCheck.
>         extB := 0.
> +       numExtB := 0.
>         (byte2 noMask: coInterpreter remoteIsInstVarAccess)
>                 ifTrue:
>                         [ self
>                                 genStorePop: boolean
>                                 RemoteTemp: byte1
>                                 At: byte2
>                                 needsStoreCheck: needsStoreCheck.
>                         self cppIf: IMMUTABILITY ifTrue: [ self
> annotateBytecode: self Label ] ]
>                 ifFalse:
>                         [index := byte1 + (extA << 8).
>                          extA := 0.
>                          ((coInterpreter isWriteMediatedContextInstVarIndex:
> index) and: [ maybeContext ])
>                                 ifTrue: [self
>                                                 genStorePop: boolean
>                                                 MaybeContextRemoteInstVar:
> index
>                                                 ofObjectAt: byte2 -
> coInterpreter remoteIsInstVarAccess
>                                                 needsStoreCheck:
> needsStoreCheck
>                                                 needsImmutabilityCheck:
> needsImmCheck ]
>                                 ifFalse: [self
>                                                 genStorePop: boolean
>                                                 RemoteInstVar: index
>                                                 ofObjectAt: byte2 -
> coInterpreter remoteIsInstVarAccess
>                                                 needsStoreCheck:
> needsStoreCheck
>                                                 needsImmutabilityCheck:
> needsImmCheck ] ].
>         ^ 0!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>genLowcodePerformCallStructure
> (in category 'inline primitive generators generated code') -----
>   genLowcodePerformCallStructure
>         <option: #LowcodeVM>    "Lowcode instruction generator"
>
>         "Push the result space"
>         self ssNativeTop nativeStackPopToReg: TempReg.
>         self ssNativePop: 1.
>         self PushR: TempReg.
>         "Call the function"
>         self callSwitchToCStack.
>         self MoveCw: extA R: TempReg.
>         self CallRT: ceFFICalloutTrampoline.
>         "Fetch the result"
>         self MoveR: backEnd cResultRegister R: ReceiverResultReg.
>         self ssPushNativeRegister: ReceiverResultReg.
>         extA := 0.
>         extB := 0.
> +       numExtB := 0.
>
>         ^ 0
>
>   !
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> genLowcodePointerAddConstantOffset (in category 'inline primitive
> generators generated code') -----
>   genLowcodePointerAddConstantOffset
>         <option: #LowcodeVM>    "Lowcode instruction generator"
>         | base offset |
>         offset := extB.
>
>         (base := backEnd availableRegisterOrNoneFor: self liveRegisters) =
> NoReg ifTrue:
>                 [self ssAllocateRequiredReg:
>                         (base := optStatus isReceiverResultRegLive
>                                 ifTrue: [Arg0Reg]
>                                 ifFalse: [ReceiverResultReg])].
>         base = ReceiverResultReg ifTrue:
>                 [ optStatus isReceiverResultRegLive: false ].
>         self ssNativeTop nativePopToReg: base.
>         self ssNativePop: 1.
>
>         self AddCq: offset R: base.
>         self ssPushNativeRegister: base.
>
>         extB := 0.
> +       numExtB := 0.
>         ^ 0
>
>   !
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean: (in category
> 'bytecode generators') -----
>   genSistaExtStoreAndPopReceiverVariableBytecodePopBoolean: popBoolean
>         <inline: true>
>         | index needsStoreCheck needsImmCheck maybeContext |
>         needsStoreCheck := self sistaNeedsStoreCheck.
>         needsImmCheck := self extBSpecifiesImmCheck.
>         "Long form and short form exist for popInto. Only the long form
> exists for store.
>         Store have an explicit flag to mark context accessing, while
> popInto context accessing are done through the long form,
>         hence generate the context form if the flag is set or if this is a
> popInto."
>         maybeContext := popBoolean or: [self extBSpecifiesMaybeContext].
>         extB := 0.
> +       numExtB := 0.
>         index := byte1 + (extA << 8).
>         extA := 0.
>         ^((coInterpreter isWriteMediatedContextInstVarIndex: index) and:
> [maybeContext])
>                 ifTrue: [self
>                                 genStorePop: popBoolean
>                                 MaybeContextReceiverVariable: index
>                                 needsStoreCheck: needsStoreCheck
>                                 needsImmutabilityCheck: needsImmCheck]
>                 ifFalse: [self
>                                  genStorePop: popBoolean
>                                  ReceiverVariable: index
>                                  needsStoreCheck: needsStoreCheck
>                                  needsImmutabilityCheck: needsImmCheck]!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> genSistaExtStoreLiteralVariableBytecodePopBoolean: (in category 'bytecode
> generators') -----
>   genSistaExtStoreLiteralVariableBytecodePopBoolean: boolean
>         <inline: true>
>         | index needsStoreCheck needsImmCheck |
>         needsStoreCheck := self sistaNeedsStoreCheck.
>         needsImmCheck := self extBSpecifiesImmCheck.
>         index := byte1 + (extA << 8).
> +       extA := numExtB := extB := 0.
> -       extA := extB := 0.
>         ^self
>                 genStorePop: boolean
>                 LiteralVariable: index
>                 needsStoreCheck: needsStoreCheck
>                 needsImmutabilityCheck: needsImmCheck!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>scanBlock: (in category
> 'compile abstract instructions') -----
>   scanBlock: blockStart
>         "Scan the block to determine if the block needs a frame or not"
>         | descriptor pc end framelessStackDelta nExts pushingNils
> numPushNils |
>         <var: #blockStart type: #'BlockStart *'>
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         needsFrame := false.
>         LowcodeVM ifTrue: [ hasNativeFrame := false ].
>         prevBCDescriptor := nil.
>         methodOrBlockNumArgs := blockStart numArgs.
>         inBlock := InVanillaBlock.
>         pc := blockStart startpc.
>         end := blockStart startpc + blockStart span.
> +       framelessStackDelta := nExts := extA := numExtB := extB := 0.
> -       framelessStackDelta := nExts := extA := extB := 0.
>         pushingNils := true.
>         [pc < end] whileTrue:
>                 [byte0 := (objectMemory fetchByte: pc ofObject: methodObj)
> + bytecodeSetOffset.
>                  descriptor := self generatorAt: byte0.
>                  descriptor isExtension ifTrue:
>                         [self loadSubsequentBytesForDescriptor:
> descriptor at: pc.
>                          self perform: descriptor generator].
>                  needsFrame ifFalse:
>                         [(descriptor needsFrameFunction isNil
>                           or: [self perform: descriptor needsFrameFunction
> with: framelessStackDelta])
>                                 ifTrue: [needsFrame := true]
>                                 ifFalse: [framelessStackDelta :=
> framelessStackDelta + descriptor stackDelta]].
>                  objectRepresentation maybeNoteDescriptor: descriptor
> blockStart: blockStart.
>                  (pushingNils
>                   and: [descriptor isExtension not]) ifTrue:
>                         ["Count the initial number of pushed nils acting
> as temp initializers.  We can't tell
>                           whether an initial pushNil is an operand
> reference or a temp initializer, except
>                           when the pushNil is a jump target (has a fixup),
> which never happens:
>                                         self systemNavigation
> browseAllSelect:
>                                                 [:m| | ebc |
>                                                 (ebc := m
> embeddedBlockClosures
>
> select: [:ea| ea decompile statements first isMessage]
>
> thenCollect: [:ea| ea decompile statements first selector]) notEmpty
>                                                 and: [(#(whileTrue
> whileFalse whileTrue: whileFalse:) intersection: ebc) notEmpty]]
>                           or if the bytecode set has a push multiple nils
> bytecode.  We simply count initial nils.
>                           Rarely we may end up over-estimating.  We will
> correct by checking the stack depth
>                           at the end of the block in compileBlockBodies."
>                          (numPushNils := self numPushNils: descriptor pc:
> pc nExts: nExts method: methodObj) > 0
>                                 ifTrue:
>                                         [self assert: (descriptor numBytes
> = 1
>
> or: [descriptor generator == #genPushClosureTempsBytecode]).
>                                          blockStart numInitialNils:
> blockStart numInitialNils + numPushNils]
>                                 ifFalse:
>                                         [pushingNils := false]].
>                  pc := self nextBytecodePCFor: descriptor at: pc exts:
> nExts in: methodObj.
>                  descriptor isExtension
>                         ifTrue: [nExts := nExts + 1]
> +                       ifFalse: [nExts := extA := numExtB := extB := 0].
> -                       ifFalse: [nExts := extA := extB := 0].
>                  prevBCDescriptor := descriptor].
>         "It would be nice of this wasn't necessary but alas we need to do
> the eager
>          scan for frameless methods so that we don't end up popping too
> much off
>          the simulated stack, e.g. for pushNil; returnTopFromBlock
> methods."
>         needsFrame ifFalse:
>                 [self assert: (framelessStackDelta >= 0 and: [blockStart
> numInitialNils >= framelessStackDelta]).
>                  blockStart numInitialNils: blockStart numInitialNils -
> framelessStackDelta].
>         ^0!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>scanMethod (in category
> 'compile abstract instructions') -----
>   scanMethod
>         "Scan the method (and all embedded blocks) to determine
>                 - what the last bytecode is; extra bytes at the end of a
> method are used to encode things like source pointers or temp names
>                 - if the method needs a frame or not
>                 - what are the targets of any backward branches.
>                 - how many blocks it creates
>          Answer the block count or on error a negative error code"
>         | latestContinuation nExts descriptor pc numBlocks distance
> targetPC framelessStackDelta seenInstVarStore |
>         <var: #descriptor type: #'BytecodeDescriptor *'>
>         needsFrame := useTwoPaths := seenInstVarStore := false.
>         LowcodeVM ifTrue: [ hasNativeFrame := false ].
>         self maybeInitNumFixups.
>         self maybeInitNumCounters.
>         prevBCDescriptor := nil.
>         NewspeakVM ifTrue:
>                 [numIRCs := 0].
>         (primitiveIndex > 0
>          and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex])
> ifTrue:
>                 [^0].
>         pc := latestContinuation := initialPC.
> +       numBlocks := framelessStackDelta := nExts := extA := numExtB :=
> extB := 0.
> -       numBlocks := framelessStackDelta := nExts := extA := extB := 0.
>         [pc <= endPC] whileTrue:
>                 [byte0 := (objectMemory fetchByte: pc ofObject: methodObj)
> + bytecodeSetOffset.
>                  descriptor := self generatorAt: byte0.
>                  descriptor isExtension ifTrue:
>                         [descriptor opcode = Nop ifTrue: "unknown bytecode
> tag; see Cogit class>>#generatorTableFrom:"
>                                 [^EncounteredUnknownBytecode].
>                          self loadSubsequentBytesForDescriptor:
> descriptor at: pc.
>                          self perform: descriptor generator].
>                  (descriptor isReturn
>                   and: [pc >= latestContinuation]) ifTrue:
>                         [endPC := pc].
>
>                   needsFrame ifFalse:
>                         [(descriptor needsFrameFunction isNil
>                           or: [self perform: descriptor needsFrameFunction
> with: framelessStackDelta])
>                                         ifTrue:
>                                                 ["With immutability we win
> simply by avoiding a frame build if the receiver is young and not
> immutable."
>                                                  self cppIf: IMMUTABILITY
>                                                         ifTrue:
> [descriptor is1ByteInstVarStore
>
> ifTrue: [useTwoPaths := true]
>
> ifFalse: [needsFrame := true. useTwoPaths := false]]
>                                                         ifFalse:
> [needsFrame := true. useTwoPaths := false]]
>                                         ifFalse:
>                                                 [framelessStackDelta :=
> framelessStackDelta + descriptor stackDelta.
>                                                  "Without immutability we
> win if there are two or more stores and the receiver is new."
>                                                  self cppIf: IMMUTABILITY
>                                                         ifTrue: []
>                                                         ifFalse:
>
> [descriptor is1ByteInstVarStore ifTrue:
>
> [seenInstVarStore
>
>       ifTrue: [useTwoPaths := true]
>
>       ifFalse: [seenInstVarStore := true]]]]].
>
>                  descriptor isBranch ifTrue:
>                         [distance := self spanFor: descriptor at: pc exts:
> nExts in: methodObj.
>                          targetPC := pc + descriptor numBytes + distance.
>                          self maybeCountFixup: descriptor.
>                          (self isBackwardBranch: descriptor at: pc exts:
> nExts in: methodObj)
>                                 ifTrue: [self initializeFixupAt: targetPC
> - initialPC]
>                                 ifFalse:
>                                         [latestContinuation :=
> latestContinuation max: targetPC.
>                                          self maybeCountCounter]].
>                  descriptor isBlockCreation ifTrue:
>                         [numBlocks := numBlocks + 1.
>                          distance := self spanFor: descriptor at: pc exts:
> nExts in: methodObj.
>                          targetPC := pc + descriptor numBytes + distance.
>                          latestContinuation := latestContinuation max:
> targetPC.
>                          self maybeCountFixup: descriptor].
>
>                  NewspeakVM ifTrue:
>                         [descriptor hasIRC ifTrue: [numIRCs := numIRCs +
> 1]].
>                  pc := pc + descriptor numBytes.
> +                nExts := descriptor isExtension ifTrue: [nExts + 1]
> ifFalse: [extA := numExtB := extB := 0].
> -                nExts := descriptor isExtension ifTrue: [nExts + 1]
> ifFalse: [extA := extB := 0].
>                  prevBCDescriptor := descriptor].
>         ^numBlocks!
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20170108/c39c9762/attachment-0001.html>


More information about the Vm-dev mailing list