VM Maker: VMMaker.oscog-eem.2025.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.2025.mcz

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

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

Name: VMMaker.oscog-eem.2025
Author: eem
Time: 5 December 2016, 11:37:37.687804 am
UUID: fabd1a90-44f2-4c24-a717-0ddf8f524bdb
Ancestors: VMMaker.oscog-EstebanLorenzano.2024

RegisterAllocatingCogit:

Clean up reconcilePoppingWith:

Fix bug with merging results into temp vars with live regs.  If merging a non-temp with a temp that has a live register we can assign to the register, but must unassign the register from the temp, otherwise the temp will acquire the merged value without an assignment.

Fix bug with allocateRegForStackEntryAt:; use the register of the entry if it has one.

Nuke captureUnspilledSpillsForSpecialSelectorSend:.  With the recent changes to merge logic this is no longer necessary.

Fix bugs with genSpecialSelectorArithmetic.  Assign a new register for the result unless rcvr is otherwise unused register or constant; do /not/ overwrite rcvrReg (which could be a temp).  If rcvr or arg are live ensure they're restored correctly after tag removal or overflow during arithmetic.

Improve printing of cogMethods with nil selectors.

Execution now gets much further; up to the compilation of findBinaryIndex:do:ifNone: in the context of restoring the display.  This method requires swapCurrentRegistersInMask:accordingToRegisterOrderIn: to be implemented.

Clément, please review especially genSpecialSelectorArithmetic carefully. Thanks!

=============== Diff against VMMaker.oscog-EstebanLorenzano.2024 ===============

Item was changed:
  ----- Method: CoInterpreter>>printCogMethod: (in category 'debug printing') -----
  printCogMethod: cogMethod
  <api>
  <var: #cogMethod type: #'CogMethod *'>
  | address primitive |
  self cCode: ''
  inSmalltalk:
  [self transcript ensureCr.
  cogMethod isInteger ifTrue:
  [^self printCogMethod: (self cCoerceSimple: cogMethod to: #'CogMethod *')]].
  address := cogMethod asInteger.
  self printHex: address;
  print: ' <-> ';
  printHex: address + cogMethod blockSize.
  cogMethod cmType = CMMethod ifTrue:
  [self print: ': method: ';
  printHex: cogMethod methodObject.
  primitive := self primitiveIndexOfMethod: cogMethod methodObject
  header: cogMethod methodHeader.
  primitive ~= 0 ifTrue:
  [self print: ' prim '; printNum: primitive]].
  cogMethod cmType = CMBlock ifTrue:
  [self print: ': block home: ';
  printHex: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod asUnsignedInteger].
  cogMethod cmType = CMClosedPIC ifTrue:
  [self print: ': Closed PIC N: ';
  printHex: cogMethod cPICNumCases].
  cogMethod cmType = CMOpenPIC ifTrue:
  [self print: ': Open PIC '].
  self print: ' selector: '; printHex: cogMethod selector.
  cogMethod selector = objectMemory nilObject
+ ifTrue: [| s |
+ (cogMethod cmType = CMMethod
+ and: [(s := self maybeSelectorOfMethod: cogMethod methodObject) notNil])
+ ifTrue: [self print: ' (nil: '; printStringOf: s; print: ')']
+ ifFalse: [self print: ' (nil)']]
- ifTrue: [self print: ' (nil)']
  ifFalse: [self space; printStringOf: cogMethod selector].
  self cr!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileForwardsWith: (in category 'compile abstract instructions') -----
  reconcileForwardsWith: targetEntry
  "Make the state of the receiver, a stack entry at the end of a basic block,
  the same as the corresponding simStackEntry at the target of a preceding
  jump to the beginning of the next basic block.  Make sure targetEntry
  reflects the state of the merged simStack; it will be installed as the current
+ entry by restoreSimStackAtMergePoint: in mergeWithFixupIfRequired:.
+
+ Answer if the liveRegister for the targetEntry (if any) should be deassigned;
+ this is because if merging a non-temp with a temp that has a live register we
+ can assign to the register, but must unassign the register from the temp,
+ otherwise the temp will acquire the merged value without an assignment."
- entry by restoreSimStackAtMergePoint: in mergeWithFixupIfRequired:."
  <var: #targetEntry type: #'targetEntry *'>
  | targetReg |
  (targetReg := targetEntry registerOrNone) = NoReg ifTrue:
  [self assert: (self isSameEntryAs: targetEntry).
+ ^false].
- ^self].
  liveRegister ~= NoReg ifTrue:
  [liveRegister ~= targetReg ifTrue:
  [cogit MoveR: liveRegister R: targetReg].
  (spilled and: [targetEntry spilled not]) ifTrue:
  [cogit AddCq: objectRepresentation wordSize R: SPReg].
+ ^false].
- ^self].
  spilled
  ifTrue:
  [targetEntry spilled ifFalse:
  [cogit PopR: targetReg. "KISS; generate the least number of instructions..."
+ ^false]]
- ^self]]
  ifFalse:
