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

Ronie Salgado roniesalg at gmail.com
Mon Mar 6 04:54:47 UTC 2017


Hi Eliot,

When generating the sources, I am getting an error for "conflicting
implementations for #reinitialize". CogSSBytecodeFixup >> #reinitialize vs
CogAbstractInstruction >> #reinitialize.

Best regards,
Ronie

2017-03-05 0:27 GMT-03:00 <commits at source.squeak.org>:

>
> Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2144.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-eem.2144
> Author: eem
> Time: 4 March 2017, 7:26:19.274398 pm
> UUID: 04b5cdd0-8070-4427-8771-913885fada41
> Ancestors: VMMaker.oscog-eem.2143
>
> 64-bit Sista: Spur64BitMemoryManager must export fetchClassTagOf:.
>
> Spur:
> Check 64-bit translation for signed comparisons in SpurPlanningCompactor
> as well as 32-bit.
>
> Cogit:
> Rename blockPass, saveForBlockCompile et al to compilationPass,
> saveForRecompile etc.  This so that RegisterAllocatingCogit can recompile
> when discovering a loop that needs a merge so that the register set
> computed at the end of a loop can be installed at the head.
> Refactor initializeFixupAt: into it and initializeFixup: to support RAC's
> recompilation.
> Add some inlines to eliminate some thin intermediate functions.
> Add support for adding #ifdef's to struct defs and use it to avoid
> CogSSBytecodeFixup's simNativeStackPtr and simNativeStackSize in
> non-Lowcode VMs.
>
> RegisterAllocatingCogit:
> Arrange to recompile when discovering loops with merges required to jump
> to the head.  Installing the register set at the end of the loop at its
> beginning means a much faster back branch on the common path and should be
> a win for simple loops.
> Refactor resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: into it
> and conflictingRegistersBetweenSimStackAnd: for use by
> ensureRegisterAssignmentsAreAtHeadOfLoop:.
>
> Fix several slips where methodOrBlockNumArgs was used instead of
> methodOrBlockNumTemps.
>
> Nuke unused method & variable.
>
> =============== Diff against VMMaker.oscog-eem.2143 ===============
>
> Item was added:
> + ----- Method: CogAbstractInstruction>>reinitialize (in category
> 'initialization') -----
> + reinitialize
> +       annotation := nil.
> +       dependent := nil.
> +       operands at: 0 put: (operands at: 1 put: (operands at: 2 put: 0))!
>
> Item was added:
> + ----- Method: CogBytecodeFixup class>>filteredInstVarNames (in category
> 'translation') -----
> + filteredInstVarNames
> +       "Override to eliminate bcpc,"
> +       ^super filteredInstVarNames copyWithout: 'bcpc'!
>
> Item was changed:
>   ----- Method: CogBytecodeFixup class>>instVarNamesAndTypesForTranslationDo:
> (in category 'translation') -----
>   instVarNamesAndTypesForTranslationDo: aBinaryBlock
>         "enumerate aBinaryBlock with the names and C type strings for the
> inst vars to include in a BytecodeFixup struct."
>
> +       self filteredInstVarNames do:
> -       self allInstVarNames do:
>                 [:ivn|
> +                aBinaryBlock
> +                       value: ivn
> +                       value: (ivn = 'targetInstruction'
> +                                       ifTrue: [#'AbstractInstruction *']
> +                                       ifFalse:
> +                                               [#sqInt])]!
> -               ivn ~= 'bcpc' ifTrue:
> -                       [aBinaryBlock
> -                               value: ivn
> -                               value: (ivn = 'targetInstruction'
> -                                               ifTrue:
> [#'AbstractInstruction *']
> -                                               ifFalse:
> -                                                       [#sqInt])]]!
>
> Item was changed:
>   ----- Method: CogBytecodeFixup>>recordBcpc: (in category 'simulation')
> -----
>   recordBcpc: theBytecodePC
>         <inline: true>
>         self cCode: '' inSmalltalk:
>                 [(bcpc isNil or: [bcpc = theBytecodePC])
>                         ifTrue: [bcpc := theBytecodePC]
>                         ifFalse:
>                                 [bcpc := bcpc isInteger
>                                                         ifTrue: [{bcpc.
> theBytecodePC}]
> +                                                       ifFalse:
> +                                                               [(bcpc
> includes: theBytecodePC) ifTrue: [^self].
> +                                                                bcpc,
> {theBytecodePC}]]]!
> -                                                       ifFalse: [bcpc,
> {theBytecodePC}]]]!
>
> Item was added:
> + ----- Method: CogSSBytecodeFixup class>>filteredInstVarNames (in
> category 'translation') -----
> + filteredInstVarNames
> +       "Override to add ifdef LowcodeVM around the native stack info.
> +        self typedef"
> +       ^super filteredInstVarNames
> +               copyReplaceAll: #('simNativeStackPtr' 'simNativeStackSize')
> +               with: #('#if LowcodeVM' 'simNativeStackPtr'
> 'simNativeStackSize' '#endif')!
>
> Item was changed:
>   ----- Method: CogSSBytecodeFixup>>reinitialize (in category
> 'accessing') -----
>   reinitialize
>         <inline: true>
> +       targetInstruction := simStackPtr := 0.
> +       LowcodeVM ifTrue:
> +               [simNativeStackPtr := simNativeStackSize := 0]!
> -       targetInstruction := 0.
> -       simStackPtr := 0.
> -       LowcodeVM ifTrue: [
> -               simNativeStackPtr := 0.
> -       ]!
>
> Item was changed:
>   CogClass subclass: #Cogit
>         instanceVariableNames: 'coInterpreter objectMemory
> objectRepresentation processor threadManager methodZone methodZoneBase
> codeBase minValidCallAddress lastNInstructions simulatedAddresses
> simulatedTrampolines simulatedVariableGetters simulatedVariableSetters
> printRegisters printInstructions compilationTrace clickConfirm breakPC
> breakBlock singleStep guardPageSize traceFlags traceStores breakMethod
> methodObj enumeratingCogMethod methodHeader initialPC endPC
> methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex
> backEnd literalsManager postCompileHook methodLabel stackCheckLabel
> blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset
> stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment
> uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset
> noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry
> cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0
> endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
>  ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable
> byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex
> numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment
> expectedSPAlignment expectedFPAlignment codeModified maxLitIndex
> ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline
> ceCPICMissTrampoline ceReturnToInterpreterTrampoline
> ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline
> ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline
> ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg
> ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode
> cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline
> ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline
> ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction
> ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline
> ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers
> ordinarySendTrampolines superSen
>  dTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines
> outerSendTrampolines selfSendTrampolines firstSend lastSend
> realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg
> realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex
> trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex
> cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner
> ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs
> receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass
> cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer
> CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel
> ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline
> debugBytecodePointers debugOpcodeIndices disassemblingMethod'
> +       classVariableNames: 'AltBlockCreationBytecodeSize
> AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors
> AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs
> BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N
> EagerInstructionDecoration FirstAnnotation FirstSpecialSelector
> HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend
> IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend
> IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall
> IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize
> MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex
> NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime
> NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
> -       classVariableNames: 'AltBlockCreationBytecodeSize
> AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors
> AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs
> BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N
> EagerInstructionDecoration FirstAnnotation FirstSpecialSelector
> HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperSend
> IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend
> IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall
> IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize
> MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex
> NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NeedsFixupFlag
> NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines
> ProcessorClass RRRName'
>         poolDictionaries: 'CogAbstractRegisters CogCompilationConstants
> CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants
> VMObjectIndices VMStackFrameOffsets'
>         category: 'VMMaker-JIT'!
>   Cogit class
>         instanceVariableNames: 'generatorTable primitiveTable'!
>
>   !Cogit commentStamp: 'eem 2/25/2017 17:53' prior: 0!
>   I am the code generator for the Cog VM.  My job is to produce machine
> code versions of methods for faster execution and to manage inline caches
> for faster send performance.  I can be tested in the current image using my
> class-side in-image compilation facilities.  e.g. try
>
>         StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
>
>   I have concrete subclasses that implement different levels of
> optimization:
>         SimpleStackBasedCogit is the simplest code generator.
>
>         StackToRegisterMappingCogit is the current production code
> generator  It defers pushing operands
>         to the stack until necessary and implements a register-based
> calling convention for low-arity sends.
>
>         SistaCogit is an experimental code generator with support for
> counting
>         conditional branches, intended to support adaptive optimization.
>
>         RegisterAllocatingCogit is an experimental code generator with
> support for allocating temporary variables
>         to registers. It is inended to serve as the superclass to
> SistaCogit once it is working.
>
>         SistaRegisterAllocatingCogit and SistaCogitClone are temporary
> classes that allow testing a clone of
>         SistaCogit that inherits from RegisterAllocatingCogit.  Once
> things work these will be merged and
>         will replace SistaCogit.
>
>   coInterpreter <CoInterpreterSimulator>
>         the VM's interpreter with which I cooperate
>   methodZoneManager <CogMethodZoneManager>
>         the manager of the machine code zone
>   objectRepresentation <CogObjectRepresentation>
>         the object used to generate object accesses
>   processor <BochsIA32Alien|?>
>         the simulator that executes the IA32/x86 machine code I generate
> when simulating execution in Smalltalk
>   simulatedTrampolines <Dictionary of Integer -> MessageSend>
>         the dictionary mapping trap jump addresses to run-time routines
> used to warp from simulated machine code in to the Smalltalk run-time.
>   simulatedVariableGetters <Dictionary of Integer -> MessageSend>
>         the dictionary mapping trap read addresses to variables in
> run-time objects used to allow simulated machine code to read variables in
> the Smalltalk run-time.
>   simulatedVariableSetters <Dictionary of Integer -> MessageSend>
>         the dictionary mapping trap write addresses to variables in
> run-time objects used to allow simulated machine code to write variables in
> the Smalltalk run-time.
>   printRegisters printInstructions clickConfirm <Boolean>
>         flags controlling debug printing and code simulation
>   breakPC <Integer>
>         machine code pc breakpoint
>   cFramePointer cStackPointer <Integer>
>         the variables representing the C stack & frame pointers, which
> must change on FFI callback and return
>   selectorOop <sqInt>
>         the oop of the methodObj being compiled
>   methodObj <sqInt>
>         the bytecode method being compiled
>   initialPC endPC <Integer>
>         the start and end pcs of the methodObj being compiled
>   methodOrBlockNumArgs <Integer>
>         argument count of current method or block being compiled
>   needsFrame <Boolean>
>         whether methodObj or block needs a frame to execute
>   primitiveIndex <Integer>
>         primitive index of current method being compiled
>   methodLabel <CogAbstractOpcode>
>         label for the method header
>   blockEntryLabel <CogAbstractOpcode>
>         label for the start of the block dispatch code
>   stackOverflowCall <CogAbstractOpcode>
>         label for the call of ceStackOverflow in the method prolog
>   sendMissCall <CogAbstractOpcode>
>         label for the call of ceSICMiss in the method prolog
>   entryOffset <Integer>
>         offset of method entry code from start (header) of method
>   entry <CogAbstractOpcode>
>         label for the first instruction of the method entry code
>   noCheckEntryOffset <Integer>
>         offset of the start of a method proper (after the method entry
> code) from start (header) of method
>   noCheckEntry <CogAbstractOpcode>
>         label for the first instruction of start of a method proper
>   fixups <Array of <AbstractOpcode Label | nil>>
>         the labels for forward jumps that will be fixed up when reaching
> the relevant bytecode.  fixups has one element per byte in methodObj's
> bytecode; initialPC maps to fixups[0].
>   abstractOpcodes <Array of <AbstractOpcode>>
>         the code generated when compiling methodObj
>   byte0 byte1 byte2 byte3 <Integer>
>         individual bytes of current bytecode being compiled in methodObj
>   bytecodePointer <Integer>
>         bytecode pc (same as Smalltalk) of the current bytecode being
> compiled
>   opcodeIndex <Integer>
>         the index of the next free entry in abstractOpcodes (this code is
> translated into C where OrderedCollection et al do not exist)
>   numAbstractOpcodes <Integer>
>         the number of elements in abstractOpcocdes
>   blockStarts <Array of <BlockStart>>
>         the starts of blocks in the current method
>   blockCount
>         the index into blockStarts as they are being noted, and hence
> eventually the total number of blocks in the current method
>   labelCounter <Integer>
>         a nicety for numbering labels not needed in the production system
> but probably not expensive enough to worry about
>   ceStackOverflowTrampoline <Integer>
>   ceSend0ArgsTrampoline <Integer>
>   ceSend1ArgsTrampoline <Integer>
>   ceSend2ArgsTrampoline <Integer>
>   ceSendNArgsTrampoline <Integer>
>   ceSendSuper0ArgsTrampoline <Integer>
>   ceSendSuper1ArgsTrampoline <Integer>
>   ceSendSuper2ArgsTrampoline <Integer>
>   ceSendSuperNArgsTrampoline <Integer>
>   ceSICMissTrampoline <Integer>
>   ceCPICMissTrampoline <Integer>
>   ceStoreCheckTrampoline <Integer>
>   ceReturnToInterpreterTrampoline <Integer>
>   ceBaseFrameReturnTrampoline <Integer>
>   ceSendMustBeBooleanTrampoline <Integer>
>   ceClosureCopyTrampoline <Integer>
>         the various trampolines (system-call-like jumps from machine code
> to the run-time).
>         See Cogit>>generateTrampolines for the mapping from trampoline to
> run-time
>         routine and then read the run-time routine for a funcitonal
> description.
>   ceEnterCogCodePopReceiverReg <Integer>
>         the enilopmart (jump from run-time to machine-code)
>   methodZoneBase <Integer>
>   !
>   Cogit class
>         instanceVariableNames: 'generatorTable primitiveTable'!
>
> Item was removed:
> - ----- Method: InLineLiteralsManager>>resetForBlockCompile (in category
> 'compile abstract instructions') -----
> - resetForBlockCompile!
>
> Item was added:
> + ----- Method: InLineLiteralsManager>>resetForRecompile (in category
> 'compile abstract instructions') -----
> + resetForRecompile!
>
> Item was removed:
> - ----- Method: InLineLiteralsManager>>saveForBlockCompile (in category
> 'compile abstract instructions') -----
> - saveForBlockCompile!
>
> Item was added:
> + ----- Method: InLineLiteralsManager>>saveForRecompile (in category
> 'compile abstract instructions') -----
> + saveForRecompile!
>
> Item was removed:
> - ----- Method: OutOfLineLiteralsManager>>resetForBlockCompile (in
> category 'initialization') -----
> - resetForBlockCompile
> -       firstOpcodeIndex := savedFirstOpcodeIndex.
> -       nextLiteralIndex := savedNextLiteralIndex.
> -       lastDumpedLiteralIndex := savedLastDumpedLiteralIndex!
>
> Item was added:
> + ----- Method: OutOfLineLiteralsManager>>resetForRecompile (in category
> 'initialization') -----
> + resetForRecompile
> +       <inline: true>
> +       firstOpcodeIndex := savedFirstOpcodeIndex.
> +       nextLiteralIndex := savedNextLiteralIndex.
> +       lastDumpedLiteralIndex := savedLastDumpedLiteralIndex!
>
> Item was removed:
> - ----- Method: OutOfLineLiteralsManager>>saveForBlockCompile (in
> category 'initialization') -----
> - saveForBlockCompile
> -       savedFirstOpcodeIndex := firstOpcodeIndex.
> -       savedNextLiteralIndex := nextLiteralIndex.
> -       savedLastDumpedLiteralIndex := lastDumpedLiteralIndex!
>
> Item was added:
> + ----- Method: OutOfLineLiteralsManager>>saveForRecompile (in category
> 'initialization') -----
> + saveForRecompile
> +
> +       <inline: true>
> +       savedFirstOpcodeIndex := firstOpcodeIndex.
> +       savedNextLiteralIndex := nextLiteralIndex.
> +       savedLastDumpedLiteralIndex := lastDumpedLiteralIndex!
>
> Item was changed:
>   StackToRegisterMappingCogit subclass: #RegisterAllocatingCogit
> +       instanceVariableNames: 'numFixups mergeSimStacksBase nextFixup
> scratchSimStack scratchSpillBase scratchOptStatus
> ceSendMustBeBooleanAddTrueLongTrampoline ceSendMustBeBooleanAddFalseLongTrampoline
> recompileForLoopRegisterAssignments'
> -       instanceVariableNames: 'numFixups mergeSimStacksBase nextFixup
> scratchSimStack scratchSpillBase scratchOptStatus
> ceSendMustBeBooleanAddTrueLongTrampoline ceSendMustBeBooleanAddFalseLon
> gTrampoline'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'VMMaker-JIT'!
>
>   !RegisterAllocatingCogit commentStamp: 'eem 2/9/2017 10:40' prior: 0!
>   RegisterAllocatingCogit is an optimizing code generator that is
> specialized for register allocation.
>
>   On the contrary to StackToRegisterMappingCogit, RegisterAllocatingCogit
> keeps at each control flow merge point the state of the simulated stack to
> merge into and not only an integer fixup. Each branch and jump record the
> current state of the simulated stack, and each fixup is responsible for
> merging this state into the saved simulated stack.
>
>   Instance Variables
>         ceSendMustBeBooleanAddFalseLongTrampoline:              <Integer>
>         ceSendMustBeBooleanAddTrueLongTrampoline:               <Integer>
>         mergeSimStacksBase:
>                      <Integer>
>         nextFixup:
>                                       <Integer>
>         numFixups:
>                                       <Integer>
>         scratchOptStatus:
>                              <CogSSOptStatus>
>         scratchSimStack:
>                               <Array of CogRegisterAllocatingSimStackE
> ntry>
>         scratchSpillBase:
>                              <Integer>
>
>   ceSendMustBeBooleanAddFalseLongTrampoline
>         - the must-be-boolean trampoline for long jump false bytecodes
> (the existing ceSendMustBeBooleanAddFalseTrampoline is used for short
> branches)
>
>   ceSendMustBeBooleanAddTrueLongTrampoline
>         - the must-be-boolean trampoline for long jump true bytecodes (the
> existing ceSendMustBeBooleanAddTrueTrampoline is used for short branches)
>
>   mergeSimStacksBase
>         - the base address of the alloca'ed memory for merge fixups
>
>   nextFixup
>         - the index into mergeSimStacksBase from which the next needed
> mergeSimStack will be allocated
>
>   numFixups
>         - a conservative (over) estimate of the number of merge fixups
> needed in a method
>
>   scratchOptStatus
>         - a scratch variable to hold the state of optStatus while merge
> code is generated
>
>   scratchSimStack
>         - a scratch variable to hold the state of simStack while merge
> code is generated
>
>   scratchSpillBase
>         - a scratch variable to hold the state of spillBase while merge
> code is generated!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>compileAbstractInstructionsFrom:through:
> (in category 'compile abstract instructions') -----
>   compileAbstractInstructionsFrom: start through: end
>         "Loop over bytecodes, dispatching to the generator for each
> bytecode, handling fixups in due course.
>          Override to provide a development-time only escape for failed
> merges due to partially implemented
> +        parallel move.  Override to recompile after a loop requiring a
> merge is detected."
> +       ^[| result initialOpcodeIndex initialCounterIndex
> initialIndexOfIRC |
> +          compilationPass := 1.
> +          initialOpcodeIndex := opcodeIndex.
> +          initialCounterIndex := self maybeCounterIndex."for SistaCogit"
> +          literalsManager saveForRecompile.
> +          NewspeakVM ifTrue:
> +                       [initialIndexOfIRC := indexOfIRC].
> +          [recompileForLoopRegisterAssignments := false.
> +           result := super compileAbstractInstructionsFrom: start
> through: end.
> +           result = 0 and: [recompileForLoopRegisterAssignments]]
> +               whileTrue:
> +                       [self reinitializeAllButBackwardFixupsFrom: start
> through: end.
> +                        self resetSimStack: start.
> +                        self reinitializeOpcodesFrom: initialOpcodeIndex
> to: opcodeIndex - 1.
> +                        compilationPass := compilationPass + 1.
> +                        nextFixup := 0.
> +                        opcodeIndex := initialOpcodeIndex.
> +                        self maybeSetCounterIndex: initialCounterIndex.
> "For SistaCogit"
> +                        literalsManager resetForRecompile.
> +                        NewspeakVM ifTrue:
> +                               [indexOfIRC := initialIndexOfIRC]].
> +           result]
> +                       on: Notification
> +                       do: [:ex|
> +                               ex tag == #failedMerge ifTrue:
> +                                       [coInterpreter transcript
> +                                               ensureCr; nextPutAll:
> 'FAILED MERGE IN ';
> +                                               nextPutAll: (coInterpreter
> nameOfClass: (coInterpreter methodClassOf: methodObj));
> +                                               nextPutAll: '>>#';
> nextPutAll: (coInterpreter stringOf: (coInterpreter maybeSelectorOfMethod:
> methodObj));
> +                                               flush.
> +                                        ^ShouldNotJIT].
> +                               ex pass]!
> -        parallel move."
> -       ^[super compileAbstractInstructionsFrom: start through: end]
> -               on: Notification
> -               do: [:ex|
> -                       ex tag == #failedMerge ifTrue:
> -                               [coInterpreter transcript
> -                                       ensureCr; nextPutAll: 'FAILED
> MERGE IN ';
> -                                       nextPutAll: (coInterpreter
> nameOfClass: (coInterpreter methodClassOf: methodObj));
> -                                       nextPutAll: '>>#'; nextPutAll:
> (coInterpreter stringOf: (coInterpreter maybeSelectorOfMethod: methodObj));
> -                                       flush.
> -                                ^ShouldNotJIT].
> -                       ex pass]!
>
> Item was added:
> + ----- Method: RegisterAllocatingCogit>>conflictingRegistersBetweenSimStackAnd:
> (in category 'bytecode generator support') -----
> + conflictingRegistersBetweenSimStackAnd: mergeSimStack
> +       <var: #mergeSimStack type: #'SimStackEntry *'>
> +       | currentRegsMask mergeRegsMask potentialConflictRegMask |
> +       <var: #currentEntry type: #'SimStackEntry *'>
> +       <var: #targetEntry type: #'SimStackEntry *'>
> +       currentRegsMask := mergeRegsMask := potentialConflictRegMask := 0.
> +       0 to: simStackPtr do:
> +               [:i| | currentEntry targetEntry currentRegMask
> mergeRegMask |
> +                currentRegMask := (currentEntry := self simStack:
> simStack at: i) registerMaskOrNone.
> +                mergeRegMask := (targetEntry := self simStack:
> mergeSimStack at: i) registerMaskOrNone.
> +                (currentRegMask ~= mergeRegMask
> +                 and: [currentRegMask ~= 0 or: [mergeRegMask ~= 0]])
> ifTrue:
> +                       [potentialConflictRegMask :=
> potentialConflictRegMask bitOr: (currentRegMask bitOr: mergeRegMask)].
> +                currentRegsMask := currentRegsMask bitOr: currentRegMask.
> +                mergeRegsMask := mergeRegsMask bitOr: mergeRegMask].
> +       ^potentialConflictRegMask bitAnd: (currentRegsMask bitAnd:
> mergeRegsMask)!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>deassignRegisterForTempVar:in:
> (in category 'bytecode generator support') -----
>   deassignRegisterForTempVar: targetEntry in: mergeSimStack
>         "If merging a non-temp with a temp that has a live register we can
> assign
>          to the register, but must unassign the register from the temp,
> otherwise
>          the temp will acquire the merged value without an assignment.
> The targetEntry
> +        must also be transmogrified into an SSRegister entry, which is
> done in the caller."
> -        must also be transmogrified into an SSRegister entry."
>         <var: #targetEntry type: #'SimStackEntry *'>
>         <var: #duplicateEntry type: #'SimStackEntry *'>
>         <var: #mergeSimStack type: #'SimStackEntry *'>
>         <inline: true>
>         | reg |
>         reg := targetEntry liveRegister.
>         self assert: (reg ~= NoReg and: [targetEntry type = SSConstant or:
> [targetEntry isFrameTempVar]]).
>         targetEntry type = SSConstant
>                 ifTrue:
>                         [simStackPtr to: 0 by: -1 do:
>                                 [:j| | duplicateEntry |
>                                  duplicateEntry := self simStack:
> mergeSimStack at: j.
>                                  (duplicateEntry registerOrNone = reg
>                                   and: [duplicateEntry type = SSBaseOffset
> or: [duplicateEntry type = SSSpill]]) ifTrue:
>                                         [duplicateEntry liveRegister:
> NoReg]]]
>                 ifFalse:
>                         [simStackPtr to: 0 by: -1 do:
>                                 [:j| | duplicateEntry |
>                                  duplicateEntry := self simStack:
> mergeSimStack at: j.
>                                  (targetEntry isSameEntryAs:
> duplicateEntry) ifTrue:
>                                         [j < methodOrBlockNumTemps
>                                                 ifTrue: [duplicateEntry
> liveRegister: NoReg]
> +                                               ifFalse: [duplicateEntry
> type: SSRegister; register: reg]]]]!
> -                                               ifFalse: [duplicateEntry
> type: SSRegister; register: reg]]]].
> -       targetEntry
> -               type: SSRegister;
> -               register: reg!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>ensureFixupAt: (in category
> 'bytecode generator support') -----
>   ensureFixupAt: targetPC
>         "Make sure there's a flagged fixup at the target pc in fixups.
>          Initially a fixup's target is just a flag.  Later on it is
> replaced with a proper instruction.
>          Override to enerate stack merging code if required."
>         | fixup |
>         <var: #fixup type: #'BytecodeFixup *'>
>         self assert: targetPC > bytecodePC.
>         fixup := self fixupAt: targetPC.
>         fixup needsFixup
>                 ifTrue:
>                         [fixup mergeSimStack
>                                 ifNil: [self setMergeSimStackOf: fixup]
>                                 ifNotNil: [self mergeCurrentSimStackWith:
> fixup forwards: true]]
>                 ifFalse:
> +                       [self assert: (fixup mergeSimStack isNil or:
> [compilationPass = 2]).
> -                       [self assert: fixup mergeSimStack isNil.
>                          self moveVolatileSimStackEntriesToRegisters.
> +                        fixup mergeSimStack
> +                               ifNil: [self setMergeSimStackOf: fixup]
> +                               ifNotNil: [self assert: (self simStack:
> simStack isIdenticalTo: fixup mergeSimStack)]].
> -                        self setMergeSimStackOf: fixup].
>         ^super ensureFixupAt: targetPC!
>
> Item was added:
> + ----- Method: RegisterAllocatingCogit>>ensureRegisterAssignmentsAreAtHeadOfLoop:
> (in category 'bytecode generator support') -----
> + ensureRegisterAssignmentsAreAtHeadOfLoop: target
> +       "Compiling a loop body will compute a set of live registers.  The
> backward branch must merge
> +        with the head of the loop.  So it is preferrable to make the
> register assignments at the end of
> +        the loop available at the head.  To do this, simply copy the
> register assignments to the loop
> +        head's fixup in the first compilation pass and schedule a second
> compilation pass.  On the
> +        second pass the merge will occur when encountering the fixup for
> the loop head, using
> +        exactly the same code as for a merge at the end of an if."
> +       | conflictingRegsMask |
> +       compilationPass > 1 ifTrue:
> +               ["self deny: (self mergeRequiredToTarget: target
> mergeSimStack)."
> +                self assert: (target mergeSimStack isNil or: [self
> simStack: simStack isIdenticalTo: target mergeSimStack]).
> +                ^self].
> +       (self mergeRequiredToTarget: target mergeSimStack) ifFalse:
> +               [^self].
> +       "Schedule a recompile and merge the end-of-loop assignments into
> the head of the loop,
> +        giving priority to the assignments at this point, and preserving
> any other non-conflicting
> +        assignments."
> +       recompileForLoopRegisterAssignments := true.
> +       conflictingRegsMask := self conflictingRegistersBetweenSimStackAnd:
> target mergeSimStack.
> +       self deny: (self register: FPReg isInMask: conflictingRegsMask).
> +       0 to: simStackPtr do:
> +               [:i| | currentEntry targetEntry |
> +                currentEntry := self simStack: simStack at: i.
> +                targetEntry := self simStack: target mergeSimStack at: i.
> +                currentEntry liveRegister ~= NoReg
> +                       ifTrue:
> +                               [targetEntry liveRegister: currentEntry
> liveRegister]
> +                       ifFalse:
> +                               [(targetEntry registerMask anyMask:
> conflictingRegsMask) ifTrue:
> +                                       [targetEntry liveRegister:
> NoReg]]].
> +       optStatus isReceiverResultRegLive ifTrue:
> +               [target isReceiverResultRegSelf: true]!
>
> Item was removed:
> - ----- Method: RegisterAllocatingCogit>>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 |
> -
> -       reg := self allocateRegForStackEntryAt: 0.
> -       self ssTop popToReg: reg.
> -
> -       literal := self getLiteral: (extA * 256 + byte1).
> -       extA := 0.
> -       distance := extB * 256 + byte2.
> -       extB := 0.
> -       numExtB := 0.
> -
> -       "Because ensureFixupAt: will generate code to merge with the
> target simStack when required, it is
> -        necessary to tease apart the jump and the merge so that the merge
> code is only executed if the
> -        branch is taken.  i.e. if merge code is required we generate
> -                       jump not cond Lcontinue
> -                       ... merge code ...
> -                       jump Ltarget
> -               Lcontinue:
> -        instead of the incorrect
> -                       ... merge code ...
> -                       jump cond Ltarget"
> -       (self mergeRequiredForJumpTo: bytecodePC + 3 + distance) ifTrue:
> -               [self shouldBeImplemented].
> -
> -       targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC
> + 3 + distance) to: #'AbstractInstruction *'.
> -
> -       (objectMemory isArrayNonImm: literal)
> -               ifTrue: [objectRepresentation branchIf: reg
> notInstanceOfBehaviors: literal target: targetFixUp]
> -               ifFalse: [objectRepresentation branchIf: reg
> notInstanceOfBehavior: literal target: targetFixUp].
> -
> -       self ssPop: 1.
> -
> -       ^0!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>genJumpBackTo: (in category
> 'bytecode generator support') -----
>   genJumpBackTo: targetPC
>         | target |
> +       "On first pass install register allocations (if any) as of the end
> of the loop and back up to recompile.
> +        One the second pass generate
> +                               (any merge elided because register
> assignments copied to loop head in first pass)
> -       "We generate
> -                               merge
>                                 cmp stackLimit
>                                 jumpAboveOrEqual target
>                                 flush
>                                 checkForInterrupts
> +                               merge from flushed (N.B. If stack was
> flushed before loop we could conceivably jump to the pre-loop merge code)
> -                               marge from flushed
>                                 jmp target
>          self printSimStack; printSimStack: target mergeSimStack"
>         self assert: targetPC < bytecodePC.
>         target := self fixupAt: targetPC.
> +       self ensureRegisterAssignmentsAreAtHeadOfLoop: target.
> -       self mergeCurrentSimStackWith: target forwards: false.
>         self MoveAw: coInterpreter stackLimitAddress R: TempReg.
>         self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
>         self JumpAboveOrEqual: target.
>
>         self ssFlushTo: simStackPtr.
>         self CallRT: ceCheckForInterruptTrampoline.
>         self annotateBytecode: self Label.
>         self flushLiveRegistersForSuspensionPoint.
>         self mergeCurrentSimStackWith: target forwards: false.
>         self Jump: target.
>         deadCode := true. "can't fall through"
>         ^0!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith:forwards:
> (in category 'bytecode generator support') -----
>   mergeCurrentSimStackWith: fixup forwards: forwards
>         "At a merge point the cogit expects the stack to be in the same
> state as mergeSimStack.
>          mergeSimStack is the state as of some jump forward or backward to
> this point.  So make simStack agree
>          with mergeSimStack (it is, um, problematic to plant code at the
> jump).
>          Values may have to be assigned to registers.  Registers may have
> to be swapped.
>          The state of optStatus must agree.
>          Generate code to merge the current simStack with that of the
> target fixup,
>          the goal being to keep as many registers live as possible.  If
> the merge is forwards
>          registers can be deassigned (since registers are always written
> to temp vars).
>          But if backwards, nothing can be deassigned, and the state /must/
> reflect the target."
>         "self printSimStack; printSimStack: fixup mergeSimStack"
>         "abstractOpcodes object copyFrom: startIndex to: opcodeIndex"
>         <var: #fixup type: #'BytecodeFixup *'>
>         | startIndex mergeSimStack currentEntry targetEntry
> writtenToRegisters |
>         <var: #mergeSimStack type: #'SimStackEntry *'>
>         <var: #targetEntry type: #'SimStackEntry *'>
>         <var: #currentEntry type: #'SimStackEntry *'>
>         (mergeSimStack := fixup mergeSimStack) ifNil: [^self].
>         startIndex := opcodeIndex. "for debugging"
>         "Assignments amongst the registers must be made in order to avoid
> overwriting.
>          If necessary exchange registers amongst simStack's entries to
> resolve any conflicts."
>         self resolveRegisterOrderConflictsBetweenCurrentSimStackAnd:
> mergeSimStack.
>         (self asserta: (self conflictsResolvedBetweenSimStackAnd:
> mergeSimStack)) ifFalse:
>                 [Notification new tag: #failedMerge; signal].
> +       "Compute written to registers.  Perhaps we should use 0 in place
> of methodOrBlockNumArgs
> +        but Smalltalk does not assign to arguments."
>         writtenToRegisters := 0.
>         (self pushForMergeWith: mergeSimStack)
>                 ifTrue:
>                         [methodOrBlockNumArgs to: simStackPtr do:
>                                 [:i|
>                                  currentEntry := self simStack: simStack
> at: i.
>                                  targetEntry := self simStack:
> mergeSimStack at: i.
>                                  writtenToRegisters := writtenToRegisters
> bitOr: targetEntry registerMask.
>                                  (currentEntry reconcileForwardsWith:
> targetEntry) ifTrue:
>                                         [self assert: i >=
> methodOrBlockNumArgs.
> +                                        self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack.
> +                                        targetEntry
> +                                               type: SSRegister;
> +                                               register: targetEntry
> liveRegister].
> -                                        self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack].
>                                  "Note, we could update the simStack and
> spillBase here but that is done in restoreSimStackAtMergePoint:
>                                  spilled ifFalse:
>                                         [simSpillBase := i - 1].
>                                  simStack
>                                         at: i
>                                         put: (self
>                                                         cCode:
> [mergeSimStack at: i]
>                                                         inSmalltalk:
> [(mergeSimStack at: i) copy])"]]
>                 ifFalse:
>                         [simStackPtr to: methodOrBlockNumArgs by: -1 do:
>                                 [:i|
>                                  currentEntry := self simStack: simStack
> at: i.
>                                  targetEntry := self simStack:
> mergeSimStack at: i.
>                                  writtenToRegisters := writtenToRegisters
> bitOr: targetEntry registerMask.
>                                  (currentEntry reconcileForwardsWith:
> targetEntry) ifTrue:
>                                         [self assert: i >=
> methodOrBlockNumArgs.
> +                                        self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack.
> +                                        targetEntry
> +                                               type: SSRegister;
> +                                               register: targetEntry
> liveRegister].
> -                                        self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack].
>                                  "Note, we could update the simStack and
> spillBase here but that is done in restoreSimStackAtMergePoint:
>                                  spilled ifFalse:
>                                         [simSpillBase := i - 1].
>                                  simStack
>                                         at: i
>                                         put: (self
>                                                         cCode:
> [mergeSimStack at: i]
>                                                         inSmalltalk:
> [(mergeSimStack at: i) copy])"]].
> +       "Note that since we've deassigned any conflicts beyond the temps
> above we need only compare the temps here."
> +       methodOrBlockNumTemps - 1 to: 0 by: -1 do:
> -       methodOrBlockNumArgs - 1 to: 0 by: -1 do:
>                 [:i|
>                  targetEntry := self simStack: mergeSimStack at: i.
>                  (targetEntry registerMask noMask: writtenToRegisters)
> ifTrue:
>                         [currentEntry := self simStack: simStack at: i.
>                          writtenToRegisters := writtenToRegisters bitOr:
> targetEntry registerMask.
>                          (currentEntry reconcileForwardsWith: targetEntry)
> ifTrue:
>                                 [self assert: i >= methodOrBlockNumArgs.
>                                  self deassignRegisterForTempVar:
> targetEntry in: mergeSimStack]]].
>         optStatus isReceiverResultRegLive ifFalse:
>                 [forwards
>                         ifTrue: "a.k.a. fixup isReceiverResultRegSelf:
> (fixup isReceiverResultRegSelf and: [optStatus isReceiverResultRegLive])"
>                                 [fixup isReceiverResultRegSelf: false]
>                         ifFalse:
>                                 [fixup isReceiverResultRegSelf ifTrue:
>                                         [self
> putSelfInReceiverResultReg]]]!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>mergeWithFixupIfRequired: (in
> category 'simulation stack') -----
>   mergeWithFixupIfRequired: fixup
>         "If this bytecode has a fixup, some kind of merge needs to be
> done. There are 4 cases:
>                 1) the bytecode has no fixup (fixup isNotAFixup)
>                         do nothing
>                 2) the bytecode has a non merge fixup
>                         the fixup has needsNonMergeFixup.
>                         The code generating non merge fixup (currently
> only special selector code) is responsible
>                                 for the merge so no need to do it.
>                         We set deadCode to false as the instruction can be
> reached from jumps.
>                 3) the bytecode has a merge fixup, but execution flow
> *cannot* fall through to the merge point.
>                         the fixup has needsMergeFixup and deadCode = true.
>                         ignores the current simStack as it does not mean
> anything
>                         restores the simStack to the state the jumps to
> the merge point expects it to be.
>                 4) the bytecode has a merge fixup and execution flow *can*
> fall through to the merge point.
>                         the fixup has needsMergeFixup and deadCode = false.
>                         Merge the state into the fixup's state via
> mergeCurrentSimStackWith:forwards:.
>
>         In addition, if this is a backjump merge point, we patch the fixup
> to hold the current simStackPtr
>         for later assertions. self printSimStack: fixup mergeSimStack"
>
>         <var: #fixup type: #'BytecodeFixup *'>
>         "case 1"
>         fixup notAFixup ifTrue: [^0].
>
>         "case 2"
>         fixup isNonMergeFixup ifTrue:
>                 [deadCode
>                         ifTrue:
>                                 [self deny: fixup simStackPtr isNil.
>                                  simStackPtr := fixup simStackPtr.
>                                  self restoreSimStackAtMergePoint: fixup.
>                                  deadCode := false]
>                         ifFalse:
>                                 [self flushRegistersOnlyLiveOnFallThrough:
> fixup].
>                  ^0].
>
>         "cases 3 and 4"
>         self assert: fixup isMergeFixup.
>         self traceMerge: fixup.
>         deadCode
>                 ifTrue: [simStackPtr := fixup simStackPtr] "case 3"
> +               ifFalse: [(fixup isBackwardBranchFixup and:
> [compilationPass > 1]) ifTrue:
> +                                       [fixup simStackPtr: simStackPtr].
> +                               self mergeCurrentSimStackWith: fixup
> forwards: true]. "case 4"
> -               ifFalse: [self mergeCurrentSimStackWith: fixup forwards:
> true]. "case 4"
>         "cases 3 and 4"
>         deadCode := false.
>         fixup isBackwardBranchFixup ifTrue:
> +               [self assert: fixup mergeSimStack isNil ==
> (compilationPass = 1).
> +                fixup mergeSimStack ifNil:
> +                       [self setMergeSimStackOf: fixup]].
> -               [self assert: fixup mergeSimStack isNil.
> -                self setMergeSimStackOf: fixup].
>         fixup targetInstruction: self Label.
>         self assert: simStackPtr = fixup simStackPtr.
>         self cCode: '' inSmalltalk:
>                 [self assert: fixup simStackPtr = (self
> debugStackPointerFor: bytecodePC)].
>         self restoreSimStackAtMergePoint: fixup.
>
>         ^0!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>pushForMergeWith: (in category
> 'bytecode generator support') -----
>   pushForMergeWith: mergeSimStack
>         "Answer if values must be pushed from simStack to merge with
> mergeSimStack, otherwise < 0 (the default)."
>         <var: #mergeSimStack type: #'SimStackEntry *'>
>         <inline: true>
> +       simStackPtr to: methodOrBlockNumTemps by: -1 do:
> -       simStackPtr to: methodOrBlockNumArgs by: -1 do:
>                 [:i|
> +                (self simStack: mergeSimStack at: i) spilled ~= (self
> simStack: simStack at: i) spilled ifTrue:
> -                (self simStack: mergeSimStack at: i) spilled ~=(self
> simStack: simStack at: i) spilled ifTrue:
>                         [^(self simStack: mergeSimStack at: i) spilled]].
>         ^false!
>
> Item was added:
> + ----- Method: RegisterAllocatingCogit>>reinitializeAllButBackwardFixupsFrom:through:
> (in category 'compile abstract instructions') -----
> + reinitializeAllButBackwardFixupsFrom: start through: end
> +       "When a method must be recompiled due to moving a loop's register
> +        assignments to the head of a loop, backward fixups must be marked
> +        as such, and all but backward fixups must be reinitialized."
> +       <inline: true>
> +       | descriptor nExts pc distance targetPC |
> +       <var: #descriptor type: #'BytecodeDescriptor *'>
> +       pc := start.
> +       nExts := 0.
> +       [pc <= end] whileTrue:
> +               [byte0 := (objectMemory fetchByte: pc ofObject: methodObj)
> + bytecodeSetOffset.
> +                descriptor := self generatorAt: byte0.
> +                (descriptor isBranch
> +                 and: [self isBackwardBranch: descriptor at: pc exts:
> nExts in: methodObj]) ifTrue:
> +                       [distance := self spanFor: descriptor at: pc exts:
> nExts in: methodObj.
> +                        targetPC := pc + descriptor numBytes + distance.
> +                        self initializeFixupAt: targetPC].
> +                descriptor isBlockCreation
> +                       ifTrue:
> +                               [distance := self spanFor: descriptor at:
> pc exts: nExts in: methodObj.
> +                                pc := pc + descriptor numBytes + distance]
> +                       ifFalse: [pc := pc + descriptor numBytes].
> +                nExts := descriptor isExtension ifTrue: [nExts + 1]
> ifFalse: [0]].
> +       start to: end do:
> +               [:i| | fixup |
> +                fixup := self fixupAt: i.
> +                (fixup notAFixup or: [fixup isBackwardBranchFixup])
> ifFalse:
> +                       [fixup reinitialize]]!
>
> Item was added:
> + ----- Method: RegisterAllocatingCogit>>reinitializeOpcodesFrom:to: (in
> category 'bytecode generator support') -----
> + reinitializeOpcodesFrom: start to: end
> +       <inline: true>
> +       start to: end do:
> +               [:i|
> +               (self abstractInstructionAt: i) reinitialize]!
>
> Item was added:
> + ----- Method: RegisterAllocatingCogit>>resetSimStack: (in category
> 'bytecode generator support') -----
> + resetSimStack: startPC
> +       <inline: true>
> +       simSpillBase := methodOrBlockNumTemps.
> +       simStackPtr := methodOrBlockNumTemps - 1.
> +       self voidReceiverResultRegContainsSelf.
> +       self flushLiveRegistersForSend.
> +       self cCode: '' inSmalltalk:
> +               [0 to: methodOrBlockNumTemps - 1 do:
> +                       [:i|
> +                       (self simStackAt: i) bcptr: startPC]]!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>resolveRegisterOrderConflictsBetweenCurrentSimStackAnd:
> (in category 'bytecode generator support') -----
>   resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: mergeSimStack
>         <var: #mergeSimStack type: #'SimStackEntry *'>
>         "One simple algorithm is to spill everything if there are any
> conflicts and then pop back.
>          But this is terrible :-(  Can we do better? Yes... Consider the
> following two simStacks
>                 target:         0: | rA | __ | rB | rC | rD | <- sp
>                 current:        0: | __ | __ | rD | rA | rC | <- sp
>          If we were to assign in a naive order, 0 through sp rA would be
> overwritten before its value in current[3] is written to rC,
>          and rC would be overwritten before its value in current[4] is
> written to rD.  But if we swap the registers in current so that
>          they respect the reverse ordering in target we can assign
> directly:
>                 swap current[3] & current[4]
>                                         0: | __ | __ | rD | rC | rA | <- sp
>          now do the assignment in the order target[0] := current[0],
> target[1] := current[1], ...  target[4] := current[4],
>          i.e. rA := current[0]; rB := rD; (rC := rC); (rD := rD).
>
>          So find any conflicts, and if there are any, swap registers in
> the simStack to resolve them.
>          The trivial case of a single conflict is resolved by assigning
> that conflict to TempReg."
> +       | conflictingRegsMask |
> +       conflictingRegsMask := self conflictingRegistersBetweenSimStackAnd:
> mergeSimStack.
> -       | currentRegsMask mergeRegsMask potentialConflictRegMask
> conflictingRegsMask
> -          currentRegMask mergeRegMask currentEntry targetEntry |
> -       <var: #currentEntry type: #'SimStackEntry *'>
> -       <var: #targetEntry type: #'SimStackEntry *'>
> -       currentRegsMask := mergeRegsMask := potentialConflictRegMask := 0.
> -       0 to: simStackPtr do:
> -               [:i|
> -                currentRegMask := (currentEntry := self simStack:
> simStack at: i) registerMaskOrNone.
> -                mergeRegMask := (targetEntry := self simStack:
> mergeSimStack at: i) registerMaskOrNone.
> -                (currentRegMask ~= mergeRegMask
> -                 and: [currentRegMask ~= 0 or: [mergeRegMask ~= 0]])
> ifTrue:
> -                       [potentialConflictRegMask :=
> potentialConflictRegMask bitOr: (currentRegMask bitOr: mergeRegMask)].
> -                currentRegsMask := currentRegsMask bitOr: currentRegMask.
> -                mergeRegsMask := mergeRegsMask bitOr: mergeRegMask].
> -       conflictingRegsMask := potentialConflictRegMask bitAnd:
> (currentRegsMask bitAnd: mergeRegsMask).
>         conflictingRegsMask ~= 0 ifTrue:
>                 [(self isAPowerOfTwo: conflictingRegsMask) "Multiple
> conflicts mean we have to sort"
>                         ifFalse: [self swapCurrentRegistersInMask:
> conflictingRegsMask accordingToRegisterOrderIn: mergeSimStack]
>                         ifTrue: [self assignToTempRegConflictingRegisterIn:
> conflictingRegsMask]].!
>
> Item was changed:
>   ----- Method: RegisterAllocatingCogit>>simSelfOnStackInReceiverResultReg
> (in category 'bytecode generator support') -----
>   simSelfOnStackInReceiverResultReg
>         "For assert checking only."
> +       methodOrBlockNumTemps to: simStackPtr do:
> -       methodOrBlockNumArgs to: simStackPtr do:
>                 [:i|
>                  (((self addressOf: simSelf) isSameEntryAs: (self
> simStackAt: i))
>                   and: [(self simStackAt: i) registerOrNone =
> ReceiverResultReg]) ifTrue:
>                         [^true]].
>         ^false!
>
> Item was changed:
>   ----- Method: Spur64BitMemoryManager>>fetchClassTagOf: (in category
> 'interpreter access') -----
>   fetchClassTagOf: oop
> +       <api>
>         | tagBits |
>         ^(tagBits := oop bitAnd: self tagMask) ~= 0
>                 ifTrue: [tagBits]
>                 ifFalse: [self classIndexOf: oop]!
>
> Item was added:
> + ----- Method: SpurPlanningCompactor class>>identify32BitSignedComparisons
> (in category 'analysis') -----
> + identify32BitSignedComparisons
> +       "self identify32BitSignedComparisons"
> +       self identifySignedComparisonsFor: #(ObjectMemory
> Spur32BitMemoryManager)
> +               noise: #('(manager bytesInObject: largestFreeChunk) >=
> spaceEstimate'
> +                               '(self classIndexOf: o*) > self
> isForwardedObjectClassIndexPun'
> +                               'GCModeFull > 0'
> +                               'ReceiverIndex + (objectMemory
> integerValueOf: sp*) < (objectMemory lengthOf: o*)'
> +                               'availableSpace > 0'
> +                               'bytes + 2 * 8 > availableSpace'
> +                               'fmt* < manager firstCompiledMethodFormat'
> +                               'fmt* < self firstCompiledMethodFormat'
> +                               'fmt* <= 5'
> +                               'gcPhaseInProgress > 0'
> +                               'i <= finishIndex'
> +                               'numPointerSlots > 0'
> +                               'scavenger rememberedSetSize > 0')!
>
> Item was added:
> + ----- Method: SpurPlanningCompactor class>>identify64BitSignedComparisons
> (in category 'analysis') -----
> + identify64BitSignedComparisons
> +       "self identify64BitSignedComparisons"
> +       self identifySignedComparisonsFor: #(ObjectMemory
> Spur64BitMemoryManager)
> +               noise: #('(manager bytesInObject: largestFreeChunk) >=
> spaceEstimate'
> +                               '(self classIndexOf: o*) > self
> isForwardedObjectClassIndexPun'
> +                               'GCModeFull > 0'
> +                               'ReceiverIndex + (objectMemory
> integerValueOf: sp*) < (objectMemory lengthOf: o*)'
> +                               'availableSpace > 0'
> +                               'bytes + 2 * 8 > availableSpace'
> +                               'fmt* < manager firstCompiledMethodFormat'
> +                               'fmt* < self firstCompiledMethodFormat'
> +                               'fmt* <= 5'
> +                               'gcPhaseInProgress > 0'
> +                               'i <= finishIndex'
> +                               'numPointerSlots > 0'
> +                               'scavenger rememberedSetSize > 0')!
>
> Item was removed:
> - ----- Method: SpurPlanningCompactor class>>identifySignedComparisons
> (in category 'analysis') -----
> - identifySignedComparisons
> -       "self identifySignedComparisons"
> -       | vmm cg noise |
> -       noise := #('(manager bytesInObject: largestFreeChunk) >=
> spaceEstimate'
> -                               '(self classIndexOf: o*) > self
> isForwardedObjectClassIndexPun'
> -                               'GCModeFull > 0'
> -                               'ReceiverIndex + (objectMemory
> integerValueOf: sp*) < (objectMemory lengthOf: o*)'
> -                               'availableSpace > 0'
> -                               'bytes + 2 * 8 > availableSpace'
> -                               'fmt* < manager firstCompiledMethodFormat'
> -                               'fmt* < self firstCompiledMethodFormat'
> -                               'fmt* <= 5'
> -                               'gcPhaseInProgress > 0'
> -                               'i <= finishIndex'
> -                               'i >= 0'
> -                               'numPointerSlots > 0'
> -                               'scavenger rememberedSetSize > 0').
> -       vmm := (VMMaker forPlatform: 'Cross')
> -                               interpreterClass: StackInterpreter;
> -                               options: #(ObjectMemory
> Spur32BitMemoryManager).
> -       cg := [vmm buildCodeGeneratorForInterpreter]
> -                       on: Notification
> -                       do: [:ex|
> -                               ex tag == #getVMMaker
> -                                       ifTrue: [ex resume: vmm]
> -                                       ifFalse: [ex pass]].
> -       cg vmClass preGenerationHook: cg.
> -       cg inferTypesForImplicitlyTypedVariablesAndMethods.
> -       cg retainMethods: self selectors.
> -       cg prepareMethods.
> -       cg doInlining: true.
> -       self selectors sort do:
> -               [:sel|
> -               (cg methodNamed: sel) ifNotNil:
> -                       [:m|
> -                       m parseTree nodesDo:
> -                               [:node|
> -                               (node isSend
> -                                and: [(#(< > <= >=) includes: node
> selector)
> -                                and: [({node receiver. node args first }
> anySatisfy:
> -                                               [:o| (cg typeFor: o in: m)
> -                                                               ifNil:
> [true]
> -                                                               ifNotNil:
> [:t| (cg isIntegralCType: t) and: [t first ~= $u]]])
> -                                and: [noise noneSatisfy: [:n| n match:
> node printString]]]]) ifTrue:
> -                                       [Transcript ensureCr; nextPutAll:
> sel; space; print: node; flush]]]]!
>
> Item was added:
> + ----- Method: SpurPlanningCompactor class>>identifySignedComparisonsFor:noise:
> (in category 'analysis') -----
> + identifySignedComparisonsFor: options noise: noise
> +       "self identify32BitSignedComparisons"
> +       "self identify64BitSignedComparisons"
> +       | vmm cg |
> +       vmm := (VMMaker forPlatform: 'Cross')
> +                               interpreterClass: StackInterpreter;
> +                               options: options.
> +       cg := [vmm buildCodeGeneratorForInterpreter]
> +                       on: Notification
> +                       do: [:ex|
> +                               ex tag == #getVMMaker
> +                                       ifTrue: [ex resume: vmm]
> +                                       ifFalse: [ex pass]].
> +       cg vmClass preGenerationHook: cg.
> +       cg inferTypesForImplicitlyTypedVariablesAndMethods.
> +       cg retainMethods: self selectors.
> +       cg prepareMethods.
> +       cg doInlining: true.
> +       self selectors sort do:
> +               [:sel|
> +               (cg methodNamed: sel) ifNotNil:
> +                       [:m|
> +                       m parseTree nodesDo:
> +                               [:node|
> +                               (node isSend
> +                                and: [(#(< > <= >=) includes: node
> selector)
> +                                and: [({node receiver. node args first }
> anySatisfy:
> +                                               [:o| (cg typeFor: o in: m)
> +                                                               ifNil:
> [true]
> +                                                               ifNotNil:
> [:t| (cg isIntegralCType: t) and: [t first ~= $u]]])
> +                                and: [noise noneSatisfy: [:n| n match:
> node printString]]]]) ifTrue:
> +                                       [Transcript ensureCr; nextPutAll:
> sel; space; print: node; flush]]]]!
>
> Item was changed:
>   SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
> +       instanceVariableNames: 'prevBCDescriptor numPushNilsFunction
> pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf
> simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs
> ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines
> picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC
> ceCall2ArgsPIC debugStackPointers debugFixupBreaks
> realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs
> deadCode useTwoPaths currentCallCleanUpSize simNativeStack
> simNativeStackPtr simNativeSpillBase simNativeStackSize hasNativeFrame
> compilationPass'
> -       instanceVariableNames: 'prevBCDescriptor numPushNilsFunction
> pushNilSizeFunction methodOrBlockNumTemps regArgsHaveBeenPushed simSelf
> simStack simStackPtr simSpillBase optStatus ceCallCogCodePopReceiverArg0Regs
> ceCallCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines
> picAbortTrampolines picMissTrampolines ceCall0ArgsPIC ceCall1ArgsPIC
> ceCall2ArgsPIC debugStackPointers debugFixupBreaks
> realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverArg1Arg0Regs
> deadCode useTwoPaths currentCallCleanUpSize simNativeStack
> simNativeStackPtr simNativeSpillBase simNativeStackSize hasNativeFrame
> blockPass'
>         classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag'
>         poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants
> VMObjectIndices VMStackFrameOffsets'
>         category: 'VMMaker-JIT'!
>   StackToRegisterMappingCogit class
>         instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!
>
> + !StackToRegisterMappingCogit commentStamp: 'eem 3/3/2017 10:29' prior: 0!
> - !StackToRegisterMappingCogit commentStamp: 'eem 2/9/2017 10:07' prior: 0!
>   StackToRegisterMappingCogit is an optimizing code generator that
> eliminates a lot of stack operations and inlines some special selector
> arithmetic.  It does so by a simple stack-to-register mapping scheme based
> on deferring the generation of code to produce operands until
> operand-consuming operations.  The operations that consume operands are
> sends, stores and returns.
>
>   See methods in the class-side documentation protocol for more detail.
>
>   Instance Variables
> +       compilationPass:
>               <Integer>
> +       currentCallCleanUpSize:
>  <Integer>
> +       ceCall0ArgsPIC:
>              <Integer>
> +       ceCall1ArgsPIC:
>              <Integer>
> +       ceCall2ArgsPIC:
>              <Integer>
> +       ceCallCogCodePopReceiverArg0Regs:                       <Integer>
> +       ceCallCogCodePopReceiverArg1Arg0Regs:           <Integer>
> +       deadCode
>                       <Boolean>
> -       callerSavedRegMask:
>      <Integer>
> -       ceEnter0ArgsPIC:
>               <Integer>
> -       ceEnter1ArgsPIC:
>               <Integer>
> -       ceEnter2ArgsPIC:
>               <Integer>
> -       ceEnterCogCodePopReceiverArg0Regs:              <Integer>
> -       ceEnterCogCodePopReceiverArg1Arg0Regs:  <Integer>
>         debugBytecodePointers:
> <Set of Integer>
>         debugFixupBreaks:
>              <Set of Integer>
>         debugStackPointers:
>      <CArrayAccessor of (Integer|nil)>
> +       hasNativeFrame
>       <Boolean>
>         methodAbortTrampolines:
>  <CArrayAccessor of Integer>
>         methodOrBlockNumTemps:
> <Integer>
> +       numPushNilsFunction:
>       <Symbol>
>         optStatus:
>                       <Integer>
>         picAbortTrampolines:
>       <CArrayAccessor of Integer>
>         picMissTrampolines:
>      <CArrayAccessor of Integer>
> +       pushNilSizeFunction:
>       <Symbol>
> +       realCECallCogCodePopReceiverArg0Regs:           <Integer>
> +       realCECallCogCodePopReceiverArg1Arg0Regs:       <Integer>
> -       realCEEnterCogCodePopReceiverArg0Regs:          <Integer>
> -       realCEEnterCogCodePopReceiverArg1Arg0Regs:      <Integer>
>         regArgsHaveBeenPushed:
> <Boolean>
> +       simNativeSpillBase:
>              <Integer>
> +       simNativeStack:
>      <CArrayAccessor of CogSimStackNativeEntry>
> +       simNativeStackPtr:
>               <Integer>
> +       simNativeStackSize:
>      <Integer>
>         simSelf:
>                               <CogSimStackEntry>
>         simSpillBase:
>              <Integer>
>         simStack:
>                      <CArrayAccessor of CogSimStackEntry>
>         simStackPtr:
>               <Integer>
>         traceSimStack:
>               <Integer>
>         useTwoPaths
>              <Boolean>
>
> + compilationPass
> +       - counter indicating whether on the first pass through bytecodes
> in a V3-style embedded block or not.  The V3 closure implementation uses
> pushNil to initialize temporary variables and this makes an initial pushNil
> ambiguous.  With the V3 bytecode set, the JIT must compile to the end of
> the block to discover if a pushNil is for initializing a temp or to produce
> an operand.
> - callerSavedRegMask
> -       - the bitmask of the ABI's caller-saved registers
>
> + currentCallCleanUpSize
> +       - the number of bytes to remove from the stack in a Lowcode call.
> +
> + ceCall0ArgsPIC ceCall1ArgsPIC ceCall2ArgsPIC
> - ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
>         - the trampoline for entering an N-arg PIC
>
> + ceCallCogCodePopReceiverArg0Regs ceCallCogCodePopReceiverArg1Arg0Regs
> +       - the trampoline for invokinging a method with N register args
> - ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
> -       - the trampoline for entering a method with N register args
>
>   debugBytecodePointers
>         - a Set of bytecode pcs for setting breakpoints (simulation only)
>
> + deadCode
> +       - set to true to indicate that the next bytecode (up to the next
> fixup) is not reachable.  Used to avoid generating dead code.
> +
>   debugFixupBreaks
>         - a Set of fixup indices for setting breakpoints (simulation only)
>
>   debugStackPointers
>         - an Array of stack depths for each bytecode for code verification
>
> + hasNativeFrame
> +       - set to true when Lowcode creates a native stack frame for
> Lowcode callouts.
> +
>   methodAbortTrampolines
>         - a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
>
>   methodOrBlockNumTemps
>         - the number of method or block temps (including args) in the
> current compilation unit (method or block)
>
>   optStatus
>         - the variable used to track the status of ReceiverResultReg for
> avoiding reloading that register with self between adjacent inst var
> accesses
>
> + numPushNilsFunction
> +       - the function used to determine the number of push nils at the
> beginning of a block.  This abstracts away from the specific bytecode
> set(s).
> +
>   picAbortTrampolines
>         - a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
>
>   picMissTrampolines
>         - a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
>
> + pushNilSizeFunction
> +       - the function used to determine the number of bytes in the push
> nils bytecode(s) at the beginning of a block.  This abstracts away from the
> specific bytecode set(s).
> - realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverA
> rg1Arg0Regs
> -       - the real trampolines for ebtering machine code with N reg args
> when in the Debug regime
>
> + realCECallCogCodePopReceiverArg0Regs realCECallCogCodePopReceiverAr
> g1Arg0Regs
> +       - the real trampolines for invoking machine code with N reg args
> when in the Debug regime
> +
>   regArgsHaveBeenPushed
>         - whether the register args have been pushed before frame build
> (e.g. when an interpreter primitive is called)
>
> + simNativeSpillBase
> +       - the variable tracking how much of the Lowcode simulation stack
> has been spilled to the real stack
> +
> + simNativeStack
> +       - the Lowcode simulation stack itself
> +
> + simNativeStackPtr
> +       - the pointer to the top of the Lowcode simulation stack
> +
> + simNativeStackSize
> +       - the size of the Lowcode stack so far
> +
>   simSelf
>         - the simulation stack entry representing self in the current
> compilation unit
>
>   simSpillBase
>         - the variable tracking how much of the simulation stack has been
> spilled to the real stack
>
>   simStack
>         - the simulation stack itself
>
>   simStackPtr
>         - the pointer to the top of the simulation stack
>
>   useTwoPaths
>         - a variable controlling whether to create two paths through a
> method based on the existence of inst var stores.  With immutability this
> causes a frameless path to be generated if an otherwise frameless method is
> frameful simply because of inst var stores.  In this case the test to take
> the first frameless path is if the receiver is not immutable.  Without
> immutability, if a frameless method contains two or more inst var stores,
> the first path will be code with no store check, chosen by a single check
> for the receiver being in new space.
>   !
>   StackToRegisterMappingCogit class
>         instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>compileBlockBodies (in
> category 'compile abstract instructions') -----
>   compileBlockBodies
>         <inline: false>
>         | result compiledBlocksCount blockStart savedNeedsFrame
> savedNumArgs savedNumTemps
>           initialStackPtr initialOpcodeIndex initialIndexOfIRC
> initialCounterIndex |
>         <var: #blockStart type: #'BlockStart *'>
>         self assert: blockCount > 0.
>         "scanBlock: in compileBlockEntry: sets both of these appropriately
> for each block."
>         savedNeedsFrame := needsFrame.
>         savedNumArgs := methodOrBlockNumArgs.
>         savedNumTemps := methodOrBlockNumTemps.
>         inBlock := InVanillaBlock.
>         compiledBlocksCount := 0.
>         [compiledBlocksCount < blockCount] whileTrue:
> +               [compilationPass := 1.
> -               [blockPass := 1.
>                  blockStart := self blockStartAt: compiledBlocksCount.
>                  (result := self scanBlock: blockStart) < 0 ifTrue:
> [^result].
>                  initialOpcodeIndex := opcodeIndex.
>                  initialCounterIndex := self maybeCounterIndex."for
> SistaCogit"
> +                literalsManager saveForRecompile.
> -                literalsManager saveForBlockCompile.
>                  NewspeakVM ifTrue:
>                         [initialIndexOfIRC := indexOfIRC].
>                  [self compileBlockEntry: blockStart.
>                   initialStackPtr := simStackPtr.
>                   (result := self compileAbstractInstructionsFrom:
> blockStart startpc + (self pushNilSize: methodObj numInitialNils:
> blockStart numInitialNils)
>                                                 through: blockStart
> startpc + blockStart span - 1) < 0 ifTrue:
>                         [^result].
>                   "If the final simStackPtr is less than the initial
> simStackPtr then scanBlock: over-
>                    estimated the number of initial nils (because it
> assumed one or more pushNils to
>                    produce an operand were pushNils to initialize temps.
> This is very rare, so
>                    compensate by checking, adjusting numInitialNils and
> recompiling the block body.
>                    N.B.  No need to reinitialize the literalsManager
> because it answers existing literals."
>                   initialStackPtr = simStackPtr]
>                         whileFalse:
>                                 [self assert: (initialStackPtr >
> simStackPtr or: [deadCode]).
> +                                compilationPass := compilationPass + 1.
> "for asserts"
> -                                blockPass := blockPass + 1. "for asserts
> :-("
>                                  blockStart numInitialNils: blockStart
> numInitialNils + simStackPtr - initialStackPtr.
>                                  blockStart fakeHeader dependent: nil.
>                                  self reinitializeFixupsFrom: blockStart
> startpc + blockStart numInitialNils
>                                         through: blockStart startpc +
> blockStart span - 1.
>                                  self cCode: 'bzero(abstractOpcodes +
> initialOpcodeIndex,
>
> (opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'
>                                         inSmalltalk: [initialOpcodeIndex
> to: opcodeIndex - 1 do:
>
> [:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].
>                                  opcodeIndex := initialOpcodeIndex.
>                                  self maybeSetCounterIndex:
> initialCounterIndex. "For SistaCogit"
> +                                literalsManager resetForRecompile.
> -                                literalsManager resetForBlockCompile.
>                                  NewspeakVM ifTrue:
>                                         [indexOfIRC := initialIndexOfIRC]].
>                 compiledBlocksCount := compiledBlocksCount + 1].
>         needsFrame := savedNeedsFrame.
>         methodOrBlockNumArgs := savedNumArgs.
>         methodOrBlockNumTemps := savedNumTemps.
>         ^0!
>
> Item was added:
> + ----- Method: StackToRegisterMappingCogit>>initializeFixup: (in
> category 'compile abstract instructions') -----
> + initializeFixup: fixup
> +       "Initialize a fixup.  These are the targets of backward branches.
> A backward branch fixup's
> +        simStackPtr needs to be set when generating the code for the
> bytecode at the targetPC.
> +        Initially a fixup's target is just a flag.  Later on it is
> replaced with a proper instruction."
> +       <var: #fixup type: #'BytecodeFixup *'>
> +       <inline: true>
> +       fixup
> +               becomeMergeFixup;
> +               setIsBackwardBranchFixup!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>initializeFixupAt: (in
> category 'compile abstract instructions') -----
>   initializeFixupAt: targetPC
>         "Make sure there's a flagged fixup at the targetPC in fixups.
> +        These are the targets of backward branches.  A backward branch
> fixup's simStackPtr
> -        These are the targets  of backward branches.  A backward branch
> fixup's simStackPtr
>          needs to be set when generating the code for the bytecode at the
> targetPC.
>          Initially a fixup's target is just a flag.  Later on it is
> replaced with a proper instruction."
> -       <returnTypeC: #'BytecodeFixup *'>
>         | fixup |
> -       <var: #fixup type: #'BytecodeFixup *'>
>         fixup := self fixupAt: targetPC.
> +       self initializeFixup: fixup!
> -       fixup
> -               becomeMergeFixup;
> -               setIsBackwardBranchFixup.
> -       ^fixup!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>
> maybeCompilingFirstPassOfBlockWithInitialPushNil (in category
> 'debugging') -----
>   maybeCompilingFirstPassOfBlockWithInitialPushNil
>         "For assert checking; or rather for avoiding assert fails when
> dealing with the hack for block temps in the SqueakV3PlusClosures bytecode
> set."
> +       ^inBlock = InVanillaBlock and: [methodOrBlockNumTemps >
> methodOrBlockNumArgs and: [compilationPass = 1]]!
> -       ^inBlock = InVanillaBlock and: [methodOrBlockNumTemps >
> methodOrBlockNumArgs and: [blockPass = 1]]!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>ssFlushAll (in category
> 'simulation stack') -----
>   ssFlushAll
> +       <inline: true>
>         self ssFlushTo: simStackPtr nativeFlushTo: simNativeStackPtr!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>ssFlushTo: (in category
> 'simulation stack') -----
>   ssFlushTo: index
> +       <inline: true>
>         self ssFlushTo: index nativeFlushTo: simNativeStackPtr.!
>
> Item was changed:
>   ----- Method: StackToRegisterMappingCogit>>traceMerge: (in category
> 'simulation only') -----
>   traceMerge: fixup
>         <cmacro: '(ign) 0'>
> +       | index original |
> -       | index |
>         (compilationTrace anyMask: 16) ifTrue:
>                 [index := (fixups object identityIndexOf: fixup) - 1.
> +                (fixup isBackwardBranchFixup and: [compilationPass > 1
> and: [(original := fixup simStackPtr) < 0]]) ifTrue:
> +                       [fixup simStackPtr: simStackPtr].
> +
> +                [coInterpreter transcript
> +                               ensureCr;
> +                               print: index; nextPut: $/; print: index +
> initialPC;
> +                               nextPut: $:; space.
> +                               fixup printStateOn: coInterpreter
> transcript.
> +                               coInterpreter transcript cr; flush]
> +                       ensure: [original ifNotNil: [fixup simStackPtr:
> original]]]!
> -                coInterpreter transcript
> -                       ensureCr;
> -                       print: index; nextPut: $/; print: index +
> initialPC;
> -                       nextPut: $:; space.
> -                       fixup printStateOn: coInterpreter transcript.
> -                       coInterpreter transcript cr; flush]!
>
> Item was changed:
>   ----- Method: VMStructType class>>printTypedefOn: (in category
> 'translation') -----
>   printTypedefOn: aStream
>         aStream nextPutAll: 'typedef struct '.
>         self needsTypeTag ifTrue:
>                 [aStream nextPutAll: self structTagName; space].
>         aStream nextPut: ${; cr.
>         self instVarNamesAndTypesForTranslationDo:
>                 [:ivn :typeArg| | type |
> +               ivn first == $#
> +                       ifTrue: [aStream nextPutAll: ivn]
> +                       ifFalse:
> +                               [type := typeArg.
> +                                #(BytesPerWord BaseHeaderSize
> BytesPerOop) do:
> +                                       [:sizeConstant| | index
> sizeConstantSize |
> +                                       (type notNil
> +                                       and: [(index := type indexOf:
> sizeConstant ifAbsent: 0) > 0]) ifTrue:
> +                                               [sizeConstantSize  :=
> VMBasicConstants classPool at: sizeConstant.
> +                                               type := (type at: index +
> 1) = sizeConstantSize ifTrue:
> +
>  [type := type copyReplaceFrom: index to: index + 1 with: #().
> +
> type size = 1 ifTrue: [type first] ifFalse: [type]]]].
> +                                type ifNotNil:
> +                                       [type isArray
> +                                               ifTrue:
> +                                                       [aStream tab: 1.
> +                                                        aStream
> nextPutAll: type first.
> +                                                        (type first last
> isSeparator or: [type first last = $*]) ifFalse:
> +                                                               [aStream
> tab: 2].
> +                                                        aStream
> nextPutAll: ivn.
> +                                                        type last first
> isSeparator ifFalse:
> +                                                               [aStream
> space].
> +                                                        aStream
> nextPutAll: type last]
> +                                               ifFalse:
> +                                                       [aStream tab: 1.
> +                                                        aStream
> nextPutAll: type.
> +                                                        (type last
> isSeparator or: [type last = $*]) ifFalse:
> +                                                               [aStream
> tab: 1].
> +                                                        aStream
> nextPutAll: ivn]].
> +                                aStream nextPut: $;].
> +                aStream cr].
> -               type := typeArg.
> -               #(BytesPerWord BaseHeaderSize BytesPerOop) do:
> -                       [:sizeConstant| | index sizeConstantSize |
> -                       (type notNil
> -                       and: [(index := type indexOf: sizeConstant
> ifAbsent: 0) > 0]) ifTrue:
> -                               [sizeConstantSize  := VMBasicConstants
> classPool at: sizeConstant.
> -                               type := (type at: index + 1) =
> sizeConstantSize ifTrue:
> -                                                       [type := type
> copyReplaceFrom: index to: index + 1 with: #().
> -                                                        type size = 1
> ifTrue: [type first] ifFalse: [type]]]].
> -               type ifNotNil:
> -                       [type isArray
> -                               ifTrue:
> -                                       [aStream tab: 1.
> -                                        aStream nextPutAll: type first.
> -                                        (type first last isSeparator or:
> [type first last = $*]) ifFalse:
> -                                               [aStream tab: 2].
> -                                        aStream nextPutAll: ivn.
> -                                        type last first isSeparator
> ifFalse:
> -                                               [aStream space].
> -                                        aStream
> -                                               nextPutAll: type last;
> -                                               nextPut: $;;
> -                                               cr]
> -                               ifFalse:
> -                                       [aStream tab: 1.
> -                                        aStream nextPutAll: type.
> -                                        (type last isSeparator or: [type
> last = $*]) ifFalse:
> -                                               [aStream tab: 1].
> -                                        aStream
> -                                               nextPutAll: ivn;
> -                                               nextPut: $;;
> -                                               cr]]].
>         aStream
>                 nextPutAll: ' } ';
>                 nextPutAll: self structTypeName;
>                 nextPut: $;;
>                 cr.
>         self name ~= self structTypeName ifTrue:
>                 [(self withAllSuperclasses copyUpThrough: (self class
> whichClassIncludesSelector: #structTypeName) theNonMetaClass) do:
>                         [:structClass|
>                          aStream cr; nextPutAll: '#define '; nextPutAll:
> structClass name; space; nextPutAll: self structTypeName].
>                  aStream cr].
>         aStream flush!
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20170306/19fa766b/attachment-0001.html>


More information about the Vm-dev mailing list