<div dir="ltr">Hi Eliot,<div><br></div><div>With this commit I got the following compilation error on Mac OS X 64. I made a quick fix by replacing the case into ifTrue:iFalse:</div><div><br></div><div><div>../../spur64src/vm/cogitX64.c:29060:4: error: statement requires expression of integer type ('sqInt (*)(void)' (aka 'long (*)(void)') invalid)</div><div>                        switch ((descriptor->generator)) {</div><div>                        ^       ~~~~~~~~~~~~~~~~~~~~~~~</div><div>../../spur64src/vm/cogitX64.c:29061:9: error: expression is not an integer constant expression</div><div>                        case genPushConstantTrueBytecode:</div><div>                             ^~~~~~~~~~~~~~~~~~~~~~~~~~~</div><div>../../spur64src/vm/cogitX64.c:29064:9: error: expression is not an integer constant expression</div><div>                        case genPushConstantFalseBytecode:</div></div><div><br></div><div>(spur64src because I am using the Pharo branch, where I can load the LowcodeOpalCompiler for testing)</div><div><br></div><div>Best regards,</div><div>Ronie</div></div><div class="gmail_extra"><br><div class="gmail_quote">2017-01-17 1:21 GMT-03:00  <span dir="ltr"><<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>></span>:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"> <br>Eliot Miranda uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2094.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/<wbr>VMMaker/VMMaker.oscog-eem.<wbr>2094.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-eem.2094<br>
Author: eem<br>
Time: 16 January 2017, 8:20:54.697006 pm<br>
UUID: 69b76ffe-68d9-423c-a3a7-<wbr>546a6bbb3110<br>
Ancestors: VMMaker.oscog-rsf.2093<br>
<br>
StackToRegisterMappingCogit:<br>
Follow jumps to jumps and push: aBoolean; jump:if:s, eliminating dead code.<br>
<br>
Elimnate jumps to the immediately following instruction in StackToRegisterMappingCogit>><wbr>generateInstructionsAt:.<br>
<br>
Neaten the simulation-only breakpointing for bytecode and machine code pcs.  Add suport for breakPC during in-image compilation.<br>
<br>
=============== Diff against VMMaker.oscog-rsf.2093 ===============<br>
<br>
Item was changed:<br>
  ----- Method: Cogit class>>testPCMappingSelect:<wbr>options: (in category 'tests') -----<br>
  testPCMappingSelect: aBlock options: optionsDictionaryOrArray<br>
        "Test pc mapping both ways using a selection of the methods in the current image."<br>
+       | n cogit coInterpreter |<br>
-       | cogit coInterpreter |<br>
        cogit := self instanceForTests: optionsDictionaryOrArray.<br>
        coInterpreter := CurrentImageCoInterpreterFacad<wbr>e forCogit: cogit.<br>
        [cogit<br>
                        setInterpreter: coInterpreter;<br>
                        singleStep: true;<br>
                        initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size]<br>
                on: Notification<br>
                do: [:ex|<br>
                        (ex messageText beginsWith: 'cannot find receiver for') ifTrue:<br>
                                [ex resume: coInterpreter]].<br>
+       n := -1.<br>
        SystemNavigation new allSelect:<br>
                [:m| | cm |<br>
                (m isQuick not<br>
                 and: [aBlock value: m]) ifTrue:<br>
+                       [(n := n + 1) \\ 10 = 0 ifTrue: [Transcript nextPut: $.; flush].<br>
-                       [Transcript nextPut: $.; flush.<br>
                         cm := cogit<br>
                                                cog: (coInterpreter oopForObject: m)<br>
                                                selector: (coInterpreter oopForObject: m selector).<br>
                          cm ifNil:<br>
                                [cogit methodZone clearCogCompiledCode.<br>
                                 coInterpreter initializeObjectMap.<br>
                                 cm := cogit<br>
                                                        cog: (coInterpreter oopForObject: m)<br>
                                                        selector: (coInterpreter oopForObject: m selector).<br>
                                cm ifNil: [Transcript show: 'After 1 Cog compiled code compaction, still not able to generate the cog method...' ] ].<br>
                          cm ifNotNil:<br>
                                [cogit testPCMappingForCompiledMethod<wbr>: m cogMethod: cm]].<br>
                 false] !<br>
<br>
Item was changed:<br>
  ----- Method: Cogit>><wbr>compileAbstractInstructionsFro<wbr>m:through: (in category 'compile abstract instructions') -----<br>
  compileAbstractInstructionsFro<wbr>m: start through: end<br>
        "Loop over bytecodes, dispatching to the generator for each bytecode, handling fixups in due course."<br>
        | nextOpcodeIndex descriptor fixup result nExts |<br>
        <var: #descriptor type: #'BytecodeDescriptor *'><br>
        <var: #fixup type: #'BytecodeFixup *'><br>
        bytecodePC := start.<br>
        nExts := result := 0.<br>
        descriptor := nil.<br>
+       [self maybeHaltIfDebugPC.<br>
-       [self cCode: '' inSmalltalk: [self isDebugPC ifTrue: [self halt]].<br>
         descriptor := self loadBytesAndGetDescriptor.<br>
         nextOpcodeIndex := opcodeIndex.<br>
         result := self perform: descriptor generator.<br>
         self assertExtsAreConsumed: descriptor.<br>
         fixup := self fixupAt: bytecodePC - initialPC.<br>
         self patchFixupTargetIfNeeded: fixup nextOpcodeIndex: nextOpcodeIndex.<br>
         self maybeDumpLiterals: descriptor.<br>
         bytecodePC := self nextBytecodePCFor: descriptor exts: nExts.<br>
         result = 0 and: [bytecodePC <= end]]<br>
                whileTrue:<br>
                        [nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].<br>
        self checkEnoughOpcodes.<br>
        ^result!<br>
<br>
Item was changed:<br>
  ----- Method: Cogit>>generateInstructionsAt: (in category 'generate machine code') -----<br>
  generateInstructionsAt: eventualAbsoluteAddress<br>
        "Size pc-dependent instructions and assign eventual addresses to all instructions.<br>
         Answer the size of the code.<br>
         Compute forward branches based on virtual address (abstract code starts at 0),<br>
         assuming that any branches branched over are long.<br>
         Compute backward branches based on actual address.<br>
         Reuse the fixups array to record the pc-dependent instructions that need to have<br>
         their code generation postponed until after the others."<br>
        | absoluteAddress pcDependentIndex abstractInstruction fixup |<br>
        <var: #abstractInstruction type: #'AbstractInstruction *'><br>
        <var: #fixup type: #'BytecodeFixup *'><br>
        absoluteAddress := eventualAbsoluteAddress.<br>
        pcDependentIndex := 0.<br>
        0 to: opcodeIndex - 1 do:<br>
                [:i|<br>
+               self maybeBreakGeneratingAt: absoluteAddress.<br>
-               self cCode: [] inSmalltalk: [self maybeBreakGeneratingAt: absoluteAddress].<br>
                abstractInstruction := self abstractInstructionAt: i.<br>
                abstractInstruction isPCDependent<br>
                        ifTrue:<br>
                                [abstractInstruction sizePCDependentInstructionAt: absoluteAddress.<br>
                                 fixup := self fixupAt: pcDependentIndex.<br>
                                 pcDependentIndex := pcDependentIndex + 1.<br>
                                 fixup instructionIndex: i.<br>
                                 absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]<br>
                        ifFalse:<br>
                                [absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].<br>
        0 to: pcDependentIndex - 1 do:<br>
                [:j|<br>
                fixup := self fixupAt: j.<br>
                abstractInstruction := self abstractInstructionAt: fixup instructionIndex.<br>
+               self maybeBreakGeneratingAt: abstractInstruction address.<br>
-               self cCode: [] inSmalltalk: [self maybeBreakGeneratingAt: abstractInstruction address].<br>
                abstractInstruction concretizeAt: abstractInstruction address].<br>
        ^absoluteAddress - eventualAbsoluteAddress!<br>
<br>
Item was removed:<br>
- ----- Method: Cogit>>isDebugPC (in category 'compile abstract instructions') -----<br>
- isDebugPC<br>
-       <doNotGenerate><br>
-       ^ debugBytecodePointers includes: bytecodePC!<br>
<br>
Item was changed:<br>
  ----- Method: Cogit>>maybeBreakGeneratingAt: (in category 'simulation only') -----<br>
  maybeBreakGeneratingAt: address<br>
+       "Variation on maybeBreakAt: that only works for integer breakPCs,<br>
-       "Variation on maybeBreakAt: that inly forks for integer breakPCs,<br>
         so we can have break blocks that stop at any pc, except when generating."<br>
+       <cmacro: '(address) 0'> "Simulation only; void in C"<br>
-       <doNotGenerate><br>
        (breakPC = address<br>
         and: [breakBlock shouldStopIfAtPC: address]) ifTrue:<br>
                [coInterpreter changed: #byteCountText.<br>
                 self halt: 'machine code generation at ', address hex, ' in ', thisContext sender selector]!<br>
<br>
Item was added:<br>
+ ----- Method: Cogit>>maybeHaltIfDebugPC (in category 'compile abstract instructions') -----<br>
+ maybeHaltIfDebugPC<br>
+       <cmacro: '0'> "Simulation only; void in C"<br>
+       (debugBytecodePointers includes: bytecodePC) ifTrue:<br>
+               [self halt]!<br>
<br>
Item was changed:<br>
  ----- Method: Cogit>>setInterpreter: (in category 'initialization') -----<br>
  setInterpreter: aCoInterpreter<br>
        "Initialization of the code generator in the simulator.<br>
         These objects already exist in the generated C VM<br>
         or are used only in the simulation."<br>
        <doNotGenerate><br>
        coInterpreter := aCoInterpreter.<br>
        objectMemory := aCoInterpreter objectMemory.<br>
        threadManager := aCoInterpreter threadManager. "N.B. may be nil"<br>
        methodZone := CogMethodZone new.<br>
        objectRepresentation := objectMemory objectRepresentationClass<br>
                                                                forCogit: self methodZone: methodZone.<br>
        methodZone setInterpreter: aCoInterpreter<br>
                                objectRepresentation: objectRepresentation<br>
                                cogit: self.<br>
        generatorTable := self class generatorTable.<br>
        processor := ProcessorClass new.<br>
        simulatedAddresses := Dictionary new.<br>
        simulatedTrampolines := Dictionary new.<br>
        simulatedVariableGetters := Dictionary new.<br>
        simulatedVariableSetters := Dictionary new.<br>
        traceStores := 0.<br>
        traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])<br>
                                        ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"<br>
                                        ifFalse: [0].<br>
        debugPrimCallStackOffset := 0.<br>
        singleStep := printRegisters := printInstructions := clickConfirm := false.<br>
        backEnd := CogCompilerClass for: self.<br>
        methodLabel := CogCompilerClass for: self.<br>
        (literalsManager := backEnd class literalsManagerClass new) cogit: self.<br>
        ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).<br>
        superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).<br>
        BytecodeSetHasDirectedSuperSen<wbr>d ifTrue:<br>
                [directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].<br>
        NewspeakVM ifTrue:<br>
                [selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).<br>
                dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).<br>
                implicitReceiverSendTrampoline<wbr>s := CArrayAccessor on: (Array new: NumSendTrampolines).<br>
                outerSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].<br>
        "debug metadata"<br>
        objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).<br>
        runtimeObjectRefIndex := 0.<br>
        "debug metadata"<br>
        trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).<br>
        trampolineTableIndex := 0.<br>