+ [targetEntry spilled ifTrue:
+ [cogit SubCq: objectRepresentation wordSize R: SPReg]].
- [self deny: targetEntry spilled].
  type caseOf: {
  [SSBaseOffset] -> [cogit MoveMw: offset r: register R: targetReg].
  [SSSpill] -> [cogit MoveMw: offset r: register R: targetReg].
  [SSConstant] -> [cogit genMoveConstant: constant R: targetReg].
  [SSRegister] -> [register ~= targetReg ifTrue:
  [cogit MoveR: register R: targetReg]] }.
  (targetEntry type = SSConstant
  and: [type ~= SSConstant or: [constant ~= targetEntry constant]]) ifTrue:
  [targetEntry
  register: targetReg;
+ type: SSRegister].
+ "If merging a non-temp with a temp that has a live register we can assign
+ to the register, but must unassign the register from the temp, otherwise
+ the temp will acquire the merged value without an assignment."
+ ^targetEntry type = SSBaseOffset
+  and: [targetEntry register = FPReg
+  and: [(self isSameEntryAs: targetEntry) not]]!
- type: SSRegister]!

Item was changed:
  ----- Method: CogRegisterAllocatingSimStackEntry>>reconcilePoppingWith: (in category 'compile abstract instructions') -----
  reconcilePoppingWith: targetEntry
  "Make the state of a targetEntry, a stack entry following a non-inlined special selector
  send, the same as the corresponding entry (the receiver) along the inlined path."
  <var: #targetEntry type: #'targetEntry *'>
  | targetReg |
  targetEntry spilled ifTrue:
  [self assert: (self isSameEntryAs: targetEntry).
  (targetReg := targetEntry registerOrNone) = NoReg ifTrue:
  [^self].
  type caseOf: {
  [SSBaseOffset] -> [cogit MoveMw: offset r: register R: targetReg].
  [SSSpill] -> [cogit MoveMw: offset r: register R: targetReg].
  [SSConstant] -> [cogit genMoveConstant: constant R: targetReg].
  [SSRegister] -> [targetReg ~= register ifTrue:
  [cogit MoveR: register R: targetReg]] }.
  ^self].
+ (targetEntry type ~= SSConstant
+ and: [(targetReg := targetEntry registerOrNone) ~= NoReg])
+ ifTrue: [cogit PopR: targetReg]
+ ifFalse: [cogit AddCq: objectRepresentation wordSize R: SPReg]!
- targetEntry type = SSConstant ifTrue:
- [self assert: (targetEntry registerOrNone) = NoReg.
- cogit AddCq: objectRepresentation wordSize R: SPReg.
- ^self].
- (targetReg := targetEntry registerOrNone) ~= NoReg ifTrue:
- [cogit PopR: targetReg.
- ^self].
- self halt!

