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

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

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

Name: VMMaker.oscog-eem.2026
Author: eem
Time: 6 December 2016, 11:07:43.390182 am
UUID: e24cd05c-d1c9-490c-8994-b0cf94152a18
Ancestors: VMMaker.oscog-eem.2025

RegisterAllocatingCogit:
3+4=7 :-)

genSpecialSelectorComparison must create merge fixups at the targets (fall-through after the following branch and jump destination) for register assignments to be carried forwards.  Doing so eliminates the merge conflicts seen in SequenceableCollection>>#findBinaryIndex:do:ifNone: and so means that, for now, the code in resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: is not used.

Make sure that ensureNonMergeFixupAt: reciords bytecodePC for debugging.

Hack implement swapCurrentRegistersInMask:accordingToRegisterOrderIn: for the trivial two-registers-in-conflict case.

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

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."
  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.
  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 ensureFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+ self Jump: (self ensureFixupAt: postBranchPC - initialPC).
- 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>>resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: (in category 'bytecode generator support') -----
  resolveRegisterOrderConflictsBetweenCurrentSimStackAnd: mergeSimStack
  <var: #mergeSimStack type: #'SimStackEntry *'>
  "One simple algorithm is to spill everything if there are any conflicts and then pop back.
  But this is terrible :-(  Can we do better? Yes... Consider the following two simStacks
  target: 0: | rA | __ | rB | rC | rD | <- sp
  current: 0: | __ | __ | rD | rA | rC | <- sp
  If we were to assign in a naive order, 0 through sp rA would be overwritten before its value in current[3] is written to rC,
  and rC would be overwritten before its value in current[4] is written to rD.  But if we swap the registers in current so that
  they respect the reverse ordering in target we can assign directly:
  swap current[3] & current[4]
  0: | __ | __ | rD | rC | rA | <- sp
  now do the assignment in the order target[0] := current[0],  target[1] := current[1], ...  target[4] := current[4],
  i.e. rA := current[0]; rB := rD; (rC := rC); (rD := rD).
 
  So find any conflicts, and if there are any, swap registers in the simStack to resolve them.
+ The trivial case of a single conflict is resolved by assigning that conflict to TempReg."
- The trivial case of a single conflict is resolved by assigning that conflict to TempReg.
- "
  | currentRegsMask mergeRegsMask potentialConflictRegMask conflictingRegsMask
    currentRegMask mergeRegMask currentEntry targetEntry |
  <var: #currentEntry type: #'SimStackEntry *'>
  <var: #targetEntry type: #'SimStackEntry *'>
  currentRegsMask := mergeRegsMask := potentialConflictRegMask := 0.
  0 to: simStackPtr do:
  [:i|
  currentRegMask := (currentEntry := self simStack: simStack at: i) registerMaskOrNone.
  mergeRegMask := (targetEntry := self simStack: mergeSimStack at: i) registerMaskOrNone.
  (currentRegMask ~= mergeRegMask
   and: [currentRegMask ~= 0 or: [mergeRegMask ~= 0]]) ifTrue:
  [potentialConflictRegMask := potentialConflictRegMask bitOr: (currentRegMask bitOr: mergeRegMask)].
  currentRegsMask := currentRegsMask bitOr: currentRegMask.
  mergeRegsMask := mergeRegsMask bitOr: mergeRegMask].
  conflictingRegsMask := potentialConflictRegMask bitAnd: (currentRegsMask bitAnd: mergeRegsMask).
  conflictingRegsMask ~= 0 ifTrue:
  [(self isAPowerOfTwo: conflictingRegsMask) "Multiple conflicts mean we have to sort"
+ ifFalse: [self swapCurrentRegistersInMask: conflictingRegsMask accordingToRegisterOrderIn: mergeSimStack]
- ifFalse: [self swapCurrentRegistersInMask: currentRegsMask accordingToRegisterOrderIn: mergeSimStack]
  ifTrue: [self assignToTempRegConflictingRegisterIn: conflictingRegsMask]].!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>swapCurrentRegistersInMask:accordingToRegisterOrderIn: (in category 'bytecode generator support') -----
+ swapCurrentRegistersInMask: conflictingRegsMask accordingToRegisterOrderIn: mergeSimStack
+ <var: #mergeSimStack type: #'SimStackEntry *'>
+ "Swap liveRegisters in simStack entries according to their order in mergeSimStack so as to avoid
+ overwriting live registers when merging simStack into mergeSimStack.  Consider the following two simStacks
+ target: 0: | rA | __ | rB | rC | rD | <- sp
+ current: 0: | __ | __ | rD | rA | rC | <- sp
+ If we were to assign in a naive order, 0 through sp rA would be overwritten before its value in current[3] is written to rC,
+ and rC would be overwritten before its value in current[4] is written to rD.  But if we swap the registers in current so that
+ they respect the reverse ordering in target we can assign directly:
+ swap current[3] & current[4]
+ 0: | __ | __ | rD | rC | rA | <- sp
+ now do the assignment in the order target[0] := current[0],  target[1] := current[1], ...  target[4] := current[4],
+ i.e. rA := current[0]; rB := rD; (rC := rC); (rD := rD).
+
+ See https://hal.inria.fr/inria-00435844/file/article-hal.pdf
+ Florent Bouchez, Quentin Colombet, Alain Darte, Christophe Guillon, Fabrice Rastello.
+ Parallel Copy Motion. SCOPES, ACM, 2010, pp.0. <inria-00435844>
+
+ So find any conflicts, and if there are any, swap registers in the simStack to resolve them."
+
+ "self printSimStack; printSimStack: mergeSimStack"
+
+ "Some processors have a SwapRR but not all.  Write one-size-fits-all code that moves things through TempReg."
+ | order n visitedMask ssEntry regA regB |
+ <var: 'order' declareC: 'sqInt order[8*BytesPerWord]'>
+ <var: 'ssEntry' type: #'SimStackEntry *'>
+ self cCode: [self me: order ms: 0 et: (self sizeof: order)]
+ inSmalltalk: [order := CArrayAccessor on: (Array new: 8*BytesPerWord withAll: 0)].
+ n := 0.
+ visitedMask := conflictingRegsMask.
+ 0 to: methodOrBlockNumTemps - 1 do:
+ [:i|
+ ssEntry := self simStack: mergeSimStack at: i.
+ (ssEntry registerMaskOrNone anyMask: visitedMask) ifTrue:
+ [order at: ssEntry registerOrNone put: (n := n + 1).
+ visitedMask := visitedMask - ssEntry registerMaskOrNone]].
+ self assert: n > 1.
+ n = 2 ifTrue: "simple case; here to show me what I have to do in addition to the sort"
+ [regA := conflictingRegsMask highBit - 1.
+ regB := (conflictingRegsMask - (1 << regA)) highBit - 1.
+ self MoveR: regA R: TempReg.
+ self MoveR: regB R: regA.
+ self MoveR: TempReg R: regB.
+ 0 to: simStackPtr do:
+ [:i|
+ ssEntry := self simStackAt: i.
+ (ssEntry registerMaskOrNone anyMask: conflictingRegsMask) ifTrue:
+ [| reg |
+ reg := ssEntry registerOrNone = regA ifTrue: [regB] ifFalse: [regA].
+ ssEntry type = SSRegister ifTrue:
+ [ssEntry register: reg].
+ ssEntry liveRegister: reg]].
+ ^self].
+
+ self halt!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ensureNonMergeFixupAt: (in category 'compile abstract instructions') -----
  ensureNonMergeFixupAt: targetIndex
  "Make sure there's a flagged fixup at the targetIndex (pc relative to first pc) in fixups.
  Initially a fixup's target is just a flag.  Later on it is replaced with a proper instruction."
  <returnTypeC: #'BytecodeFixup *'>
  | fixup |
  <var: #fixup type: #'BytecodeFixup *'>
  fixup := self fixupAt: targetIndex.
  fixup notAFixup ifTrue:
  [fixup becomeNonMergeFixup].
  self cCode: '' inSmalltalk:
  [fixup isMergeFixupOrIsFixedUp ifTrue:
  [self assert:
  (fixup isBackwardBranchFixup
  or: [fixup simStackPtr = (self debugStackPointerFor: targetIndex + initialPC)])]].
+ fixup recordBcpc: bytecodePC.
  ^fixup!