<br>
        extA := numExtB := extB := 0.<br>
<br>
        compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].<br>
        debugOpcodeIndices := self class initializationOptions at: #debugOpcodeIndices ifAbsent: [Set new].<br>
+       debugBytecodePointers := self class initializationOptions at: #debugBytecodePointers ifAbsent: [Set new].<br>
+       self class initializationOptions at: #breakPC ifPresent: [:pc| breakPC := pc]!<br>
-       debugBytecodePointers := self class initializationOptions at: #debugBytecodePointers ifAbsent: [Set new]!<br>
<br>
Item was changed:<br>
  ----- Method: RegisterAllocatingCogit>><wbr>genJumpIf:to: (in category 'bytecode generator support') -----<br>
  genJumpIf: boolean to: targetBytecodePC<br>
        <inline: false><br>
+       | eventualTarget desc reg fixup ok |<br>
-       | desc reg fixup ok |<br>
        <var: #desc type: #'CogSimStackEntry *'><br>
        <var: #fixup type: #'BytecodeFixup *'><br>
        <var: #ok type: #'AbstractInstruction *'><br>
+       eventualTarget := self eventualTargetOf: targetBytecodePC.<br>
        desc := self ssTop.<br>
        self ssPop: 1.<br>
        (desc type == SSConstant<br>
         and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:<br>
                ["Must arrange there's a fixup at the target whether it is jumped to or<br>
                  not so that the simStackPtr can be kept correct."<br>
+                fixup := self ensureFixupAt: eventualTarget - initialPC.<br>
-                fixup := self ensureFixupAt: targetBytecodePC - initialPC.<br>
                 "Must annotate the bytecode for correct pc mapping."<br>
                 self annotateBytecode: (desc constant = boolean<br>
                                                                        ifTrue: [self Jump: fixup]<br>
                                                                        ifFalse: [self prevInstIsPCAnnotated<br>
                                                                                                ifTrue: [self Nop]<br>
                                                                                                ifFalse: [self Label]]).<br>
                 extA := 0.<br>
                 ^0].<br>
        "try and use the top entry's register if anty, but only if it can be destroyed."<br>
        reg := (desc type ~= SSRegister<br>
                        or: [(self anyReferencesToRegister: desc register inAllButTopNItems: 0)<br>
                        or: [(desc register = ReceiverResultReg and: [optStatus isReceiverResultRegLive])]])<br>
                                ifTrue: [TempReg]<br>
                                ifFalse: [desc register].<br>
        desc popToReg: reg.<br>
        "Cunning trick by LPD.  If true and false are contiguous subtract the smaller.<br>
         Correct result is either 0 or the distance between them.  If result is not 0 or<br>
         their distance send mustBeBoolean."<br>
        self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.<br>
        self genSubConstant: boolean R: reg.<br>
+       self JumpZero: (self ensureFixupAt: eventualTarget - initialPC).<br>
-       self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).<br>
<br>
        self extASpecifiesNoMustBeBoolean ifTrue:<br>
                [extA := 0.<br>
                 self annotateBytecode: self lastOpcode.<br>
                 ^0].<br>
        extA := 0.<br>