Item was changed:
  ----- Method: Cogit>>recordProcessing (in category 'simulation only') -----
  recordProcessing
  | inst |
  self recordRegisters.
  inst := self recordLastInstruction.
  "Set RRRName ito the selector that accesses ReceiverResultReg (RRR) to alter instruction printing to add the value of RRR as a suffix
  (RRRName := #rdx)
  (RRRName := #edx)
+ (RRRName := nil)"
- (RRRName := #nil)"
  printRegisters ifTrue:
  [RRRName ifNil: [processor printRegistersOn: coInterpreter transcript].
  printInstructions ifFalse:
  [coInterpreter transcript cr]].
  printInstructions ifTrue:
  [printRegisters ifTrue:
  [coInterpreter transcript cr].
  coInterpreter transcript nextPutAll: inst.
  RRRName ifNotNil:
  [coInterpreter transcript space; nextPutAll: RRRName; space.
  (processor perform: RRRName) printOn: coInterpreter transcript base: 16 length: 8 padded: false].
  coInterpreter transcript cr; flush]!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>allocateRegForStackEntryAt: (in category 'simulation stack') -----
  allocateRegForStackEntryAt: index
  "If the stack entry is already in a register, answers it,
  else allocate a new register for it"
  <inline: true>
+ | reg |
+ (reg := (self ssValue: index) registerOrNone) ~= NoReg ifTrue:
+ [^reg].
+ ^self allocateRegForStackEntryAt: index notConflictingWith: (self liveRegisters bitOr: (self registerMaskFor: FPReg and: SPReg and: TempReg))!
- ^self allocateRegForStackEntryAt: index notConflictingWith: (self registerMaskFor: FPReg and: SPReg and: TempReg)!

Item was removed:
- ----- Method: RegisterAllocatingCogit>>captureUnspilledSpillsForSpecialSelectorSend: (in category 'bytecode generator support') -----
- captureUnspilledSpillsForSpecialSelectorSend: liveRegisterMask
- "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.  But any values that would need to be spilled
- along the non-inlined path must be captured before the split so that both paths can join.  If we don't
- capture the values on the non-inlined path we could access stale values.  So for all stack entries that
- would be spilled along the non-inlined path, assign them to registers, or spill if none are available."
- | i liveRegs reg |
- liveRegs := liveRegisterMask.
- self assert: (simSelf liveRegister = ReceiverResultReg) = optStatus isReceiverResultRegLive.
- optStatus isReceiverResultRegLive ifTrue:
- [liveRegs := liveRegs + (self registerMaskFor: ReceiverResultReg)].
- reg := TempReg. "Anything but NoReg"
- i := simStackPtr + 1. "We must spill a contiguous range at the hot top of stack, so we assign coldest first :-("
- [reg ~= NoReg and: [i > simSpillBase and: [i > 0]]] whileTrue:
- [i := i - 1.
- ((self simStackAt: i) spilled not
-  and: [(self simStackAt: i) type = SSBaseOffset]) ifTrue:
- [reg := self allocateRegNotConflictingWith: liveRegs.
- reg ~= NoReg ifTrue:
- [(self simStackAt: i) storeToReg: reg.
- liveRegs := liveRegs bitOr: (self registerMaskFor: reg)]]].
- reg = NoReg ifTrue:
- [self ssFlushTo: i]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>deassignRegisterForTempVar:in: (in category 'bytecode generator support') -----
+ deassignRegisterForTempVar: targetEntry in: mergeSimStack
+ "If merging a non-temp with a temp that has a live register we can assign
+ to the register, but must unassign the register from the temp, otherwise
+ the temp will acquire the merged value without an assignment.  The targetEntry
+ must also be transmogrified into an SSRegister entry."
+ <var: #targetEntry type: #'SimStackEntry *'>
+ <var: #mergeSimStack type: #'SimStackEntry *'>
+ <inline: true>
+ | reg |
+ reg := targetEntry liveRegister.
+ self assert: (targetEntry type = SSBaseOffset and: [targetEntry register = FPReg]).
+ simStackPtr to: 0 by: -1 do:
+ [:j| | duplicateEntry |
+ duplicateEntry := self simStack: mergeSimStack at: j.
+ (targetEntry isSameEntryAs: duplicateEntry) ifTrue:
+ [duplicateEntry liveRegister: NoReg]].
+ targetEntry
+ type: SSRegister;
+ register: reg!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
+ | primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt destReg
+ jumpNotSmallInts jumpContinue jumpOverflow index rcvrReg argReg regMask |
+ <var: #jumpOverflow type: #'AbstractInstruction *'>
- | primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
- jumpNotSmallInts jumpContinue index rcvrReg argReg regMask |
  <var: #jumpContinue type: #'AbstractInstruction *'>
  <var: #primDescriptor type: #'BytecodeDescriptor *'>
  <var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  primDescriptor := self generatorAt: byte0.
  argIsInt := (argIsConst := self ssTop type = SSConstant)
  and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
 
  (argIsInt and: [rcvrIsInt]) ifTrue:
+ [| result |
+ rcvrInt := objectMemory integerValueOf: rcvrInt.
- [rcvrInt := objectMemory integerValueOf: rcvrInt.
  argInt := objectMemory integerValueOf: argInt.
  primDescriptor opcode caseOf: {
  [AddRR] -> [result := rcvrInt + argInt].
  [SubRR] -> [result := rcvrInt - argInt].
  [AndRR] -> [result := rcvrInt bitAnd: argInt].
+ [OrRR] -> [result := rcvrInt bitOr: argInt] }.
- [OrRR] -> [result := rcvrInt bitOr: argInt] }.
  (objectMemory isIntegerValue: result) ifTrue:
  ["Must annotate the bytecode for correct pc mapping."
  ^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  ^self genSpecialSelectorSend].
 
  "If there's any constant involved other than a SmallInteger don't attempt to inline."
  ((rcvrIsConst and: [rcvrIsInt not])
  or: [argIsConst and: [argIsInt not]]) ifTrue:
  [^self genSpecialSelectorSend].
 
  "If we know nothing about the types then better not to inline as the inline cache and
  primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  (argIsInt or: [rcvrIsInt]) ifFalse:
  [^self genSpecialSelectorSend].
 
  "Since one or other of the arguments is an integer we can very likely profit from inlining.
+ But if the other type is not SmallInteger or if the operation overflows then we will need
+ to do a send.  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.
+ See reconcileRegisterStateForJoinAfterSpecialSelectorSend below."
- But if the other type is not SmallInteger or if the operation overflows then we will need to do a send.
- 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.  But any values that would need to be spilled
- along the non-inlined path must be captured before the split so that both paths can join.  If we don't
- capture the values on the non-iblined path we could access stale values.  So for all stack entries that
- would be spilled along the non-inlined path, assign them to registers, or spill if none are available."
  argIsInt
  ifTrue:
  [rcvrReg := self allocateRegForStackEntryAt: 1.
  (self ssValue: 1) popToReg: rcvrReg.
  self MoveR: rcvrReg R: TempReg.
  regMask := self registerMaskFor: rcvrReg]
  ifFalse:
  [self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext].
  self ssTop popToReg: argReg.
  (self ssValue: 1) popToReg: rcvrReg.
  self MoveR: argReg R: TempReg.
  regMask := self registerMaskFor: rcvrReg and: argReg].
+
+ "rcvrReg can be reused for the result iff the receiver is a constant or is an SSRegister that is not used elsewhere."
+ destReg := (rcvrIsInt
+ or: [(self ssValue: 1) type = SSRegister
+ and: [(self anyReferencesToRegister: rcvrReg inAllButTopNItems: 2) not]])
+ ifTrue: [rcvrReg]
+ ifFalse: [self allocateRegNotConflictingWith: regMask].
  self ssPop: 2.
- self captureUnspilledSpillsForSpecialSelectorSend: regMask.
  jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg]
  ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch: TempReg scratch: ClassReg].
+ rcvrReg ~= destReg ifTrue:
+ [self MoveR: rcvrReg R: destReg].
  primDescriptor opcode caseOf: {
  [AddRR] -> [argIsInt
  ifTrue:
+ [self AddCq: argInt - ConstZero R: destReg.
- [self AddCq: argInt - ConstZero R: rcvrReg.
  jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before doing send"
+ rcvrReg = destReg ifTrue:
+ [self SubCq: argInt - ConstZero R: rcvrReg]]
- "overflow; must undo the damage before continuing"
- self SubCq: argInt - ConstZero R: rcvrReg]
  ifFalse:
+ [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: destReg.
+ self AddR: argReg R: destReg.
+ jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before doing send"
+ destReg = rcvrReg ifTrue:
+ [rcvrIsInt
+ ifTrue: [self MoveCq: rcvrInt R: rcvrReg]
+ ifFalse:
+ [self SubR: argReg R: rcvrReg.
+ objectRepresentation genSetSmallIntegerTagsIn: rcvrReg]]]].
- [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: rcvrReg.
- self AddR: argReg R: rcvrReg.
- jumpContinue := self JumpNoOverflow: 0.
- "overflow; must undo the damage before continuing"
- rcvrIsInt
- ifTrue: [self MoveCq: rcvrInt R: rcvrReg]
- ifFalse:
- [self SubR: argReg R: rcvrReg.
- objectRepresentation genSetSmallIntegerTagsIn: rcvrReg]]].
  [SubRR] -> [argIsInt
  ifTrue:
+ [self SubCq: argInt - ConstZero R: destReg.
- [self SubCq: argInt - ConstZero R: rcvrReg.
  jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before doing send"
+ rcvrReg = destReg ifTrue:
+ [self AddCq: argInt - ConstZero R: rcvrReg]]
- "overflow; must undo the damage before continuing"
- self AddCq: argInt - ConstZero R: rcvrReg]
  ifFalse:
+ [(self anyReferencesToRegister: argReg inAllButTopNItems: 0)
+ ifTrue: "argReg is live; cannot strip tags and continue on no overflow without restoring tags"
+ [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
+ self SubR: argReg R: destReg.
+ jumpOverflow := self JumpOverflow: 0.
+ "no overflow; must undo the damage before continuing"
+ objectRepresentation genSetSmallIntegerTagsIn: argReg.
+ jumpContinue := self Jump: 0.
+ jumpOverflow jmpTarget: self Label.
+ "overflow; must undo the damage before doing send"
+ (rcvrIsInt or: [destReg ~= rcvrReg]) ifFalse:
+ [self AddR: argReg R: destReg].
+ objectRepresentation genSetSmallIntegerTagsIn: argReg]
+ ifFalse:
+ [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
+ self SubR: argReg R: destReg.
+ jumpContinue := self JumpNoOverflow: 0.
+ "overflow; must undo the damage before doing send"
+ (rcvrIsInt or: [destReg ~= rcvrReg]) ifFalse:
+ [self AddR: argReg R: rcvrReg].
+ objectRepresentation genSetSmallIntegerTagsIn: argReg]]].
- [objectRepresentation genRemoveSmallIntegerTagsInScratchReg: argReg.
- self SubR: argReg R: rcvrReg.
- jumpContinue := self JumpNoOverflow: 0.
- "overflow; must undo the damage before continuing"
- self AddR: argReg R: rcvrReg.
- objectRepresentation genSetSmallIntegerTagsIn: argReg]].
  [AndRR] -> [argIsInt
+ ifTrue: [self AndCq: argInt R: destReg]
+ ifFalse: [self AndR: argReg R: destReg].
- ifTrue: [self AndCq: argInt R: rcvrReg]
- ifFalse: [self AndR: argReg R: rcvrReg].
  jumpContinue := self Jump: 0].
  [OrRR] -> [argIsInt
+ ifTrue: [self OrCq: argInt R: destReg]
+ ifFalse: [self OrR: argReg R: destReg].
- ifTrue: [self OrCq: argInt R: rcvrReg]
- ifFalse: [self OrR: argReg R: rcvrReg].
  jumpContinue := self Jump: 0] }.
  jumpNotSmallInts jmpTarget: self Label.
