VM Maker: VMMaker.oscog-eem.2140.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker.oscog-eem.2140.mcz

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

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

Name: VMMaker.oscog-eem.2140
Author: eem
Time: 28 February 2017, 10:57:08.30277 am
UUID: aa8bca00-5798-4bba-9cec-b1458e30071b
Ancestors: VMMaker.oscog-eem.2139

V3 Cogit:
Fix regression in #==.

Fix assert fail for machine code perform primitive failure check.

Cogit:
Fix in-image compilation given new receiverTagBitsForMethod: mclass scheme.

Fix mistakes in the Cogit command and provide a CogSimStackEntry comment.  Move liveRegister up from CogRegisterAllocatingSimStackEntry to CogSimStackEntry, eliminate an unused inst var, and type the register fields appropriately, saving a word per struct.

Set a temp var's simStackEntry's bytecode pointer on assignment.

Fix temp var padding in printSimStack.

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

Item was changed:
  CogSimStackEntry subclass: #CogRegisterAllocatingSimStackEntry
+ instanceVariableNames: ''
- instanceVariableNames: 'liveRegister'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'VMMaker-JIT'!

Item was changed:
  VMStructType subclass: #CogSimStackEntry
+ instanceVariableNames: 'cogit objectRepresentation type spilled liveRegister register offset constant bcptr'
- instanceVariableNames: 'cogit objectRepresentation type spilled annotateUse register offset constant bcptr'
  classVariableNames: ''
  poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogRTLOpcodes'
  category: 'VMMaker-JIT'!
+
+ !CogSimStackEntry commentStamp: 'eem 2/25/2017 11:14' prior: 0!
+ A CogSimStackEntry represents an object pushed on the stack, but during the partial evaluation that occurs as part of the StackToRegisterMappingCogit's compilation.  Bytecodes that produce operands (push items onto the stack) push suitably descriptive instances of CogSimStackEntry onto the simStack (simulation stack).  Bytecodes that cnsume operands (sends, assignments, returns, etc) take items off the simStack.  Hence teh generated code avoids pushing items onto the real stack, and the StackToRegisterMappngCogit can put the operands found on the simSTack in registers, etc.  Hence actual stack raffic is much reduced, a much more efficient calling convention is enabled, and so overall performance is increased.  This scheme is due to L. Peter Deutsch and extended here.
+
+ Instance Variables
+ bcptr: <Integer>
+ cogit: <StackToRegisterMappingCogit>
+ constant: <Oop>
+ liveRegister: <Integer>
+ objectRepresentation: <CogObjectRepresentation>
+ offset: <Integer>
+ register: <Integer>
+ spilled: <Boolean>
+ type: <Integer from SSBaseOffset, SSConstant, SSRegister or SSSpill>
+
+ bcptr
+ - the bytecode PC at which this particular entry was created (pushed onto the stack).
+
+ cogit
+ - the StackToRegisterMappingCogit using this instance
+
+ constant
+ - if type = SSConstant then this is the constant's oop
+
+ liveRegister
+ - unused other than for simSelf.  This is here for simSelf and for the subclass CogRegisterAllocatingSimStackEntry
+
+ objectRepresentation
+ - the CogObjectRepresentation in use for the current object model
+
+ offset
+ - if type = SSBaseOffset or type = SSSpill then this is the offset from register
+
+ register
+ - type = SSBaseOffset or type = SSSpill or type = SSRegister then this is the register's code (NoReg, TempReg, ReceiverResultReg et al)
+
+ spilled
+ - if true, then this entry has been spilled onto the actual stack (or rather code has been generated to push the entry onto the real stack)
+
+ type
+ - SSBaseOffset, SSConstant, SSRegister or SSSpill!

Item was changed:
  ----- Method: CogSimStackEntry class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