<br>
  .     self CmpCq: (boolean = objectMemory falseObject<br>
                                        ifTrue: [objectMemory trueObject - objectMemory falseObject]<br>
                                        ifFalse: [objectMemory falseObject - objectMemory trueObject])<br>
                R: reg.<br>
        ok := self JumpZero: 0.<br>
        reg ~= TempReg ifTrue:<br>
                [self MoveR: reg R: TempReg].<br>
        self copySimStackToScratch: simSpillBase.<br>
        self ssFlushTo: simStackPtr.<br>
        self genCallMustBeBooleanFor: boolean.<br>
        "NOTREACHED"<br>
        ok jmpTarget: (self annotateBytecode: self Label).<br>
        self restoreSimStackFromScratch.<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: RegisterAllocatingCogit>><wbr>genJumpTo: (in category 'bytecode generator support') -----<br>
  genJumpTo: targetBytecodePC<br>
        "Overriden to avoid the flush because in this cogit stack state is merged at merge point."<br>
        deadCode := true. "can't fall through"<br>
+       self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC) - initialPC).<br>
-       self Jump: (self ensureFixupAt: targetBytecodePC - initialPC).<br>
        ^ 0!<br>
<br>
Item was changed:<br>
  ----- Method: SistaCogit>>genJumpIf:to: (in category 'bytecode generator support') -----<br>
  genJumpIf: boolean to: targetBytecodePC<br>
        "The heart of performance counting in Sista.  Conditional branches are 6 times less<br>
         frequent than sends and can provide basic block frequencies (send counters can't).<br>
         Each conditional has a 32-bit counter split into an upper 16 bits counting executions<br>
         and a lower half counting untaken executions of the branch.  Executing the branch<br>
         decrements the upper half, tripping if the count goes negative.  Not taking the branch<br>
         decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)<br>
         so that scanning for send and branch data is simplified and that branch data is correct."<br>
        <inline: false><br>
+       | ok counterAddress countTripped retry nextPC nextDescriptor desc eventualTarget |<br>
-       | ok counterAddress countTripped retry nextPC nextDescriptor desc |<br>
        <var: #ok type: #'AbstractInstruction *'><br>
        <var: #desc type: #'CogSimStackEntry *'><br>
        <var: #retry type: #'AbstractInstruction *'><br>
        <var: #countTripped type: #'AbstractInstruction *'><br>
        <var: #nextDescriptor type: #'BytecodeDescriptor *'><br>
<br>
        "In optimized code we don't generate counters to improve performance"<br>
        (coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].<br>
<br>
        "If the branch is reached only for the counter trip trampoline<br>
        (typically, var1 == var2 ifTrue: falls through to the branch only for the trampoline)<br>
        we generate a specific path to drastically reduce the number of machine instructions"<br>
        branchReachedOnlyForCounterTri<wbr>p ifTrue:<br>
                [ branchReachedOnlyForCounterTri<wbr>p := false.<br>
                ^ self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC ].<br>