+ self ssPushRegister: destReg.
- self ssPushRegister: rcvrReg.
  self copySimStackToScratch: (simSpillBase min: simStackPtr - 1).
  self ssPop: 1.
  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.
  self reconcileRegisterStateForJoinAfterSpecialSelectorSend.
  jumpContinue jmpTarget: self Label.
  ^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  | nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
   rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB index rcvrReg argReg regMask |
  <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. 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."
- "In-line, but if the types are not SmallInteger then we will need to do a send.
- 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.  But any values that would need to be spilled
- along the non-inlined path must be captured before the split so that both paths can join.  If we don't
- capture the values on the non-iblined path we could access stale values.  So for all stack entries that
- would be spilled along the non-inlined path, assign them to registers, or spill if none are available."
  argIsInt
  ifTrue:
  [rcvrReg := self allocateRegForStackEntryAt: 1.
  (self ssValue: 1) popToReg: rcvrReg.
  self MoveR: rcvrReg R: TempReg.
  regMask := self registerMaskFor: rcvrReg]
  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.
  self MoveR: argReg R: TempReg.
  regMask := self registerMaskFor: rcvrReg and: argReg].
  self ssPop: 2.
- self captureUnspilledSpillsForSpecialSelectorSend: regMask.
  jumpNotSmallInts := (argIsInt or: [rcvrIsInt])
  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].
  "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 - initialPC) asUnsignedInteger.
  self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  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.
  ^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: fixup
  <var: #fixup type: #'BytecodeFixup *'>
  | mergeSimStack currentEntry targetEntry |
  <var: #mergeSimStack type: #'SimStackEntry *'>
  "At a merge point the cogit expects the stack to be in the same state as mergeSimStack.
  mergeSimStack is the state as of some jump forward to this point.  So make simStack agree
  with mergeSimStack (it is, um, problematic to plant code at the jump).
  Values may have to be assigned to registers.  Registers may have to be swapped.
  The state of optStatus must agree."