+ "Enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogSimStackEntry struct."
+ "self typedef"
- "enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogSimStackEntry struct."
- "self printTypedefOn: Transcript"
  self filteredInstVarNames do:
  [:ivn|
  aBinaryBlock
  value: (ivn = 'register' ifTrue: ['registerr'] ifFalse: [ivn]) "avoid reservedWord conflict"
  value: (ivn caseOf: {
  ['type'] -> [#char].
+ ['spilled'] -> [#char].
+ ['register'] -> [#'signed char']. "because NoReg = -1"
+ ['liveRegister'] -> [#'signed char'].}
- ['spilled'] -> [#char].}
  otherwise:
  [#sqInt])]!

Item was changed:
  ----- Method: CogVMSimulator>>primitivePerform (in category 'debugging traps') -----
  primitivePerform
+ | receiver selector |
+ "If called from the machine code perform primitive, it should not have been found,
+ except that the cacheing for V3 has a mismatch between that used ror the first-level
+ method cache and inline caches."
+ receiver := (self stackValue: argumentCount).
- | selector |
- "If called from the machine code perform primitive, it should not have been found."
  selector := self stackValue: argumentCount - 1.
+ ((self methodHasCogMethod: newMethod)
+ and: [(objectMemory isCompactInstance: receiver) not]) ifTrue:
+ [self deny: (self newMethodInLookupCacheAt: selector and: (objectMemory fetchClassTagOf: receiver))].
+ self sendBreakpoint: selector receiver: receiver.
+ (self filterPerformOf: selector to: receiver) ifTrue:
- (self methodHasCogMethod: newMethod) ifTrue:
- [self deny: (self newMethodInLookupCacheAt: selector and: (objectMemory fetchClassTagOf: (self stackValue: argumentCount)))].
- self sendBreakpoint: selector receiver: (self stackValue: argumentCount).
- (self filterPerformOf: selector to: (self stackValue: argumentCount)) ifTrue:
  [^self pop: argumentCount].
  ^super primitivePerform!

Item was changed:
  CogClass subclass: #Cogit
  instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffset cPICCaseSize cP
 ICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCaptureCStackPointers ordinarySendTrampolines superSen
 dTrampolines directedSuperSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel maxCPICCases debugBytecodePointers debugOpcodeIndices disassemblingMethod ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline'
  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!
- !Cogit commentStamp: 'eem 2/9/2017 10:01' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
 
  StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
 
  I have concrete subclasses that implement different levels of optimization:
  SimpleStackBasedCogit is the simplest code generator.
 
  StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  to the stack until necessary and implements a register-based calling convention for low-arity sends.
 
+ SistaCogit is an experimental code generator with support for counting
- StackToRegisterMappingCogit 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 added:
+ ----- Method: CurrentImageCoInterpreterFacade>>lookupSelector:inClass: (in category 'cog jit support') -----
+ lookupSelector: selectorOop inClass: classOop
+ | class selector |
+ class := self objectForOop: classOop.
+ selector := self objectForOop: selectorOop.
+ ^(class canUnderstand: selector) ifTrue:
+ [self oopForObject: ((class whichClassIncludesSelector: selector)
+ compiledMethodAt: selector)]!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>receiverTagBitsForMethod: (in category 'accessing') -----
+ receiverTagBitsForMethod: methodOop
+ ^(self objectForOop: methodOop) methodClass
+ caseOf: {
+ [SmallInteger] -> [objectMemory smallIntegerTag].
+ [Character] -> [objectMemory characterTag].
+ [SmallFloat64] -> [objectMemory smallFloatTag] }
+ otherwise: [0]!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSqueakV3ObjectRepresentation>>receiverTagBitsForMethod: (in category 'accessing') -----
+ receiverTagBitsForMethod: methodOop
+ ^(self objectForOop: methodOop) methodClass =SmallInteger
+ ifTrue: [1]
+ ifFalse: [0]!

Item was added:
+ ----- Method: NewCoObjectMemory>>isCompactInstance: (in category 'debug support') -----
+ isCompactInstance: oop
+ "For assert checking"
+ ^(self isNonImmediate: oop) and: [((self baseHeader: oop) bitAnd: CompactClassMask) ~= 0]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genStorePop:TemporaryVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean TemporaryVariable: tempIndex
  <inline: false>
  | top srcRegOrNone destReg |
  self deny: self duplicateRegisterAssignmentsInTemporaries.
  self ssFlushUpThroughTemporaryVariable: tempIndex.
  "To avoid a stall writing through destReg, remember srcReg before the potential ssPop: 1 in ssStorePop:toReg:"
  top := self ssTop.
  srcRegOrNone := top registerOrNone.
  "ssStorePop:toPreferredReg: will allocate a register, and indeed may allocate ReceiverResultReg
  if, for example, the ssEntry to be popped is already in ReceiverResultReg (as the result of a send).
  ReceiverResultReg is not a good choice for a temporary variable; it has other uses.  So if the ssEntry
  at top of stack has ReceiverResultReg as its live variable, try and allocate an alternative."
  destReg := (self simStackAt: tempIndex) liveRegister.
  destReg ~= NoReg
  ifTrue:
  [self ssStorePop: popBoolean toReg: destReg]
  ifFalse:
  [((top type = SSConstant
     or: [srcRegOrNone = NoReg
     or: [self register: srcRegOrNone isInMask: self registerMaskUndesirableForTempVars]])
   and: [(destReg := self availableRegOrNoneNotConflictingWith: (self registerMaskUndesirableForTempVars bitOr: self liveRegisters)) ~= NoReg])
  ifTrue: [self ssStorePop: popBoolean toReg: destReg]
  ifFalse: [destReg := self ssStorePop: popBoolean toPreferredReg: TempReg].
  "The ssStorePop: may end up assigning a register to ssTop, and if it is also a temp then a new
   register must be found for the destination temp, sicne two temp vars can't share a register."
  (top isFrameTempVar and: [top liveRegister = destReg]) ifTrue:
  [srcRegOrNone := destReg.
  destReg := self availableRegOrNoneNotConflictingWith: (self registerMaskUndesirableForTempVars bitOr: self liveRegisters).
  destReg ~= NoReg ifTrue:
  [self MoveR: srcRegOrNone R: destReg]].
  (destReg ~= NoReg and: [destReg ~= TempReg]) ifTrue:
  [(self simStackAt: tempIndex) liveRegister: destReg.
  self copyLiveRegisterToCopiesOf: (self simStackAt: tempIndex)]].
  self MoveR: (srcRegOrNone ~= NoReg ifTrue: [srcRegOrNone] ifFalse: [destReg])
  Mw: (self frameOffsetOfTemporary: tempIndex)
  r: FPReg.
+ (self simStackAt: tempIndex) bcptr: bytecodePC. "for debugging"
  self deny: self duplicateRegisterAssignmentsInTemporaries.
  ^0!

Item was added:
+ ----- Method: SpurMemoryManager>>isCompactInstance: (in category 'debug support') -----
+ isCompactInstance: oop
+ "For assert checking"
+ ^false!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genStorePop:TemporaryVariable: (in category 'bytecode generator stores') -----
  genStorePop: popBoolean TemporaryVariable: tempIndex
  <inline: false>
  | reg |
  self ssFlushUpThroughTemporaryVariable: tempIndex.
  reg := self ssStorePop: popBoolean toPreferredReg: TempReg.
  self MoveR: reg
  Mw: (self frameOffsetOfTemporary: tempIndex)
  r: FPReg.
+ (self simStackAt: tempIndex) bcptr: bytecodePC. "for debugging"
  ^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genVanillaInlinedIdenticalOrNotIf: orNot
+ | nextPC postBranchPC targetPC branchDescriptor
- | nextPC postBranchPC targetBytecodePC branchDescriptor
   rcvrReg argReg argIsConstant rcvrIsConstant  |
  <var: #branchDescriptor type: #'BytecodeDescriptor *'>
 
  self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target |
+ branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := target ].
- branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
 
  argIsConstant := self ssTop type = SSConstant.
  "They can't be both constants to use correct machine opcodes.
  However annotable constants can't be resolved statically, hence we need to careful."
  rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant].
 
  self
  allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not
  rcvrNeedsReg: rcvrIsConstant not
  into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
 
  "If not followed by a branch, resolve to true or false."
  (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  [^ self
  genIdenticalNoBranchArgIsConstant: argIsConstant
  rcvrIsConstant: rcvrIsConstant
  argReg: argReg
  rcvrReg: rcvrReg
  orNotIf: orNot].
 
  "If branching the stack must be flushed for the merge"
  self ssFlushTo: simStackPtr - 2.
 
  self genCmpArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
  self ssPop: 2.
 
  "Further since there is a following conditional jump bytecode, define
  non-merge fixups and leave the cond bytecode to set the mergeness."
  (self fixupAt: nextPC) notAFixup
  ifTrue: "The next instruction is dead.  we can skip it."
  [deadCode := true.
+ self ensureFixupAt: targetPC.
- self ensureFixupAt: targetBytecodePC.
  self ensureFixupAt: postBranchPC]
  ifFalse:
  [self deny: deadCode]. "push dummy value below"
 
- self genConditionalBranch: (orNot == branchDescriptor isBranchTrue ifTrue: [JumpNonZero] ifFalse: [JumpZero])
- operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
 
+ orNot == branchDescriptor isBranchTrue "orNot is true for ~~"
+ ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
+ [self JumpZero:  (self ensureNonMergeFixupAt: targetPC).
+ self Jump: (self ensureNonMergeFixupAt: postBranchPC)]
+ ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
+ [self ensureNonMergeFixupAt: targetPC.
+ self JumpZero: (self ensureNonMergeFixupAt: postBranchPC).
+ self Jump: (self ensureNonMergeFixupAt: targetPC)].
+
+ "Not reached, execution flow has jumped to fixup"
- "If the branch is dead, then we can just fall through postBranchPC (only a nop in-between), else
- we need to jump over the code of the branch"
  deadCode ifFalse:
+ [self ssPushConstant: objectMemory trueObject]. "dummy value"
- [self Jump: (self ensureNonMergeFixupAt: postBranchPC).
- self ssPushConstant: objectMemory trueObject]. "dummy value"
  ^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>put:paddedTo:tabWidth:on: (in category 'simulation only') -----
  put: aString paddedTo: compositionWidth tabWidth: tabWidth on: aStream
  <doNotGenerate>
  | fittedString size width |
  fittedString := aString.
  size := fittedString size.
  [(width := self widthInDefaultFontOf: fittedString) > compositionWidth] whileTrue:
  [size := size - 2.
  fittedString := aString contractTo: size].
  aStream
  nextPutAll: fittedString;
+ tab: compositionWidth - width + (width \\ tabWidth) // tabWidth + 1!
- tab: compositionWidth - width + (width \\ tabWidth) // tabWidth!