<br>
        "We detect and: / or:, if found, we don't generate the counters to avoid pathological counter slow down"<br>
        boolean = objectMemory falseObject ifTrue:<br>
                [ nextPC := bytecodePC + (self generatorAt: byte0) numBytes.<br>
                  nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.<br>
                  nextDescriptor generator ==  #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].<br>
                  nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset.<br>
                  nextDescriptor generator == #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].  ].<br>
<br>
        extA := 0. "We ignore the noMustBeBoolean flag. It should not be present in methods with counters, and if it is we don't care."<br>
<br>
        "We don't generate counters on branches on true/false, the basicblock usage can be inferred"<br>
        desc := self ssTop.<br>
        (desc type == SSConstant<br>
         and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:<br>
                [ ^ super genJumpIf: boolean to: targetBytecodePC ].<br>
+<br>
+       eventualTarget := self eventualTargetOf: targetBytecodePC.<br>
+<br>
-<br>
        self ssFlushTo: simStackPtr - 1.<br>
        desc popToReg: TempReg.<br>
        self ssPop: 1.<br>
<br>
        "We need SendNumArgsReg because of the mustBeBooleanTrampoline"<br>
        self ssAllocateRequiredReg: SendNumArgsReg.<br>
<br>
        retry := self Label.<br>
        self<br>
                genExecutionCountLogicInto: [ :cAddress :countTripBranch |<br>
                        counterAddress := cAddress.<br>
                        countTripped := countTripBranch ]<br>
                counterReg: SendNumArgsReg.<br>
        counterIndex := counterIndex + 1.<br>
<br>
        "Cunning trick by LPD.  If true and false are contiguous subtract the smaller.<br>
         Correct result is either 0 or the distance between them.  If result is not 0 or<br>
         their distance send mustBeBoolean."<br>
        self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.<br>
        self genSubConstant: boolean R: TempReg.<br>
+       self JumpZero: (self ensureFixupAt: eventualTarget - initialPC).<br>
-       self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).<br>
<br>
        self genFallsThroughCountLogicCount<wbr>erReg: SendNumArgsReg counterAddress: counterAddress.<br>
<br>
        self CmpCq: (boolean = objectMemory falseObject<br>
                                        ifTrue: [objectMemory trueObject - objectMemory falseObject]<br>
                                        ifFalse: [objectMemory falseObject - objectMemory trueObject])<br>
                R: TempReg.<br>
        ok := self JumpZero: 0.<br>
        self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."<br>
<br>
        countTripped jmpTarget: (self genCallMustBeBooleanFor: boolean).<br>
<br>
        "If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:<br>
         trampoline will return directly to machine code, returning the boolean.  So the code should<br>
         jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."<br>
<br>
        "Clément: For some reason if I write self annotateBytecode: (self Jump: retry) the annotation is not at the correct place."<br>
        "Eliot: Annotations apply the the address following an instruction, and the annotation must be for the return address<br>
         of the call (since this is the address the run-time sees), so it must be on a label before the jump, not after the jump."<br>
        self annotateBytecode: self Label.<br>
        self Jump: retry.<br>
<br>
        ok jmpTarget: self Label.<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: SistaRegisterAllocatingCogit>><wbr>genJumpIf:to: (in category 'bytecode generator support') -----<br>
  genJumpIf: boolean to: targetBytecodePC<br>
        "The heart of performance counting in Sista.  Conditional branches are 6 times less<br>
         frequent than sends and can provide basic block frequencies (send counters can't).<br>
         Each conditional has a 32-bit counter split into an upper 16 bits counting executions<br>
         and a lower half counting untaken executions of the branch.  Executing the branch<br>
         decrements the upper half, tripping if the count goes negative.  Not taking the branch<br>
         decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)<br>
         so that scanning for send and branch data is simplified and that branch data is correct."<br>
        <inline: false><br>
+       | ok counterAddress countTripped retry nextPC nextDescriptor desc eventualTarget reg |<br>
-       | ok counterAddress countTripped retry nextPC nextDescriptor desc reg |<br>
        <var: #ok type: #'AbstractInstruction *'><br>
        <var: #desc type: #'CogSimStackEntry *'><br>
        <var: #retry type: #'AbstractInstruction *'><br>
        <var: #countTripped type: #'AbstractInstruction *'><br>
        <var: #nextDescriptor type: #'BytecodeDescriptor *'><br>
<br>
        "In optimized code we don't generate counters to improve performance"<br>
        (coInterpreter isOptimizedMethod: methodObj) ifTrue:<br>
                [^super genJumpIf: boolean to: targetBytecodePC].<br>
<br>
        "If the branch is reached only for the counter trip trampoline<br>
        (typically, var1 == var2 ifTrue: falls through to the branch only for the trampoline)<br>
        we generate a specific path to drastically reduce the number of machine instructions"<br>
        branchReachedOnlyForCounterTri<wbr>p ifTrue:<br>
                [<wbr>branchReachedOnlyForCounterTri<wbr>p := false.<br>
                 ^self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC].<br>
<br>
        "We detect and: / or:, if found, we don't generate the counters to avoid pathological counter slow down"<br>
        boolean = objectMemory falseObject ifTrue:<br>
                [ nextPC := bytecodePC + (self generatorAt: byte0) numBytes.<br>
                  nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.<br>
                  nextDescriptor generator ==  #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].<br>
                  nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset.<br>
                  nextDescriptor generator == #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. ].<br>
<br>
        extA := 0. "We ignore the noMustBeBoolean flag. It should not be present in methods with counters, and if it is we don't care."<br>
<br>
        "We don't generate counters on branches on true/false, the basicblock usage can be inferred"<br>
        desc := self ssTop.<br>
        (desc type == SSConstant<br>
         and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:<br>
                [ ^ super genJumpIf: boolean to: targetBytecodePC ].<br>
<br>
+       eventualTarget := self eventualTargetOf: targetBytecodePC.<br>
+<br>
        self flag: 'Because of the restriction on x64 that absolute loads must target %rax, it would perhaps be a better choice to use TempReg (%rax) for the counter reg and SendNumArgsReg for the boolean.'.<br>
        "try and use the top entry's register if ant, but only if it can be destroyed."<br>
        reg := (desc type ~= SSRegister<br>
                        or: [(self anyReferencesToRegister: desc register inAllButTopNItems: 0)<br>
                        or: [(desc register = ReceiverResultReg and: [optStatus isReceiverResultRegLive])]])<br>
                                ifTrue: [TempReg]<br>
                                ifFalse: [desc register].<br>
        desc popToReg: reg.<br>
        self ssPop: 1.<br>
<br>
        "We need SendNumArgsReg because of the mustBeBooleanTrampoline"<br>
        self ssAllocateRequiredReg: SendNumArgsReg.<br>
<br>
        retry := self Label.<br>
        self<br>
                genExecutionCountLogicInto: [ :cAddress :countTripBranch |<br>
                        counterAddress := cAddress.<br>
                        countTripped := countTripBranch ]<br>
                counterReg: SendNumArgsReg.<br>
        counterIndex := counterIndex + 1.<br>
<br>
        "Cunning trick by LPD.  If true and false are contiguous subtract the smaller.<br>
         Correct result is either 0 or the distance between them.  If result is not 0 or<br>
         their distance send mustBeBoolean."<br>
        self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.<br>
        self genSubConstant: boolean R: reg.<br>
+       self JumpZero: (self ensureFixupAt: eventualTarget - initialPC).<br>
-       self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).<br>
<br>
        self genFallsThroughCountLogicCount<wbr>erReg: SendNumArgsReg counterAddress: counterAddress.<br>
<br>
        self CmpCq: (boolean = objectMemory falseObject<br>
                                        ifTrue: [objectMemory trueObject - objectMemory falseObject]<br>
                                        ifFalse: [objectMemory falseObject - objectMemory trueObject])<br>
                R: reg.<br>
        ok := self JumpZero: 0.<br>
        self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."<br>
        reg ~= TempReg ifTrue:<br>
                [self MoveR: reg R: TempReg].<br>
        countTripped jmpTarget: self Label.<br>
        self copySimStackToScratch: simSpillBase.<br>
        self ssFlushTo: simStackPtr.<br>
        self genCallMustBeBooleanFor: boolean.<br>
<br>
        "If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped: trampoline<br>
         will return directly to machine code, returning the boolean.  So the code should jump back to the<br>
         retry point. The trampoline preserves register state when taking the ceCounterTripped: path."<br>
        "Clément: For some reason if I write self annotateBytecode: (self Jump: retry) the annotation is not at the correct place."<br>
        "Eliot: Annotations apply the the address following an instruction, and the annotation must be for the return address<br>
         of the call (since this is the address the run-time sees), so it must be on a label before the jump, not after the jump."<br>
        self annotateBytecode: self Label.<br>
        simSpillBase ~= scratchSpillBase ifTrue:<br>
                [self assert: simSpillBase > scratchSpillBase.<br>
                 self AddCq: simSpillBase - scratchSpillBase * objectMemory wordSize R: SPReg].<br>
        self Jump: retry.<br>
<br>
        ok jmpTarget: self Label.<br>
        self restoreSimStackFromScratch.<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: StackToRegisterMappingCogit>><wbr>compileAbstractInstructionsFro<wbr>m:through: (in category 'compile abstract instructions') -----<br>
  compileAbstractInstructionsFro<wbr>m: start through: end<br>
        "Loop over bytecodes, dispatching to the generator for each bytecode, handling fixups in due course."<br>
        | nextOpcodeIndex descriptor nExts fixup result |<br>
        <var: #descriptor type: #'BytecodeDescriptor *'><br>
        <var: #fixup type: #'BytecodeFixup *'><br>
        self traceSimStack.<br>
        bytecodePC := start.<br>
        nExts := result := 0.<br>
        descriptor := nil.<br>
        deadCode := false.<br>
+       [self maybeHaltIfDebugPC.<br>
-       [self cCode: '' inSmalltalk: [self isDebugPC ifTrue: [self halt]].<br>
         fixup := self fixupAt: bytecodePC - initialPC.<br>
         self mergeWithFixupIfRequired: fixup.<br>
         self assertCorrectSimStackPtr.<br>
         descriptor := self loadBytesAndGetDescriptor.<br>
         nextOpcodeIndex := opcodeIndex.<br>
         result := deadCode<br>
                                ifTrue: [self mapDeadDescriptorIfNeeded: descriptor]<br>
                                ifFalse: [self perform: descriptor generator].<br>
         self assertExtsAreConsumed: descriptor.<br>
         self traceDescriptor: descriptor; traceSimStack.<br>
         self patchFixupTargetIfNeeded: fixup nextOpcodeIndex: nextOpcodeIndex.<br>
         self maybeDumpLiterals: descriptor.<br>
         bytecodePC := self nextBytecodePCFor: descriptor exts: nExts.<br>
         result = 0 and: [bytecodePC <= end]] whileTrue:<br>
                [nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].<br>
        self checkEnoughOpcodes.<br>
        ^result!<br>
<br>
Item was changed:<br>
  ----- Method: StackToRegisterMappingCogit>><wbr>compileBlockBodies (in category 'compile abstract instructions') -----<br>
  compileBlockBodies<br>
        <inline: false><br>
        | result compiledBlocksCount blockStart savedNeedsFrame savedNumArgs savedNumTemps<br>
          initialStackPtr initialOpcodeIndex initialIndexOfIRC initialCounterIndex |<br>
        <var: #blockStart type: #'BlockStart *'><br>
        self assert: blockCount > 0.<br>
        "scanBlock: in compileBlockEntry: sets both of these appropriately for each block."<br>
        savedNeedsFrame := needsFrame.<br>
        savedNumArgs := methodOrBlockNumArgs.<br>
        savedNumTemps := methodOrBlockNumTemps.<br>
        inBlock := InVanillaBlock.<br>
        compiledBlocksCount := 0.<br>
        [compiledBlocksCount < blockCount] whileTrue:<br>
                [blockPass := 1.<br>
                 blockStart := self blockStartAt: compiledBlocksCount.<br>
                 (result := self scanBlock: blockStart) < 0 ifTrue: [^result].<br>
                 initialOpcodeIndex := opcodeIndex.<br>
                 initialCounterIndex := self maybeCounterIndex."for SistaCogit"<br>
                 literalsManager saveForBlockCompile.<br>
                 NewspeakVM ifTrue:<br>
                        [initialIndexOfIRC := indexOfIRC].<br>
                 [self compileBlockEntry: blockStart.<br>
                  initialStackPtr := simStackPtr.<br>
                  (result := self compileAbstractInstructionsFro<wbr>m: blockStart startpc + (self pushNilSize: methodObj numInitialNils: blockStart numInitialNils)<br>
                                                through: blockStart startpc + blockStart span - 1) < 0 ifTrue:<br>
                        [^result].<br>
                  "If the final simStackPtr is less than the initial simStackPtr then scanBlock: over-<br>
                   estimated the number of initial nils (because it assumed one or more pushNils to<br>
                   produce an operand were pushNils to initialize temps.  This is very rare, so<br>
                   compensate by checking, adjusting numInitialNils and recompiling the block body.<br>
                   N.B.  No need to reinitialize the literalsManager because it answers existing literals."<br>
                  initialStackPtr = simStackPtr]<br>
                        whileFalse:<br>
+                               [self assert: (initialStackPtr > simStackPtr or: [deadCode]).<br>
-                               [self assert: initialStackPtr > simStackPtr.<br>
                                 blockPass := blockPass + 1. "for asserts :-("<br>
                                 blockStart numInitialNils: blockStart numInitialNils + simStackPtr - initialStackPtr.<br>
                                 blockStart fakeHeader dependent: nil.<br>
                                 self reinitializeFixupsFrom: blockStart startpc + blockStart numInitialNils<br>
                                        through: blockStart startpc + blockStart span - 1.<br>
                                 self cCode: 'bzero(abstractOpcodes + initialOpcodeIndex,<br>
                                                                        (opcodeIndex - initialOpcodeIndex) * sizeof(AbstractInstruction))'<br>
                                        inSmalltalk: [initialOpcodeIndex to: opcodeIndex - 1 do:<br>
                                                                        [:i| abstractOpcodes at: i put: (CogCompilerClass for: self)]].<br>
                                 opcodeIndex := initialOpcodeIndex.<br>
                                 self maybeSetCounterIndex: initialCounterIndex. "For SistaCogit"<br>
                                 literalsManager resetForBlockCompile.<br>
                                 NewspeakVM ifTrue:<br>
                                        [indexOfIRC := initialIndexOfIRC]].<br>
                compiledBlocksCount := compiledBlocksCount + 1].<br>
        needsFrame := savedNeedsFrame.<br>
        methodOrBlockNumArgs := savedNumArgs.<br>
        methodOrBlockNumTemps := savedNumTemps.<br>
        ^0!<br>
<br>
Item was added:<br>
+ ----- Method: StackToRegisterMappingCogit>><wbr>eventualTargetOf: (in category 'peephole optimizations') -----<br>
+ eventualTargetOf: targetBytecodePC<br>
+       "Attempt to follow a branch to a pc.  Handle branches to unconditional jumps<br>
+        and branches to push: aBoolean; conditional branch pairs.  If the branch cannot<br>
+        be followed answer targetBytecodePC."<br>
+<br>
+       | currentTarget nextPC nExts descriptor span cond |<br>
+       <var: #descriptor type: #'BytecodeDescriptor *'><br>
+       nextPC := currentTarget := targetBytecodePC.<br>
+       [[nExts := 0.<br>
+         descriptor := self generatorAt: bytecodeSetOffset<br>
+                                                               + (objectMemory fetchByte: nextPC ofObject: methodObj).<br>
+         descriptor isReturn ifTrue: [^currentTarget]. "avoid stepping off the end of methods"<br>
+         descriptor isExtension]<br>
+               whileTrue:<br>
+                       [nExts := nExts + 1.<br>
+                        nextPC := nextPC + descriptor numBytes].<br>
+        descriptor isUnconditionalBranch<br>
+               ifTrue:<br>
+                       [span := self spanFor: descriptor at: nextPC exts: nExts in: methodObj.<br>
+                        span < 0 ifTrue: "Do *not* follow backward branches; these are interrupt points and should not be elided."<br>
+                               [^currentTarget].<br>
+                        nextPC := nextPC + descriptor numBytes + span]<br>
+               ifFalse:<br>
+                       [descriptor generator<br>
+                               caseOf: {<br>
+                               [#genPushConstantTrueBytecode] -> [cond := true].<br>
+                               [#<wbr>genPushConstantFalseBytecode] -> [cond := false] }<br>
+                               otherwise: [^currentTarget].<br>
+                        "Don't step into loops across a pushTrue; jump:if: boundary, so as not to confuse stack depth fixup."<br>
+                        (fixups at: nextPC - initialPC) isBackwardBranchFixup ifTrue:<br>
+                               [^currentTarget].<br>
+                        nextPC := self eventualTargetOf: nextPC + descriptor numBytes.<br>
+                        nExts := 0.<br>
+                        [descriptor := self generatorAt: bytecodeSetOffset<br>
+                                                               + (objectMemory fetchByte: nextPC ofObject: methodObj).<br>
+                         descriptor isReturn ifTrue: [^currentTarget]. "avoid stepping off the end of methods"<br>
+                         descriptor isExtension]<br>
+                               whileTrue:<br>
+                                       [nExts := nExts + 1.<br>
+                                        nextPC := nextPC + descriptor numBytes].<br>
+                        descriptor isBranch ifFalse:<br>
+                               [^currentTarget].<br>
+                        descriptor isUnconditionalBranch ifTrue:<br>
+                               [^currentTarget].<br>
+                        nextPC := cond == descriptor isBranchTrue<br>
+                                                                       ifTrue: [nextPC<br>
+                                                                                       + descriptor numBytes<br>
+                                                                                       + (self spanFor: descriptor at: nextPC exts: nExts in: methodObj)]<br>
+                                                                       ifFalse: [nextPC + descriptor numBytes]].<br>
+        currentTarget := nextPC]<br>
+               repeat!<br>
<br>
Item was changed:<br>
  ----- Method: StackToRegisterMappingCogit>><wbr>extractMaybeBranchDescriptorIn<wbr>to: (in category 'bytecode generator support') -----<br>
  extractMaybeBranchDescriptorIn<wbr>to: fourArgBlock<br>
        "Looks one instruction ahead of the current bytecodePC and answers its bytecode descriptor and its pc.<br>
+        If the instruction found is a branch, also answers the pc after the branch and the pc targeted by the branch."<br>
-       If the instruction found is a branch, also answers the pc after the branch and the pc targetted by the branch"<br>
        | primDescriptor nextPC nExts branchDescriptor targetBytecodePC postBranchPC |<br>
        <inline: true><br>
        <var: #primDescriptor type: #'BytecodeDescriptor *'><br>
        <var: #branchDescriptor type: #'BytecodeDescriptor *'><br>
<br>
        primDescriptor := self generatorAt: byte0.<br>
<br>
        nextPC := bytecodePC + primDescriptor numBytes.<br>
        nExts := 0.<br>
+       [[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.<br>
+         branchDescriptor isExtension] whileTrue:<br>
-       [branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.<br>
-        branchDescriptor isExtension] whileTrue:<br>
                [nExts := nExts + 1.<br>
                 nextPC := nextPC + branchDescriptor numBytes].<br>
+        branchDescriptor isUnconditionalBranch]<br>
+               whileTrue:<br>
+                       [nextPC := self eventualTargetOf: nextPC<br>
+                                                                                       + branchDescriptor numBytes<br>
+                                                                                       + (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj)].<br>
<br>
        targetBytecodePC := postBranchPC := 0.<br>
<br>
+       (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse])<br>
+               ifTrue:<br>
+                       [targetBytecodePC := self eventualTargetOf: nextPC<br>
+                                                                                                               + branchDescriptor numBytes<br>
+                                                                                                               + (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).<br>
+                        postBranchPC := self eventualTargetOf: nextPC + branchDescriptor numBytes]<br>
+               ifFalse:<br>
+                       [branchDescriptor isReturn ifFalse:<br>
+                               [postBranchPC := self eventualTargetOf: nextPC + branchDescriptor numBytes.<br>
+                                nextPC := self eventualTargetOf: bytecodePC + primDescriptor numBytes]].<br>
+<br>
-       (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifTrue:<br>
-               [ targetBytecodePC := nextPC<br>
-                                                       + branchDescriptor numBytes<br>
-                                                       + (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).<br>
-               postBranchPC := nextPC + branchDescriptor numBytes ].<br>
-<br>
        fourArgBlock value: branchDescriptor value: nextPC value: postBranchPC value: targetBytecodePC!<br>
<br>
Item was changed:<br>
  ----- Method: StackToRegisterMappingCogit>><wbr>genJumpIf:to: (in category 'bytecode generator support') -----<br>
  genJumpIf: boolean to: targetBytecodePC<br>
        <inline: false><br>
+       | desc fixup ok eventualTarget |<br>
-       | desc fixup ok |<br>
        <var: #desc type: #'CogSimStackEntry *'><br>
        <var: #fixup type: #'BytecodeFixup *'><br>
        <var: #ok type: #'AbstractInstruction *'><br>
+       eventualTarget := self eventualTargetOf: targetBytecodePC.<br>
        self ssFlushTo: simStackPtr - 1.<br>
        desc := self ssTop.<br>
        self ssPop: 1.<br>
        (desc type == SSConstant<br>
         and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:<br>
                ["Must arrange there's a fixup at the target whether it is jumped to or<br>
                  not so that the simStackPtr can be kept correct."<br>
+                fixup := self ensureFixupAt: eventualTarget - initialPC.<br>
-                fixup := self ensureFixupAt: targetBytecodePC - initialPC.<br>
                 "Must annotate the bytecode for correct pc mapping."<br>
                 self annotateBytecode: (desc constant = boolean<br>
                                                                        ifTrue: [self Jump: fixup]<br>
                                                                        ifFalse: [self prevInstIsPCAnnotated<br>
                                                                                                ifTrue: [self Nop]<br>
                                                                                                ifFalse: [self Label]]).<br>
                 extA := 0.<br>
                 ^0].<br>
        desc popToReg: TempReg.<br>
        "Cunning trick by LPD.  If true and false are contiguous subtract the smaller.<br>
         Correct result is either 0 or the distance between them.  If result is not 0 or<br>
         their distance send mustBeBoolean."<br>
        self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.<br>
        self genSubConstant: boolean R: TempReg.<br>
+       self JumpZero: (self ensureFixupAt: eventualTarget - initialPC).<br>
-       self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).<br>
<br>
        self extASpecifiesNoMustBeBoolean ifTrue:<br>
                [ extA := 0.<br>
                self annotateBytecode: self lastOpcode.<br>
                ^ 0].<br>
        extA := 0.<br>
<br>
+       self CmpCq: (boolean = objectMemory falseObject<br>
- .     self CmpCq: (boolean = objectMemory falseObject<br>
                                        ifTrue: [objectMemory trueObject - objectMemory falseObject]<br>
                                        ifFalse: [objectMemory falseObject - objectMemory trueObject])<br>
                R: TempReg.<br>
        ok := self JumpZero: 0.<br>
        self genCallMustBeBooleanFor: boolean.<br>
        ok jmpTarget: (self annotateBytecode: self Label).<br>
        ^0!<br>
<br>
Item was changed:<br>
  ----- Method: StackToRegisterMappingCogit>><wbr>genJumpTo: (in category 'bytecode generator support') -----<br>
  genJumpTo: targetBytecodePC<br>
        self ssFlushTo: simStackPtr.<br>
        deadCode := true. "can't fall through"<br>
+       self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC) - initialPC).<br>
+       ^0!<br>
-       ^super genJumpTo: targetBytecodePC!<br>
<br>
Item was added:<br>
+ ----- Method: StackToRegisterMappingCogit>><wbr>generateInstructionsAt: (in category 'generate machine code') -----<br>
+ generateInstructionsAt: eventualAbsoluteAddress<br>
+       "Size pc-dependent instructions and assign eventual addresses to all instructions.<br>
+        Answer the size of the code.<br>
+        Compute forward branches based on virtual address (abstract code starts at 0),<br>
+        assuming that any branches branched over are long.<br>
+        Compute backward branches based on actual address.<br>
+        Reuse the fixups array to record the pc-dependent instructions that need to have<br>
+        their code generation postponed until after the others.<br>
+<br>
+        Override to andd handling for null branches (branches to the immediately following<br>
+        instruction) occasioned by StackToRegisterMapping's following of jumps."<br>
+       | absoluteAddress pcDependentIndex abstractInstruction fixup |<br>
+       <var: #abstractInstruction type: #'AbstractInstruction *'><br>
+       <var: #fixup type: #'BytecodeFixup *'><br>
+       absoluteAddress := eventualAbsoluteAddress.<br>
+       pcDependentIndex := 0.<br>
+       0 to: opcodeIndex - 1 do:<br>
+               [:i|<br>
+               self maybeBreakGeneratingAt: absoluteAddress.<br>
+               abstractInstruction := self abstractInstructionAt: i.<br>
+               abstractInstruction isPCDependent<br>
+                       ifTrue:<br>
+                               [abstractInstruction sizePCDependentInstructionAt: absoluteAddress.<br>
+                                (abstractInstruction isJump<br>
+                                 and: [i + 1 < opcodeIndex<br>
+                                 and: [abstractInstruction getJmpTarget == (self abstractInstructionAt: i + 1)]])<br>
+                                       ifTrue:<br>
+                                               [abstractInstruction<br>
+                                                       opcode: Nop;<br>
+                                                       concretizeAt: absoluteAddress]<br>
+                                       ifFalse:<br>
+                                               [fixup := self fixupAt: pcDependentIndex.<br>
+                                                pcDependentIndex := pcDependentIndex + 1.<br>
+                                                fixup instructionIndex: i].<br>
+                                absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]<br>
+                       ifFalse:<br>
+                               [absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].<br>
+       0 to: pcDependentIndex - 1 do:<br>
+               [:j|<br>
+               fixup := self fixupAt: j.<br>
+               abstractInstruction := self abstractInstructionAt: fixup instructionIndex.<br>
+               self maybeBreakGeneratingAt: abstractInstruction address.<br>
+               abstractInstruction concretizeAt: abstractInstruction address].<br>
+       ^absoluteAddress - eventualAbsoluteAddress!<br>
<br>
Item was changed:<br>
  ----- Method: StackToRegisterMappingCogit>><wbr>mergeWithFixupIfRequired: (in category 'simulation stack') -----<br>
  mergeWithFixupIfRequired: fixup<br>
        "If this bytecode has a fixup, some kind of merge needs to be done. There are 4 cases:<br>
                1) the bytecode has no fixup (fixup isNotAFixup)<br>
                        do nothing<br>
                2) the bytecode has a non merge fixup<br>
                        the fixup has needsNonMergeFixup.<br>
                        The code generating non merge fixup (currently only special selector code) is responsible<br>
                                for the merge so no need to do it.<br>
                        We set deadCode to false as the instruction can be reached from jumps.<br>
                3) the bytecode has a merge fixup, but execution flow *cannot* fall through to the merge point.<br>
                        the fixup has needsMergeFixup and deadCode = true.<br>
                        ignores the current simStack as it does not mean anything<br>
                        restores the simStack to the state the jumps to the merge point expects it to be.<br>
                4) the bytecode has a merge fixup and execution flow *can* fall through to the merge point.<br>
                        the fixup has needsMergeFixup and deadCode = false.<br>
                        flushes the stack to the stack pointer so the fall through execution path simStack is<br>
                                in the state the merge point expects it to be.<br>
                        restores the simStack to the state the jumps to the merge point expects it to be.<br>
<br>
        In addition, if this is a backjump merge point, we patch the fixup to hold the current simStackPtr<br>
        for later assertions."<br>
<br>
        <var: #fixup type: #'BytecodeFixup *'><br>
        "case 1"<br>
+       fixup notAFixup ifTrue:<br>
+               [^0].<br>
-       fixup notAFixup ifTrue: [^ 0].<br>
<br>
        "case 2"<br>
+       fixup isNonMergeFixup ifTrue:<br>
+               [deadCode := false. ^0].<br>
-       fixup isNonMergeFixup ifTrue: [deadCode := false. ^ 0 ].<br>
<br>
        "cases 3 and 4"<br>
        self assert: fixup isMergeFixup.<br>
        self traceMerge: fixup.<br>
+       deadCode<br>
+               ifTrue: "case 3"<br>
+                       ["Would like to assert fixup simStackPtr >= (methodOrBlockNumTemps - 1) but can't because<br>
+                          a) the initialNils hack, b) deadCode removal allows arriving at an isBackwardBranchFixup."<br>
+                        self assert: (fixup simStackPtr >= (methodOrBlockNumTemps - 1) or: [inBlock = InVanillaBlock or: [fixup isBackwardBranchFixup]]).<br>
+                        fixup isBackwardBranchFixup ifFalse:<br>
+                               [simStackPtr := fixup simStackPtr].<br>
+                        LowcodeVM ifTrue:<br>
+                               [simNativeStackPtr := fixup simNativeStackPtr.<br>
+                               simNativeStackSize := fixup simNativeStackSize]]<br>
+               ifFalse: "case 4"<br>
+                       [self ssFlushTo: simStackPtr].<br>
-       deadCode ifTrue: [<br>
-               "case 3"<br>
-               simStackPtr := fixup simStackPtr.<br>
-               LowcodeVM ifTrue: [<br>
-                       simNativeStackPtr := fixup simNativeStackPtr.<br>
-                       simNativeStackSize := fixup simNativeStackSize.<br>
-               ]<br>
-       ] ifFalse: [<br>
-               "case 4"<br>
-               self ssFlushTo: simStackPtr<br>
-       ].<br>
<br>
        "cases 3 and 4"<br>
        deadCode := false.<br>
+       fixup isBackwardBranchFixup ifTrue:<br>
+               [fixup simStackPtr: simStackPtr.<br>
+               LowcodeVM ifTrue:<br>
+                       [fixup simNativeStackPtr: simNativeStackPtr.<br>
+                        fixup simNativeStackSize: simNativeStackSize]].<br>
-       fixup isBackwardBranchFixup ifTrue: [<br>
-               fixup simStackPtr: simStackPtr.<br>
-               LowcodeVM ifTrue: [<br>
-                       fixup simNativeStackPtr: simNativeStackPtr.<br>
-                       fixup simNativeStackSize: simNativeStackSize.<br>
-               ]<br>
-       ].<br>
        fixup targetInstruction: self Label.<br>
        self assert: simStackPtr = fixup simStackPtr.<br>
+       LowcodeVM ifTrue:<br>
+               [self assert: simNativeStackPtr = fixup simNativeStackPtr.<br>
+                self assert: simNativeStackSize = fixup simNativeStackSize].<br>
-       LowcodeVM ifTrue: [<br>
-               self assert: simNativeStackPtr = fixup simNativeStackPtr.<br>
-               self assert: simNativeStackSize = fixup simNativeStackSize.<br>
-       ].<br>
<br>
        self cCode: '' inSmalltalk:<br>
                [self assert: fixup simStackPtr = (self debugStackPointerFor: bytecodePC)].<br>
        self restoreSimStackAtMergePoint: fixup.<br>
+<br>
-<br>
        ^0!<br>
<br>
<br>
<br></blockquote></div><br></div>