- <var: #currentEntry type: #'SimStackEntry *'>
  <var: #targetEntry type: #'SimStackEntry *'>
+ <var: #currentEntry type: #'SimStackEntry *'>
+ <var: #duplicateEntry type: #'SimStackEntry *'>
  (mergeSimStack := fixup mergeSimStack) ifNil: [^self].
  "Assignments amongst the registers must be made in order to avoid overwriting.
  If necessary exchange registers amongst simStack's entries to resolve any conflicts."
  self resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: mergeSimStack.
  self assert: (self conflcitsResolvedBetweenSimStackAnd: mergeSimStack).
  simStackPtr to: 0 by: -1 do:
  [:i|
  currentEntry := self simStack: simStack at: i.
  targetEntry := self simStack: mergeSimStack at: i.
+ (currentEntry reconcileForwardsWith: targetEntry) ifTrue:
+ [self assert: i >= methodOrBlockNumArgs.
+ self deassignRegisterForTempVar: targetEntry in: mergeSimStack].
- currentEntry reconcileForwardsWith: targetEntry.
  "Note, we could update the simStack and spillBase here but that is done in restoreSimStackAtMergePoint:
  spilled ifFalse:
  [simSpillBase := i - 1].
  simStack
  at: i
  put: (self
  cCode: [mergeSimStack at: i]
  inSmalltalk: [(mergeSimStack at: i) copy])"].
 
  "a.k.a. fixup isReceiverResultRegSelf: (fixup isReceiverResultRegSelf and: [optStatus isReceiverResultRegLive])"
  optStatus isReceiverResultRegLive ifFalse:
  [fixup isReceiverResultRegSelf: false]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>anyReferencesToRegister:inAllButTopNItems: (in category 'simulation stack') -----
+ anyReferencesToRegister: reg inAllButTopNItems: n
+ | regMask |
+ regMask := self registerMaskFor: reg.
+ simStackPtr - n to: 0 by: -1 do:
+ [:i|
+ ((self simStackAt: i) registerMask anyMask: regMask) ifTrue:
+ [^true]].
+ ^false!