VM Maker: VMMaker.oscogSPC-eem.2127.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.oscogSPC-eem.2127.mcz

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

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

Name: VMMaker.oscogSPC-eem.2127
Author: eem
Time: 12 February 2017, 10:48:48.374293 am
UUID: 505b5bdb-2355-4b2b-85b7-e600b3df5c23
Ancestors: VMMaker.oscogSPC-eem.2126

Cogit:
Initialize initialPC to zero for run-time initialization (C code wasn't affected cuz it defaulted to 0).
Fix some C compilation warnings due to mismatched pointer types.
Add support for printing temp names in blocks for in-image compilation.
(Slang) Get methods that return AbstractInstrucitons to be inlinable.

SimpleStackBasedCogit:
Avoid assuming bytecode sizes in  closure creation.

StackToRegisterMappingCogit:
Simplify genForwardersInlinedIdenticalOrNotIf: to avoid an extra call of genEnsureOopInRegNotForwarded:...
Generate slightly better code in genSpecialSelectorComparison
Squash jump L1; nop; L1 to nop; nop (again as part of jump following).
Don't bother to inline genEnsureOopInRegNotForwarded:scratchReg:ifForwarder:ifNotForwarder:, but do inline genEnsureOopInRegNotForwarded:scratchReg:jumpBackTo: which is simply a call of the other.

RegisterAllocatingCogit:
Don't allocate an SSRegister's entry to a different register.
ensureNonMergeFixupAt: must remember the optStatus.  Add some asserts to check that the non-merge is appropriate.
Implement merging for genForwardersInlinedIdenticalOrNotIf: and genSpecialSelectorComparison.
Remember to flush live register state on backward branch (checkForInterrupts).
Make mergeRequiredForJumpTo: sophisitcated enough to spot matching source and destination simStacks.

=============== Diff against VMMaker.oscogSPC-eem.2126 ===============

Item was changed:
  ----- Method: CCodeGenerator>>collectInlineList: (in category 'inlining') -----
  collectInlineList: inlineFlagOrSymbol
  "Make a list of methods that should be inlined.  If inlineFlagOrSymbol == #asSpecified
  only inline methods marked with <inline: true>.  If inlineFlagOrSymbol == #asSpecifiedOrQuick
  only inline methods marked with <inline: true> or methods that are quick (^constant, ^inst var)."
  "Details: The method must not include any inline C, since the
  translator cannot currently map variable names in inlined C code.
  Methods to be inlined must be small or called from only one place."
 
  | selectorsOfMethodsNotToInline callsOf |
  self assert: (#(true false asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol).
  selectorsOfMethodsNotToInline := Set new: methods size.
  selectorsOfMethodsNotToInline addAll: macros keys.
  apiMethods ifNotNil:
  [selectorsOfMethodsNotToInline addAll: apiMethods keys].
  methods do:
  [:m|
  m isStructAccessor ifTrue:
  [selectorsOfMethodsNotToInline add: m selector]].
 
  "build dictionary to record the number of calls to each method"
  callsOf := Dictionary new: methods size * 2.
  methods keysAndValuesDo:
  [:s :m|
  (m isRealMethod
  and: [self shouldGenerateMethod: m]) ifTrue:
  [callsOf at: s put: 0]].
 
  "For each method, scan its parse tree once or twice to:
  1. determine if the method contains unrenamable C code or declarations or has a C builtin
  2. determine how many nodes it has
  3. increment the sender counts of the methods it calls"
  inlineList := Set new: methods size * 2.
  (methods reject: [:m| selectorsOfMethodsNotToInline includes: m selector]) do:
  [:m| | inlineIt hasUnrenamableCCode nodeCount |
  ((breakSrcInlineSelectors includes: m selector)
  and: [breakOnInline isNil]) ifTrue:
  [self halt].
  inlineIt := #dontCare.
  (translationDict includesKey: m selector)
  ifTrue: [hasUnrenamableCCode := true]
  ifFalse:
  [hasUnrenamableCCode := m hasUnrenamableCCode.
  nodeCount := 0.
  m parseTree nodesDo:
  [:node|
  node isSend ifTrue:
  [callsOf
  at: node selector
  ifPresent:
  [:senderCount| callsOf at: node selector put: senderCount + 1]].
  nodeCount := nodeCount + 1].
  inlineIt := m extractInlineDirective].  "may be true, false, #always, #never or #dontCare"
  (hasUnrenamableCCode or: [inlineIt == false])
  ifTrue: "don't inline if method has C code or contains negative inline directive"
  [inlineIt == true ifTrue:
  [logger
  ensureCr;
  nextPutAll: 'failed to inline ';
  nextPutAll: m selector;
  nextPutAll: ' as it contains unrenamable C declarations or C code';
  cr; flush].
  selectorsOfMethodsNotToInline add: m selector]
  ifFalse:
  [(inlineFlagOrSymbol caseOf: {
  [#asSpecified] -> [inlineIt == true].
+ [#asSpecifiedOrQuick] -> [inlineIt == true
+ or: [self isQuickCompiledMethod: m compiledMethod]].
- [#asSpecifiedOrQuick] -> [inlineIt == true or: [m compiledMethod isQuick]].
  [true] -> [nodeCount < 40 or: [inlineIt == true]].
  [false] -> [false]})
  ifTrue: "inline if method has no C code and is either small or contains inline directive"
  [inlineList add: m selector]
  ifFalse:
  [(#(asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol) ifTrue:
  [selectorsOfMethodsNotToInline add: m selector]]]].
 
  (#(asSpecified asSpecifiedOrQuick) includes: inlineFlagOrSymbol)
  ifTrue:
  [methods do: [:m| m inline ifNil: [m inline: (inlineList includes: m selector)]]]
  ifFalse:
  [callsOf associationsDo:
  [:assoc|
  (assoc value = 1
  and: [(selectorsOfMethodsNotToInline includes: assoc key) not]) ifTrue:
  [inlineList add: assoc key]]]!

Item was added:
+ ----- Method: CCodeGenerator>>isQuickCompiledMethod: (in category 'inlining') -----
+ isQuickCompiledMethod: aCompiledMethod
+ ^aCompiledMethod isQuick
+ or: [(#(pushConstant: pushLiteralVariable:) includes: (aCompiledMethod abstractBytecodeMessageAt: aCompiledMethod initialPC) selector)
+ and: [(aCompiledMethod abstractBytecodeMessageAt: (InstructionStream on: aCompiledMethod) followingPc) selector == #methodReturnTop]]!

Item was changed:
  ----- Method: CogAbstractInstruction>>getJmpTarget (in category 'accessing') -----
  getJmpTarget
  "Get the target of a jump instruction.  Jumps have the target in the first operand."
+ <inline: true>
  ^cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'!

Item was changed:
  ----- Method: CogAbstractInstruction>>isAFixup: (in category 'testing') -----
  isAFixup: fixupOrAddress
  <var: #fixupOrAddress type: #'void *'>
+ <inline: true>
  ^cogit addressIsInFixups: fixupOrAddress!

Item was changed:
  ----- Method: CogAbstractInstruction>>labelOffset (in category 'generate machine code') -----
  labelOffset
  "Hack:  To arrange that the block method field pushed in a block entry has
  its MFMethodFlagIsBlockFlag bit set we provide labels with an offset.  The
  offset for the fakeHeader reference is MFMethodFlagIsBlockFlag.  See
  compileBlockFrameBuild:"
+ <inline: true>
  ^operands at: 1!

Item was changed:
  ----- Method: CogAbstractInstruction>>updateLabel: (in category 'generate machine code') -----
  updateLabel: labelInstruction
  "Update an instruction that depends on a label outside
  of generated code (e.g. a method or block header)."
  <var: #labelInstruction type: #'AbstractInstruction *'>
+ <inline: true>
  self assert: (opcode = MoveCwR or: [opcode = PushCw]).
  operands at: 0 put: labelInstruction address + labelInstruction labelOffset!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:ifForwarder:ifNotForwarder: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch ifForwarder: fwdJumpTarget ifNotForwarder: nonFwdJumpTargetOrZero
  "Make sure that the oop in reg is not forwarded.  
  Use the fact that isForwardedObjectClassIndexPun is a power of two to save an instruction."
  | imm ok finished |
- <inline: true>
- <var: #ok type: #'AbstractInstruction *'>
- <var: #imm type: #'AbstractInstruction *'>
- <var: #finished type: #'AbstractInstruction *'>
  self assert: reg ~= scratch.
  imm := self genJumpImmediate: reg.
  "notionally
  self genGetClassIndexOfNonImm: reg into: scratch.
  cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: TempReg.
  but the following is an instruction shorter:"
  cogit MoveMw: 0 r: reg R: scratch.
  cogit
  AndCq: objectMemory classIndexMask - objectMemory isForwardedObjectClassIndexPun
  R: scratch.
  ok := cogit JumpNonZero: 0.
  self genLoadSlot: 0 sourceReg: reg destReg: reg.
  cogit Jump: fwdJumpTarget.
+ finished := nonFwdJumpTargetOrZero asUnsignedInteger = 0
+ ifTrue: [cogit Label]
+ ifFalse: [nonFwdJumpTargetOrZero].
- finished := nonFwdJumpTargetOrZero = 0
- ifTrue: [ cogit Label ]
- ifFalse: [ self cCoerceSimple: nonFwdJumpTargetOrZero to: #'AbstractInstruction *' ].
  imm jmpTarget: (ok jmpTarget: finished).
  ^0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genEnsureOopInRegNotForwarded:scratchReg:jumpBackTo: (in category 'compile abstract instructions') -----
  genEnsureOopInRegNotForwarded: reg scratchReg: scratch jumpBackTo: instruction
  <var: #instruction type: #'AbstractInstruction *'>
+ <inline: true>
  ^ self
  genEnsureOopInRegNotForwarded: reg
  scratchReg: scratch
  ifForwarder: instruction
  ifNotForwarder: 0!

Item was added:
+ ----- Method: CogRegisterAllocatingSimStackEntry>>isIdenticalEntryAs: (in category 'comparing') -----
+ isIdenticalEntryAs: ssEntry
+ <var: 'ssEntry' type: #'CogSimStackEntry *'>
+ ^type = ssEntry type
+  and: [liveRegister = ssEntry liveRegister
+  and: [((type = SSBaseOffset or: [type == SSSpill]) and: [offset = ssEntry offset and: [register = ssEntry register]])
+ or: [(type = SSRegister and: [register = ssEntry register])
+ or: [(type = SSConstant and: [constant = ssEntry constant])]]]]!

Item was added:
+ ----- Method: CogRegisterAllocatingSimStackEntry>>isMergedWithTargetEntry: (in category 'comparing') -----
+ isMergedWithTargetEntry: targetEntry
+ "The receiver is a simStackEntry at a jump to the corresponding simStackEntry at the jump's target.
+ Answer if no merge is required for the jump."
+ <var: 'ssEntry' type: #'CogSimStackEntry *'>
+ spilled ~= targetEntry spilled ifTrue: "push or pop required"
+ [^false].
+ (liveRegister = NoReg and: [targetEntry liveRegister ~= NoReg]) ifTrue: "register load required"
+ [^false].
+ (liveRegister ~= NoReg
+ and: [liveRegister = targetEntry liveRegister
+ and: [type = targetEntry type
+ and: [type = SSConstant or: [type = SSRegister and: [register = targetEntry register]]]]]) ifTrue:
+ [^true].
+ ((type = SSBaseOffset or: [type == SSSpill])
+ and: [(targetEntry type = SSBaseOffset or: [targetEntry type == SSSpill])
+ and: [offset = targetEntry offset and: [register = targetEntry register]]]) ifTrue:
+ [^true].
+ self halt: 'comment the incompatible pair please'.
+ ^false!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>popToReg: (in category 'compile abstract instructions') -----
  popToReg: reg
  liveRegister ~= NoReg
  ifTrue:
  [self deny: (type = SSRegister and: [register ~= liveRegister and: [cogit needsFrame]]).
  spilled ifTrue: "This is rare, and in some cases it isn't even needed (e.g. frameful return) but we can't tell as yet."
  [cogit AddCq: objectRepresentation wordSize R: SPReg].
  reg ~= liveRegister
  ifTrue: [cogit MoveR: liveRegister R: reg]
  ifFalse: [cogit Label]]
  ifFalse:
  [spilled
  ifTrue:
  [cogit PopR: reg]
  ifFalse:
  [type caseOf: {
  [SSBaseOffset] -> [cogit MoveMw: offset r: register R: reg].
  [SSConstant] -> [cogit genMoveConstant: constant R: reg].
  [SSRegister] -> [reg ~= register
  ifTrue: [cogit MoveR: register R: reg]
  ifFalse: [cogit Label]] }]].
 
+ (reg ~= TempReg and: [liveRegister = NoReg and: [type ~= SSRegister]]) ifTrue:
- (reg ~= TempReg and: [reg ~= liveRegister and: [type ~= SSRegister]]) ifTrue:
  [liveRegister := reg.
  cogit copyLiveRegisterToCopiesOf: self]!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>storeToReg: (in category 'compile abstract instructions') -----
  storeToReg: reg
  liveRegister ~= NoReg
  ifTrue:
  [self deny: (type = SSRegister and: [register ~= liveRegister]).
  reg ~= liveRegister
  ifTrue: [cogit MoveR: liveRegister R: reg]
  ifFalse: [cogit Label]]
  ifFalse:
  [type caseOf: {
  [SSBaseOffset] -> [cogit MoveMw: offset r: register R: reg].
  [SSSpill] -> [cogit MoveMw: offset r: register R: reg].
  [SSConstant] -> [cogit genMoveConstant: constant R: reg].
  [SSRegister] -> [reg ~= register
  ifTrue: [cogit MoveR: register R: reg]
  ifFalse: [cogit Label]] }].
 
+ (reg ~= TempReg and: [liveRegister = NoReg and: [type ~= SSRegister]]) ifTrue:
- (reg ~= TempReg and: [reg ~= liveRegister and: [type ~= SSRegister]]) ifTrue:
  [liveRegister := reg.
  cogit copyLiveRegisterToCopiesOf: self]!

Item was added:
+ ----- Method: Cogit class>>attemptToComputeTempNamesFor: (in category 'in-image compilation') -----
+ attemptToComputeTempNamesFor: aCompiledMethod
+ (aCompiledMethod respondsTo: #tempNames) ifTrue:
+ [| blocks |
+ blocks := aCompiledMethod embeddedBlockClosures.
+ initializationOptions
+ at: #tempNames
+ put: (Dictionary withAll: {aCompiledMethod initialPC -> aCompiledMethod tempNames},
+ (blocks
+ ifEmpty: [#()]
+ ifNotEmpty:
+ [aCompiledMethod embeddedBlockClosures
+ with: ((aCompiledMethod methodNode schematicTempNamesString allButFirst:
+ (aCompiledMethod methodNode schematicTempNamesString indexOf: $[)) piecesCutWhere: [:a :b| b = $[])
+ collect: [:c :s| c startpc -> s substrings]]))]!

Item was changed:
  ----- Method: Cogit class>>cog:selectorOrNumCopied:options: (in category 'in-image compilation') -----
  cog: aCompiledMethod selectorOrNumCopied: selectorOrNumCopied options: optionsDictionaryOrArray
  "StackToRegisterMappingCogit cog: (Integer >> #benchFib) selector: #benchFib options: #(COGMTVM false)"
  | cogit coInterpreter |
  cogit := self instanceForTests: optionsDictionaryOrArray.
+ self attemptToComputeTempNamesFor: aCompiledMethod.
- (aCompiledMethod respondsTo: #tempNames) ifTrue:
- [initializationOptions at: #tempNames put: aCompiledMethod tempNames].
  coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
  [cogit
  setInterpreter: coInterpreter;
  singleStep: true;
  initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size / 2. "leave space for rump C stack"
  cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
  on: Notification
  do: [:ex|
  (ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  [ex resume: coInterpreter].
  ex pass].
  ^{ coInterpreter.
  cogit.
  selectorOrNumCopied isInteger
  ifTrue: [ cogit cogFullBlockMethod: (coInterpreter oopForObject: aCompiledMethod) numCopied: selectorOrNumCopied ]
  ifFalse: [ cogit cog: (coInterpreter oopForObject: aCompiledMethod) selector: (coInterpreter oopForObject: selectorOrNumCopied) ] }!

Item was changed:
  ----- Method: Cogit>>abstractInstructionAt: (in category 'compile abstract instructions') -----
  abstractInstructionAt: index
  <cmacro: '(index) (&abstractOpcodes[index])'>
+ <returnTypeC: #'AbstractInstruction *'>
  ((debugOpcodeIndices includes: index)
  and: [breakMethod isNil or: [methodObj = breakMethod]]) ifTrue:
  [self halt].
  ^abstractOpcodes at: index!

Item was changed:
  ----- Method: Cogit>>addressIsInFixups: (in category 'testing') -----
  addressIsInFixups: address
+ <var: #address type: #'BytecodeFixup *'>
+ ^self cCode: '(AbstractInstruction *)address >= fixups && (AbstractInstruction *)address < (fixups + numAbstractOpcodes)'
+ inSmalltalk:
+ [fixups notNil
+ and: [(fixups object identityIndexOf: address) between: 1 and: numAbstractOpcodes]]!
- <var: #address type: #'AbstractInstruction *'>
- ^self cCode: 'address >= (AbstractInstruction *)&fixups[0] && address < (AbstractInstruction *)&fixups[numAbstractOpcodes]'
- inSmalltalk: [fixups notNil
- and: [(fixups object identityIndexOf: address) between: 1 and: numAbstractOpcodes]]!

Item was changed:
  ----- Method: Cogit>>blockStartAt: (in category 'compile abstract instructions') -----
  blockStartAt: index
  <cmacro: '(index) (&blockStarts[index])'>
+ "hack set startpc for printSimStack:toDepth:spillBase:on:"
+ (self class initializationOptions at: #tempNames ifAbsent: nil) ifNotNil:
+ [self class initializationOptions at: #startpc put: (blockStarts at: index) startpc].
  ^blockStarts at: index!

Item was changed:
  ----- Method: Cogit>>initialize (in category 'initialization') -----
  initialize
  | wordSize |
+ initialPC := 0.
  wordSize := self class objectMemoryClass wordSize.
  cogMethodSurrogateClass := NewspeakVM
  ifTrue:
  [wordSize = 4
  ifTrue: [NewspeakCogMethodSurrogate32]
  ifFalse: [NewspeakCogMethodSurrogate64]]
  ifFalse:
  [wordSize = 4
  ifTrue: [CogMethodSurrogate32]
  ifFalse: [CogMethodSurrogate64]].
  cogBlockMethodSurrogateClass := wordSize = 4
  ifTrue: [CogBlockMethodSurrogate32]
  ifFalse: [CogBlockMethodSurrogate64].
  nsSendCacheSurrogateClass := wordSize = 4
  ifTrue: [NSSendCacheSurrogate32]
  ifFalse: [NSSendCacheSurrogate64].!

Item was changed:
  StackToRegisterMappingCogit subclass: #RegisterAllocatingCogit
  instanceVariableNames: 'numFixups mergeSimStacksBase nextFixup scratchSimStack scratchSpillBase scratchOptStatus ceSendMustBeBooleanAddTrueLongTrampoline ceSendMustBeBooleanAddFalseLongTrampoline'
  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.
- !RegisterAllocatingCogit commentStamp: 'cb 4/15/2016 14:58' prior: 0!
- RegisterAllocatingCogit is an optimizing code generator that is specialized in 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 CogRegisterAllocatingSimStackEntry>
+ 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>>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 startOpcodeIndex |
- | fixup |
  <var: #fixup type: #'BytecodeFixup *'>
  fixup := self fixupAt:  targetPC.
  fixup needsFixup
  ifTrue:
  [fixup mergeSimStack
  ifNil: [self setMergeSimStackOf: fixup]
+ ifNotNil:
+ [startOpcodeIndex := opcodeIndex.
+ self mergeCurrentSimStackWith: fixup.
+ self deny: (startOpcodeIndex = opcodeIndex and: [thisContext sender method sendsSelector: #mergeRequiredForJumpTo:])]]
- ifNotNil: [self mergeCurrentSimStackWith: fixup]]
  ifFalse:
  [self assert: fixup mergeSimStack isNil.
  self moveVolatileSimStackEntriesToRegisters.
  self setMergeSimStackOf: fixup].
  ^super ensureFixupAt: targetPC!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>ensureNonMergeFixupAt: (in category 'compile abstract instructions') -----
  ensureNonMergeFixupAt: 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 remember the simStack state at the target, if not already there."
+ "self printSimStack; printSimStack: fixup mergeSimStack"
- Override to remember the simStack state at tyeh target, if required."
  | fixup |
  fixup := super ensureNonMergeFixupAt: targetPC.
+ fixup mergeSimStack
+ ifNil: [self setMergeSimStackOf: fixup]
+ ifNotNil: [self assert: simStackPtr = fixup simStackPtr.
+ self deny: (self mergeRequiredToTarget: fixup mergeSimStack)].
+ optStatus isReceiverResultRegLive ifFalse:
+ [fixup isReceiverResultRegSelf: false].
- fixup mergeSimStack ifNil: [self setMergeSimStackOf: fixup].
  ^fixup!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>flushLiveRegistersForCRunTimeCall (in category 'bytecode generator support') -----
  flushLiveRegistersForCRunTimeCall
+ "Flush any live registers for a C call, i.e. don't flush caller-saved registers.
+ Answer if any registers were flushed."
  <inline: true>
+ | flushed reg |
+ flushed := false.
- | reg |
  self assert: simSelf type = SSBaseOffset.
  reg := simSelf liveRegister.
  (reg ~= NoReg and: [(self isCallerSavedReg: reg)]) ifTrue:
+ [simSelf liveRegister: NoReg.
+ flushed := true].
- [simSelf liveRegister: NoReg].
  0 to: simStackPtr do:
  [:i|
  self assert: (self simStackAt: i) type = (i <= methodOrBlockNumTemps
  ifTrue: [SSBaseOffset]
  ifFalse: [SSSpill]).
  reg := (self simStackAt: i) liveRegister.
  (reg ~= NoReg and: [(self isCallerSavedReg: reg)]) ifTrue:
+ [(self simStackAt: i) liveRegister: NoReg.
+ flushed := true]].
+ ^flushed!
- [(self simStackAt: i) liveRegister: NoReg]]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>flushLiveRegistersForSuspensionPoint (in category 'bytecode generator support') -----
+ flushLiveRegistersForSuspensionPoint
+ "Flush any live registers for a C call at a suspension/resumption point, i.e.flush all registers.
+ Answer if any registers were flushed."
+ <inline: true>
+ | flushed |
+ flushed := false.
+ self assert: simSelf type = SSBaseOffset.
+ simSelf liveRegister ~= NoReg ifTrue:
+ [simSelf liveRegister: NoReg.
+ flushed := true].
+ 0 to: simStackPtr do:
+ [:i|
+ self assert: (self simStackAt: i) type = (i <= methodOrBlockNumTemps
+ ifTrue: [SSBaseOffset]
+ ifFalse: [SSSpill]).
+ (self simStackAt: i) liveRegister ~= NoReg ifTrue:
+ [(self simStackAt: i) liveRegister: NoReg.
+ flushed := true]].
+ ^flushed!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
+ | nextPC branchDescriptor unforwardRcvr argReg targetPC
+  unforwardArg  rcvrReg postBranchPC retry fixup
+  comparison
+  needMergeToTarget needMergeToContinue |
- | nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
- unforwardArg  rcvrReg postBranchPC label fixup |
  <var: #branchDescriptor type: #'BytecodeDescriptor *'>
+ <var: #toContinueLabel type: #'AbstractInstruction *'>
+ <var: #toTargetLabel type: #'AbstractInstruction *'>
+ <var: #comparison type: #'AbstractInstruction *'>
+ <var: #retry type: #'AbstractInstruction *'>
- <var: #label type: #'AbstractInstruction *'>
 
  self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target |
+ branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := target ].
- branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
 
  "If an operand is an annotable constant, it may be forwarded, so we need to store it into a
  register so the forwarder check can jump back to the comparison after unforwarding the constant.
  However, if one of the operand is an unnanotable constant, does not allocate a register for it
  (machine code will use operations on constants) and does not generate forwarder checks."
  unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
 
  self
  allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg
  rcvrNeedsReg: unforwardRcvr
  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
- [^ self
  genIdenticalNoBranchArgIsConstant: unforwardArg not
  rcvrIsConstant: unforwardRcvr not
  argReg: argReg
  rcvrReg: rcvrReg
  orNotIf: orNot].
 
+ self assert: (unforwardArg or: [unforwardRcvr]).
+
+ retry := self Label.
- label := self Label.
  self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  self ssPop: 2.
 
+ (self fixupAt: nextPC) notAFixup "The next instruction is dead.  we can skip it."
+ ifTrue:  [deadCode := true]
+ ifFalse: [self deny: deadCode]. "push dummy value below"
- "For now just deny we're in the situation we have yet to implement ;-)
- self printSimStack; printSimStack: (self fixupAt: postBranchPC) mergeSimStack"
- self deny: (self mergeRequiredForJumpTo: targetBytecodePC).
- self deny: (self mergeRequiredForJumpTo: postBranchPC).
 
+ "self printSimStack; printSimStack: (self fixupAt: postBranchPC) mergeSimStack"
+ "If there are merges to be performed on the forward branches we have to execute
+ the merge code only along the path requiring that merge, and exactly once."
+ needMergeToTarget := self mergeRequiredForJumpTo: targetPC.
+ needMergeToContinue := self mergeRequiredForJumpTo: postBranchPC.
+ orNot == branchDescriptor isBranchTrue
+ ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
+ [fixup := needMergeToContinue
+ ifTrue: [0] "jumps will fall-through to to-continue merge code"
+ ifFalse: [self ensureNonMergeFixupAt: postBranchPC].
+ comparison := self JumpZero: (needMergeToTarget
+ ifTrue: [0] "comparison will be fixed up to to-target merge code"
+ ifFalse: [self ensureNonMergeFixupAt: targetPC])]
+ ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
+ [fixup := needMergeToTarget
+ ifTrue: [0] "jumps will fall-through to to-target merge code"
+ ifFalse: [(self ensureNonMergeFixupAt: targetPC)].
+ comparison := self JumpZero: (needMergeToContinue
+ ifTrue: [0] "comparison will be fixed up to to-continue merge code"
+ ifFalse: [self ensureNonMergeFixupAt: postBranchPC])].
- "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: targetBytecodePC.
- self ensureFixupAt: postBranchPC]
- ifFalse:
- [self deny: deadCode]. "push dummy value below"
 
+ "The forwarders check(s) need(s) to jump back to the comparison (retry) if a forwarder is found,
+ else jump forward either to the next forwarder check or to the postBranch or branch target (fixup).
+ But if there is merge code along a path, the jump must be to the merge code."
+ (unforwardArg and: [unforwardRcvr]) ifTrue:
+ [objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: retry].
+ objectRepresentation
+ genEnsureOopInRegNotForwarded: (unforwardRcvr ifTrue: [rcvrReg] ifFalse: [argReg])
+ scratchReg: TempReg
+ ifForwarder: retry
+ ifNotForwarder: fixup.
+ "If fixup is zero then the ifNotForwarder path falls through to a Label which is interpreted
+ as either to-continue or to-target, depending on orNot == branchDescriptor isBranchTrue."
+ orNot == branchDescriptor isBranchTrue
+ ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
+ [needMergeToContinue ifTrue: "fall-through to to-continue merge code"
+ [self Jump: (self ensureFixupAt: postBranchPC)].
+ needMergeToTarget ifTrue: "fixup comparison to to-target merge code"
+ [comparison jmpTarget: self Label.
+ self Jump: (self ensureFixupAt: targetPC)]]
+ ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
+ [needMergeToTarget ifTrue: "fall-through to to-target merge code"
+ [self Jump: (self ensureFixupAt: targetPC)].
+ needMergeToContinue ifTrue: "fixup comparison to to-continue merge code"
+ [comparison jmpTarget: self Label.
+ self Jump: (self ensureFixupAt: postBranchPC)]].
- self assert: (unforwardArg or: [unforwardRcvr]).
- orNot == branchDescriptor isBranchTrue "orNot is true for ~~"
- ifFalse: "branchDescriptor is branchFalse"
- [ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
- self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ]
- ifTrue:
- [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
- self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ].
 
  deadCode ifFalse:
  [self ssPushConstant: objectMemory trueObject]. "dummy value"
- "The forwarders checks need to jump back to the comparison (label) if a forwarder is found, else
- jump forward either to the next forwarder check or to the postBranch or branch target (fixup)."
- unforwardArg ifTrue:
- [ unforwardRcvr
- ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
- ifFalse: [ objectRepresentation
- genEnsureOopInRegNotForwarded: argReg
- scratchReg: TempReg
- ifForwarder: label
- ifNotForwarder: fixup ] ].
- unforwardRcvr ifTrue:
- [ objectRepresentation
- genEnsureOopInRegNotForwarded: rcvrReg
- scratchReg: TempReg
- ifForwarder: label
- ifNotForwarder: fixup ].
-
- "Not reached, execution flow have jumped to fixup"
-
  ^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genJumpBackTo: (in category 'bytecode generator support') -----
  genJumpBackTo: targetBytecodePC
  | nothingToFlush label |
  <var: #label type: #'AbstractInstruction *'>
  "If there's nothing to flush then the stack state at this point is the same as that after
+ the check for interrupts and we can avoid generating the register reload code twice."
+ nothingToFlush := (self liveRegisters bitClear: (self registerMaskFor: FPReg)) = 0.
+ nothingToFlush ifTrue:
- the check for interrups and we can avoid generating the register reload code twice."
- (nothingToFlush := simStackPtr < 0 or: [self ssTop spilled]) ifTrue:
  [label := self Label].
  self reconcileRegisterStateForBackwardJoin: (self fixupAt: targetBytecodePC).
  self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  self JumpAboveOrEqual: (self fixupAt: targetBytecodePC).
 
  self ssFlushTo: simStackPtr.
  self CallRT: ceCheckForInterruptTrampoline.
  self annotateBytecode: self Label.
+ self flushLiveRegistersForSuspensionPoint.
  nothingToFlush
  ifTrue:
  [self Jump: label]
  ifFalse:
  [self reconcileRegisterStateForBackwardJoin: (self fixupAt: targetBytecodePC).
  self Jump: (self fixupAt: targetBytecodePC)].
  deadCode := true. "can't fall through"
  ^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  <inline: false>
  | eventualTarget desc reg fixup ok mbb noMustBeBoolean |
  <var: #fixup type: #'BytecodeFixup *'>
  <var: #ok type: #'AbstractInstruction *'>
  <var: #desc type: #'CogSimStackEntry *'>
  <var: #mbb type: #'AbstractInstruction *'>
  eventualTarget := self eventualTargetOf: targetBytecodePC.
  desc := self ssTop.
  self ssPop: 1.
 
  noMustBeBoolean := self extASpecifiesNoMustBeBoolean.
  extA := 0.
 
  (desc type == SSConstant
  and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  ["Must annotate the bytecode for correct pc mapping."
  desc constant = boolean
  ifTrue:
  [deadCode := true. "Can't fall through."
  fixup := self ensureFixupAt: eventualTarget.
  self annotateBytecode: (self Jump: fixup)]
  ifFalse:
  [self annotateBytecode: (self prevInstIsPCAnnotated
  ifTrue: [self Nop]
  ifFalse: [self Label])].
  ^0].
 
  "try and use the top entry's register if any, but only if it can be destroyed."
  reg := (desc type ~= SSRegister
  or: [(self anyReferencesToRegister: desc register inAllButTopNItems: 0)
  or: [(desc register = ReceiverResultReg and: [optStatus isReceiverResultRegLive])]])
  ifTrue: [TempReg]
  ifFalse: [desc register].
  desc popToReg: reg.
  "Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  Correct result is either 0 or the distance between them.  If result is not 0 or
  their distance send mustBeBoolean."
  self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
 
  "Merge required; must not generate merge code along untaken branch, so flip the order."
  (self mergeRequiredForJumpTo: eventualTarget)
  ifTrue:
  [self genSubConstant: (boolean = objectMemory trueObject
  ifTrue: [objectMemory falseObject]
  ifFalse: [objectMemory trueObject])
  R: reg.
  ok := self JumpZero: 0.
  self CmpCq: (boolean = objectMemory trueObject
  ifTrue: [objectMemory trueObject - objectMemory falseObject]
  ifFalse: [objectMemory falseObject - objectMemory trueObject])
  R: reg.
  noMustBeBoolean ifTrue:
  [self JumpZero: (self ensureFixupAt: eventualTarget). "generates merge code"
  ok jmpTarget: (self annotateBytecode: self lastOpcode).
  ^0].
  mbb := self JumpNonZero: 0.
  self Jump: (self ensureFixupAt: eventualTarget). "generates merge code"
  mbb jmpTarget: self Label]
  ifFalse:
  [self genSubConstant: boolean R: reg.
+ self JumpZero: (self ensureNonMergeFixupAt: eventualTarget).
- self JumpZero: (self ensureFixupAt: eventualTarget).
  noMustBeBoolean ifTrue:
  [self annotateBytecode: self lastOpcode.
  ^0].
  self CmpCq: (boolean = objectMemory falseObject
  ifTrue: [objectMemory trueObject - objectMemory falseObject]
  ifFalse: [objectMemory falseObject - objectMemory trueObject])
  R: reg.
  ok := self JumpZero: 0].
 
  reg ~= TempReg ifTrue:
  [self MoveR: reg R: TempReg].
  self copySimStackToScratch: simSpillBase.
  self ssFlushTo: simStackPtr.
  self genCallMustBeBooleanFor: boolean.
  "NOTREACHED"
  ok jmpTarget: (self annotateBytecode: self Label).
  self restoreSimStackFromScratch.
  ^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
+ | nextPC postBranchPC targetPC primDescriptor branchDescriptor
+  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index rcvrReg argReg branchToTarget needMergeToContinue needMergeToTarget |
- | nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
-  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index rcvrReg argReg |
  <var: #primDescriptor type: #'BytecodeDescriptor *'>
  <var: #branchDescriptor type: #'BytecodeDescriptor *'>
  <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  primDescriptor := self generatorAt: byte0.
  argIsInt := self ssTop type = SSConstant
  and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  rcvrIsInt := (self ssValue: 1) type = SSConstant
  and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
 
  (argIsInt and: [rcvrIsInt]) ifTrue:
  [^self genStaticallyResolvedSpecialSelectorComparison].
 
  self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target |
+ branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := target ].
- branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
 
  "Only interested in inlining if followed by a conditional branch."
  inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  "Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  (inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  [inlineCAB := argIsInt or: [rcvrIsInt]].
  inlineCAB ifFalse:
  [^self genSpecialSelectorSend].
 
  "In-line the comparison and the jump, but if the types are not SmallInteger then we will need
  to do a send and fall through to the following conditional branch.  Since we're allocating values
  in registers we would like to keep those registers live on the inlined path and reload registers
  along the non-inlined send path.  The merge logic at the branch destinations handles this."
  argIsInt
  ifTrue:
  [rcvrReg := self allocateRegForStackEntryAt: 1.
+ (self ssValue: 1) popToReg: rcvrReg]
- (self ssValue: 1) popToReg: rcvrReg.
- self MoveR: rcvrReg R: TempReg]
  ifFalse:
  [self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  rcvrReg = Arg0Reg ifTrue:
  [rcvrReg := argReg. argReg := Arg0Reg].
  self ssTop popToReg: argReg.
  (self ssValue: 1) popToReg: rcvrReg.
+ rcvrIsInt ifFalse:
+ [self MoveR: argReg R: TempReg]].
- self MoveR: argReg R: TempReg].
  self ssPop: 2.
  jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
+ ifFalse: "Neither known to be ints; and them together for the test..."
+ [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch: TempReg scratch: ClassReg]
+ ifTrue: "One known; in-place single-bit test for the other"
+ [objectRepresentation genJumpNotSmallInteger: (rcvrIsInt ifTrue: [argReg] ifFalse: [rcvrReg])].
- ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
- ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch: TempReg scratch: ClassReg].
  argIsInt
  ifTrue: [self CmpCq: argInt R: rcvrReg]
  ifFalse: [self CmpR: argReg R: rcvrReg].
 
+ "self printSimStack; printSimStack: (self fixupAt: postBranchPC) mergeSimStack; printSimStack: (self fixupAt: targetPC) mergeSimStack"
+ "If there are merges to be performed on the forward branches we have to execute
+ the merge code only along the path requiring that merge, and exactly once."
+ needMergeToTarget := self mergeRequiredForJumpTo: targetPC.
+ needMergeToContinue := self mergeRequiredForJumpTo: postBranchPC.
+ "Cmp is weird/backwards so invert the comparison."
+ (needMergeToTarget and: [needMergeToContinue]) ifTrue:
+ [branchToTarget := self genConditionalBranch: (branchDescriptor isBranchTrue
+ ifTrue: [primDescriptor opcode]
+ ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ operand: 0.
+ self Jump: (self ensureFixupAt: postBranchPC).
+ branchToTarget jmpTarget: self Label.
+ self Jump: (self ensureFixupAt: targetPC)].
+ (needMergeToTarget and: [needMergeToContinue not]) ifTrue:
+ [self genConditionalBranch: (branchDescriptor isBranchFalse
+ ifTrue: [primDescriptor opcode]
+ ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ operand: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
+ self Jump: (self ensureFixupAt: targetPC)].
+ (needMergeToTarget not and: [needMergeToContinue]) ifTrue:
+ [self genConditionalBranch: (branchDescriptor isBranchTrue
+ ifTrue: [primDescriptor opcode]
+ ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ operand: (self ensureNonMergeFixupAt: targetPC) asUnsignedInteger.
+ self Jump: (self ensureFixupAt: postBranchPC)].
+ (needMergeToTarget or: [needMergeToContinue]) ifFalse:
+ [self genConditionalBranch: (branchDescriptor isBranchTrue
+ ifTrue: [primDescriptor opcode]
+ ifFalse: [self inverseBranchFor: primDescriptor opcode])
+ operand: (self ensureNonMergeFixupAt: targetPC) asUnsignedInteger.
+ self Jump: (self ensureNonMergeFixupAt: postBranchPC)].
- "For now just deny we're in the situation we have yet to implement ;-)"
- self deny: (self mergeRequiredForJumpTo: targetBytecodePC).
- self deny: (self mergeRequiredForJumpTo: postBranchPC).
-
- "Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
- jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
- self genConditionalBranch: (branchDescriptor isBranchTrue
- ifTrue: [primDescriptor opcode]
- ifFalse: [self inverseBranchFor: primDescriptor opcode])
- operand: (self ensureFixupAt: targetBytecodePC) asUnsignedInteger.
- self Jump: (self ensureFixupAt: postBranchPC).
  jumpNotSmallInts jmpTarget: self Label.
  self ssFlushTo: simStackPtr.
  self deny: rcvrReg = Arg0Reg.
  argIsInt
  ifTrue: [self MoveCq: argInt R: Arg0Reg]
  ifFalse: [argReg ~= Arg0Reg ifTrue: [self MoveR: argReg R: Arg0Reg]].
  rcvrReg ~= ReceiverResultReg ifTrue: [self MoveR: rcvrReg R: ReceiverResultReg].
  index := byte0 - self firstSpecialSelectorBytecodeOffset.
  ^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeRequiredForJumpTo: (in category 'bytecode generator support') -----
  mergeRequiredForJumpTo: targetPC
  "While this is a multi-pass compiler, no intermediate control-flow graph is built from bytecode and
  there is a monotonically increasing one-to-one relationship between bytecode pcs and machine
  code pcs that map to one another.  Therefore, when jumping forward, any required code to merge
  the state of the current simStack with that at the target must be generated before the jump
  (because at the target the simStack state will be whatever falls through). If only one forward jump
  to the target exists then that jump can simply install its simStack as the required simStack at the
  target and the merge code wil be generated just before the target as control falls through.  But if
  there are two or more forward jumps to the target, a situation that occurs given that the
  StackToRegisterMappingCogit follows jump chains, then jumps other than the first must generate
  merge code before jumping.  This poses a problem for conditional branches.  The merge code must
  only be generated along the path that takes the jump  Therefore this must *not* be generated:
 
  ... merge code ...
  jump cond Ltarget
 
  which incorrectly executes the merge code along both the taken and untaken paths.  Instead
  this must be generated so that the merge code is only executed if the branch is taken.
 
  jump not cond Lcontinue
  ... merge code ...
  jump Ltarget
  Lcontinue:
 
  Note that no merge code is required for code such as self at: (expr ifTrue: [1] ifFalse: [2])
  17 <70> self
  18 <71> pushConstant: true
  19 <99> jumpFalse: 22
  20 <76> pushConstant: 1
  21 <90> jumpTo: 23
  22 <77> pushConstant: 2
  23 <C0> send: at:
  provided that 1 and 2 are assigned to the same target register."
+ | fixup |
+ (fixup := self fixupAt: targetPC) hasMergeSimStack ifFalse:
+ [^false].
+ self assert: simStackPtr = fixup simStackPtr.
+ ^self mergeRequiredToTarget: fixup mergeSimStack!
-
- self flag: 'be lazy for now; this needs more work to ignore compatible sim stacks'.
- ^(self fixupAt: targetPC) hasMergeSimStack!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>mergeRequiredToTarget: (in category 'bytecode generator support') -----
+ mergeRequiredToTarget: targetSimStack
+ <var: 'targetSimStack' type: #'SimStackEntry *'>
+ <inline: true>
+ <var: 'here' type: #'SimStackEntry *'>
+ <var: 'there' type: #'SimStackEntry *'>
+ simStackPtr to: 0 by: -1 do:
+ [:i| | here there |
+ here := self simStack: simStack at: i.
+ there := self simStack: targetSimStack at: i.
+ (here isMergedWithTargetEntry: there) ifFalse:
+ [^true]].
+ ^false!

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.
  flushes the stack to the stack pointer so the fall through execution path simStack is
  in the state the merge point expects it to be.
  restores the simStack to the state the jumps to the merge point expects it to be.
 
  In addition, if this is a backjump merge point, we patch the fixup to hold the current simStackPtr
  for later assertions."
 
  <var: #fixup type: #'BytecodeFixup *'>
  "case 1"
+ fixup notAFixup ifTrue: [^0].
- fixup notAFixup ifTrue: [^ 0].
 
  "case 2"
+ fixup isNonMergeFixup ifTrue:
+ [deadCode ifTrue:
+ [self deny: fixup simStackPtr isNil.
+ simStackPtr := fixup simStackPtr.
+ self restoreSimStackAtMergePoint: fixup.
+ deadCode := false].
+ ^0].
- fixup isNonMergeFixup ifTrue: [deadCode := false. ^ 0 ].
 
  "cases 3 and 4"
  self assert: fixup isMergeFixup.
  self traceMerge: fixup.
  deadCode
  ifTrue: [simStackPtr := fixup simStackPtr] "case 3"
  ifFalse: [self mergeCurrentSimStackWith: fixup]. "case 4"
  "cases 3 and 4"
  deadCode := false.
  fixup isBackwardBranchFixup ifTrue:
  [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>>moveVolatileSimStackEntriesToRegisters (in category 'bytecode generator support') -----
  moveVolatileSimStackEntriesToRegisters
+ "When jumping forward to a merge point the stack must be reconcilable with the state that falls through to the merge point.
- "When jumping forward to a merge point the stack mst be reconcilable with the state that falls through to the merge point.
  We cannot easily arrange that later we add code to the branch, e.g. to spill values.  Instead, any volatile contents must be
  moved to registers.  [In fact, that's not exactly true, consider these two code sequences:
  self at: (expr ifTrue: [1] ifFalse: [2]) put: a
  self at: 1 put: (expr ifTrue: [a] ifFalse: [b])
  The first one needs 1 saving to a register to reconcile with 2.
  The second one has 1 on both paths, but we're not clever enough to spot this case yet.]
  Volatile contents are anything not spilled to the stack, because as yet we can only merge registers."
  <inline: true>
  <var: #desc type: #'SimStackEntry *'>
  (simSpillBase max: 0) to: simStackPtr do:
  [:i| | desc reg |
  desc := self simStackAt: i.
  desc spilled
  ifTrue: [simSpillBase := i]
  ifFalse:
  [desc registerOrNone = NoReg ifTrue:
  [reg := self allocateRegNotConflictingWith: 0.
  reg = NoReg
  ifTrue: [self halt] "have to spill"
  ifFalse: [desc storeToReg: reg]]]]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>simStack:isIdenticalTo: (in category 'simulation stack') -----
+ simStack: aSimStack isIdenticalTo: bSimStack
+ <var: 'aSimStack' type: #'SimStackEntry *'>
+ <var: 'bSimStack' type: #'SimStackEntry *'>
+ 0 to: simStackPtr do:
+ [:i|
+ ((self simStack: aSimStack at: i) isIdenticalEntryAs: (self simStack: bSimStack at: i)) ifFalse:
+ [^false]].
+ ^true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtPushClosureBytecode (in category 'bytecode generators') -----
  genExtPushClosureBytecode
  "Block compilation.  At this point in the method create the block.  Note its start
  and defer generating code for it until after the method and any other preceding
  blocks.  The block's actual code will be compiled later."
  "253 11111101 eei i i kkk jjjjjjjj Push Closure Num Copied iii (+ Ext A // 16 * 8) Num Args kkk (+ Ext A \\ 16 * 8) BlockSize jjjjjjjj (+ Ext B * 256). ee = num extensions"
+ | startpc numArgs numCopied |
- | numArgs numCopied |
  self assert: needsFrame.
+ startpc := bytecodePC + (self generatorAt: byte0) numBytes.
+ self addBlockStartAt: startpc "0 relative"
- self addBlockStartAt: bytecodePC + 3 "0 relative"
  numArgs: (numArgs := (byte1 bitAnd: 16r7) + (extA \\ 16 * 8))
  numCopied: (numCopied := ((byte1 >> 3) bitAnd: 7) + (extA // 16 * 8))
  span: byte2 + (extB << 8).
  extA := numExtB := extB := 0.
  objectRepresentation
+ genCreateClosureAt: startpc + 1 "1 relative"
- genCreateClosureAt: bytecodePC + 4 "1 relative"
  numArgs: numArgs
  numCopied: numCopied
  contextNumArgs: methodOrBlockNumArgs
  large: (coInterpreter methodNeedsLargeContext: methodObj)
  inBlock: inBlock.
  self PushR: ReceiverResultReg.
  ^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPushClosureCopyCopiedValuesBytecode (in category 'bytecode generators') -----
  genPushClosureCopyCopiedValuesBytecode
  "Block compilation.  At this point in the method create the block.  Note its start
  and defer generating code for it until after the method and any other preceding
  blocks.  The block's actual code will be compiled later."
  "143   10001111 llllkkkk jjjjjjjj iiiiiiii Push Closure Num Copied llll Num Args kkkk BlockSize jjjjjjjjiiiiiiii"
+ | startpc numArgs numCopied |
- | numArgs numCopied |
  self assert: needsFrame.
+ startpc := bytecodePC + (self generatorAt: byte0) numBytes.
+ self addBlockStartAt: startpc "0 relative"
- self addBlockStartAt: bytecodePC + 4 "0 relative"
  numArgs: (numArgs := byte1 bitAnd: 16rF)
  numCopied: (numCopied := byte1 >> 4)
  span: (byte2 << 8) + byte3.
  objectRepresentation
+ genCreateClosureAt: startpc + 1 "1 relative"
- genCreateClosureAt: bytecodePC + 5 "1 relative"
  numArgs: numArgs
  numCopied: numCopied
  contextNumArgs: methodOrBlockNumArgs
  large: (coInterpreter methodNeedsLargeContext: methodObj)
  inBlock: inBlock.
  self PushR: ReceiverResultReg.
  ^0!

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 blockPass'
  classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag'
  poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
  category: 'VMMaker-JIT'!
  StackToRegisterMappingCogit class
  instanceVariableNames: 'numPushNilsFunction pushNilSizeFunction'!
 
+ !StackToRegisterMappingCogit commentStamp: 'eem 2/9/2017 10:07' prior: 0!
- !StackToRegisterMappingCogit commentStamp: 'eem 6/1/2016 14:50' 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
  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)>
  methodAbortTrampolines: <CArrayAccessor of Integer>
  methodOrBlockNumTemps: <Integer>
  optStatus: <Integer>
  picAbortTrampolines: <CArrayAccessor of Integer>
  picMissTrampolines: <CArrayAccessor of Integer>
  realCEEnterCogCodePopReceiverArg0Regs: <Integer>
  realCEEnterCogCodePopReceiverArg1Arg0Regs: <Integer>
  regArgsHaveBeenPushed: <Boolean>
  simSelf: <CogSimStackEntry>
  simSpillBase: <Integer>
  simStack: <CArrayAccessor of CogSimStackEntry>
  simStackPtr: <Integer>
  traceSimStack: <Integer>
  useTwoPaths <Boolean>
 
  callerSavedRegMask
  - the bitmask of the ABI's caller-saved registers
 
  ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
  - the trampoline for entering an N-arg PIC
 
  ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
+ - the trampoline for entering a method with N register args
- - teh trampoline for entering a method with N register args
 
  debugBytecodePointers
  - a Set of bytecode pcs for setting breakpoints (simulation only)
 
  debugFixupBreaks
  - a Set of fixup indices for setting breakpoints (simulation only)
 
  debugStackPointers
  - an Array of stack depths for each bytecode for code verification
 
  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
 
  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
 
  realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
  - the real trampolines for ebtering 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)
 
  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>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') -----
  genForwardersInlinedIdenticalOrNotIf: orNot
  | nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC
+  unforwardArg  rcvrReg postBranchPC label fixup |
- unforwardArg  rcvrReg postBranchPC label fixup |
  <var: #branchDescriptor type: #'BytecodeDescriptor *'>
  <var: #label type: #'AbstractInstruction *'>
 
  self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target |
  branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
 
  "If an operand is an annotable constant, it may be forwarded, so we need to store it into a
  register so the forwarder check can jump back to the comparison after unforwarding the constant.
  However, if one of the operand is an unnanotable constant, does not allocate a register for it
  (machine code will use operations on constants) and does not generate forwarder checks."
  unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not.
  unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not.
 
  self
  allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg
  rcvrNeedsReg: unforwardRcvr
  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: unforwardArg not
  rcvrIsConstant: unforwardRcvr not
  argReg: argReg
  rcvrReg: rcvrReg
  orNotIf: orNot].
 
  "If branching the stack must be flushed for the merge"
  self ssFlushTo: simStackPtr - 2.
 
  label := self Label.
  self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg.
  self ssPop: 2.
 
+ "Since there is a following conditional jump bytecode (unless there is deadCode),
+ define non-merge fixups and leave the cond bytecode to set the mergeness."
- "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: targetBytecodePC.
  self ensureFixupAt: postBranchPC]
  ifFalse:
  [self deny: deadCode]. "push dummy value below"
 
  self assert: (unforwardArg or: [unforwardRcvr]).
  orNot == branchDescriptor isBranchTrue "orNot is true for ~~"
+ ifFalse: "a == b ifTrue: ... or a ~~ b ifFalse: ... jump on equal to target pc"
+ [fixup := self ensureNonMergeFixupAt: postBranchPC.
+ self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC)]
+ ifTrue: "a == b ifFalse: ... or a ~~ b ifTrue: ... jump on equal to post-branch pc"
+ [fixup := self ensureNonMergeFixupAt: targetBytecodePC.
+ self JumpZero: (self ensureNonMergeFixupAt: postBranchPC)].
- ifFalse:
- [ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger.
- self JumpZero:  (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ]
- ifTrue:
- [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
- self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ].
-
- deadCode ifFalse:
- [self ssPushConstant: objectMemory trueObject]. "dummy value"
 
  "The forwarders checks need to jump back to the comparison (label) if a forwarder is found, else
+ jump forward either to the next forwarder check or to the postBranch or branch target (fixup)."
+ (unforwardArg and: [unforwardRcvr]) ifTrue:
+ [objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label].
+ objectRepresentation
+ genEnsureOopInRegNotForwarded: (unforwardRcvr ifTrue: [rcvrReg] ifFalse: [argReg])
+ scratchReg: TempReg
+ ifForwarder: label
+ ifNotForwarder: fixup.
- jump forward either to the next forwarder check or to the postBranch or branch target (fixup)."
- unforwardArg ifTrue:
- [ unforwardRcvr
- ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg jumpBackTo: label ]
- ifFalse: [ objectRepresentation
- genEnsureOopInRegNotForwarded: argReg
- scratchReg: TempReg
- ifForwarder: label
- ifNotForwarder: fixup ] ].
- unforwardRcvr ifTrue:
- [ objectRepresentation
- genEnsureOopInRegNotForwarded: rcvrReg
- scratchReg: TempReg
- ifForwarder: label
- ifNotForwarder: fixup ].
 
+ "Not reached, execution flow has jumped to fixup"
+ deadCode ifFalse:
+ [self ssPushConstant: objectMemory trueObject]. "dummy value"
- "Not reached, execution flow have jumped to fixup"
-
  ^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  | nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
   rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index |
  <var: #primDescriptor type: #'BytecodeDescriptor *'>
  <var: #branchDescriptor type: #'BytecodeDescriptor *'>
  <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  self ssFlushTo: simStackPtr - 2.
  primDescriptor := self generatorAt: byte0.
  argIsInt := self ssTop type = SSConstant
  and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  rcvrIsInt := (self ssValue: 1) type = SSConstant
  and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
 
  (argIsInt and: [rcvrIsInt]) ifTrue:
  [^ self genStaticallyResolvedSpecialSelectorComparison].
 
  self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target |
  branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
 
  "Only interested in inlining if followed by a conditional branch."
  inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  "Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  (inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  [inlineCAB := argIsInt or: [rcvrIsInt]].
  inlineCAB ifFalse:
  [^self genSpecialSelectorSend].
 
  argIsInt
  ifTrue:
  [(self ssValue: 1) popToReg: ReceiverResultReg.
+ self ssPop: 2]
- self ssPop: 2.
- self MoveR: ReceiverResultReg R: TempReg]
  ifFalse:
  [self marshallSendArguments: 1.
+ rcvrIsInt ifFalse:
+ [self MoveR: Arg0Reg R: TempReg]].
- self MoveR: Arg0Reg R: TempReg].
  jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
+ ifFalse: "Neither known to be ints; and them together for the test..."
+ [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg]
+ ifTrue: "One known; in-place single-bit test for the other"
+ [objectRepresentation genJumpNotSmallInteger: (rcvrIsInt ifTrue: [Arg0Reg] ifFalse: [ReceiverResultReg])].
- ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
- ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg].
  argIsInt
  ifTrue: [self CmpCq: argInt R: ReceiverResultReg]
  ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  "Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  self genConditionalBranch: (branchDescriptor isBranchTrue
  ifTrue: [primDescriptor opcode]
  ifFalse: [self inverseBranchFor: primDescriptor opcode])
  operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger.
  self Jump: (self ensureNonMergeFixupAt: postBranchPC).
  jumpNotSmallInts jmpTarget: self Label.
  argIsInt ifTrue:
  [self MoveCq: argInt R: Arg0Reg].
  index := byte0 - self firstSpecialSelectorBytecodeOffset.
  ^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateInstructionsAt: (in category 'generate machine code') -----
  generateInstructionsAt: eventualAbsoluteAddress
  "Size pc-dependent instructions and assign eventual addresses to all instructions.
  Answer the size of the code.
  Compute forward branches based on virtual address (abstract code starts at 0),
  assuming that any branches branched over are long.
  Compute backward branches based on actual address.
  Reuse the fixups array to record the pc-dependent instructions that need to have
  their code generation postponed until after the others.
 
  Override to andd handling for null branches (branches to the immediately following
  instruction) occasioned by StackToRegisterMapping's following of jumps."
  | absoluteAddress pcDependentIndex abstractInstruction fixup |
  <var: #abstractInstruction type: #'AbstractInstruction *'>
  <var: #fixup type: #'BytecodeFixup *'>
  absoluteAddress := eventualAbsoluteAddress.
  pcDependentIndex := 0.
  0 to: opcodeIndex - 1 do:
  [:i|
  self maybeBreakGeneratingAt: absoluteAddress.
  abstractInstruction := self abstractInstructionAt: i.
  abstractInstruction isPCDependent
  ifTrue:
  [abstractInstruction sizePCDependentInstructionAt: absoluteAddress.
  (abstractInstruction isJump
+  and: [(i + 1 < opcodeIndex
+   and: [abstractInstruction getJmpTarget == (self abstractInstructionAt: i + 1)])
+ or: [i + 2 < opcodeIndex
+ and: [abstractInstruction getJmpTarget == (self abstractInstructionAt: i + 2)
+ and: [(self abstractInstructionAt: i + 1) opcode = Nop]]]])
-  and: [i + 1 < opcodeIndex
-  and: [abstractInstruction getJmpTarget == (self abstractInstructionAt: i + 1)]])
  ifTrue:
  [abstractInstruction
  opcode: Nop;
  concretizeAt: absoluteAddress]
  ifFalse:
  [fixup := self fixupAtIndex: pcDependentIndex.
  pcDependentIndex := pcDependentIndex + 1.
  fixup instructionIndex: i].
  absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]
  ifFalse:
  [absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].
  0 to: pcDependentIndex - 1 do:
  [:j|
  fixup := self fixupAtIndex: j.
  abstractInstruction := self abstractInstructionAt: fixup instructionIndex.
  self maybeBreakGeneratingAt: abstractInstruction address.
  abstractInstruction concretizeAt: abstractInstruction address].
  ^absoluteAddress - eventualAbsoluteAddress!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>printSimStack:toDepth:spillBase:on: (in category 'simulation only') -----
  printSimStack: aSimStack toDepth: limit spillBase: spillBase on: aStream
  <doNotGenerate>
+ | tempNames width tabWidth |
- | tempNamesOrNil width tabWidth |
  aStream ensureCr.
  limit < 0 ifTrue:
  [^aStream nextPutAll: 'simStackEmpty'; cr; flush].
+ aSimStack ifNil:
+ [^aStream nextPutAll: 'nil simStack'; cr; flush].
+ (self class initializationOptions at: #tempNames ifAbsent: nil) ifNotNil:
+ [:tempNamesDictOrNil | | tab longest |
+ tempNames := tempNamesDictOrNil at: (self class initializationOptions at: #startpc ifAbsent: [initialPC]) + 1.
+ longest := tempNames inject: '' into: [:m :t| m size >= t size ifTrue: [m] ifFalse: [t]].
+ tabWidth := self widthInDefaultFontOf: (tab := String with: Character tab).
+ width := self widthInDefaultFontOf: longest, tab.
+ width <= ((self widthInDefaultFontOf: longest, (String with: Character space)) + 4) ifTrue:
+ [width := width + tabWidth]].
- inBlock ~~ true ifTrue:
- [(tempNamesOrNil := self class initializationOptions at: #tempNames ifAbsent: [#()]) isEmpty ifFalse:
- [| tab longest |
- longest := tempNamesOrNil inject: '' into: [:m :t| m size >= t size ifTrue: [m] ifFalse: [t]].
- tabWidth := self widthInDefaultFontOf: (tab := String with: Character tab).
- width := self widthInDefaultFontOf: longest, tab.
- width <= ((self widthInDefaultFontOf: longest, (String with: Character space)) + 4) ifTrue:
- [width := width + tabWidth]]].
  0 to: limit do:
  [:i|
  width ifNotNil:
+ [self put: (tempNames at: i + 1 ifAbsent: ['']) paddedTo: width tabWidth: tabWidth on: aStream].
- [self put: (tempNamesOrNil at: i + 1 ifAbsent: ['']) paddedTo: width tabWidth: tabWidth on: aStream].
  aStream print: i.
  i = spillBase
  ifTrue: [aStream nextPutAll: ' sb'; tab]
  ifFalse: [aStream tab; tab].
  (aSimStack at: i) printStateOn: aStream.
  aStream cr; flush]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>updateSimSpillBase (in category 'simulation stack') -----
  updateSimSpillBase
+ <inline: true>
  simSpillBase > simStackPtr ifTrue:
  [simSpillBase := simStackPtr max: 0].!

Item was changed:
  ----- Method: TMethod>>isFunctionalIn: (in category 'inlining') -----
  isFunctionalIn: aCodeGen
  "Answer if the receiver is a functional method. That is, if it
  consists of a single return statement of an expression that
  contains no other returns, or an assert or flag followed by
  such a statement.
 
  Answer false for methods with return types other than the simple
  integer types to work around bugs in the inliner."
 
  parseTree statements size = 1 ifFalse:
  [(parseTree statements size = 2
   and: [parseTree statements first isSend
   and: [parseTree statements first selector == #flag:
  or: [(aCodeGen isAssertSelector: parseTree statements first selector)
  and: [parseTree statements first selector ~~ #asserta:]]]]) ifFalse:
  [^false]].
  parseTree statements last isReturn ifFalse:
  [^false].
  parseTree statements last expression nodesDo:
  [ :n | n isReturn ifTrue: [^false]].
  ^#(int #'unsigned int' #long #'unsigned long' #'long long' #'unsigned long long'
  sqInt usqInt #'sqIntptr_t' #'usqIntptr_t' sqLong usqLong
+ #'int *' #'unsigned int *' #'sqInt *' #'usqInt *' #'sqLong *' #'usqLong *' #'char *'
+ #'CogMethod *' #'AbstractInstruction *') includes: returnType!
- #'int *' #'unsigned int *' #'sqInt *' #'usqInt *' #'sqLong *' #'usqLong *' #'CogMethod *' #'char *') includes: returnType!