Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2332.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2332 Author: eem Time: 8 February 2018, 6:01:54.68433 pm UUID: f17f3408-e209-439f-b78c-6af70bf7cdd0 Ancestors: VMMaker.oscog-eem.2331 RegisterAllocatingCogit: Moving volatile stack contents to registers should happen once before each jump, not potentially multiple times in ensureFixupAt:. Refactor moveVolatileSimStackEntriesToRegisters into moveVolatileSimStackEntriesToRegistersPreserving:, allowing easier use by the sopecial selecrtor generators, which have allocated registers before they're ready to move volatile contents to registers. When reconciling, if a constant is in a register, use the register. =============== Diff against VMMaker.oscog-eem.2331 =============== Item was changed: ----- Method: CogRegisterAllocatingSimStackEntry>>reconcileWith:spillOffset:onSpillOrUnspill: (in category 'compile abstract instructions') ----- reconcileWith: targetEntry spillOffset: spillOffset onSpillOrUnspill: spillOrUnspillBlock "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. spillOffset is zero for non-spill locations (self & temps), and the offset of the spill for volatile stack entries. spillOrUnspillBlock is a block evaluated with the target's registerOrNone if the receiver and target have different spilledness. Answer if the reconciliation merged a register; merged registers must be deassigned." <var: #targetEntry type: #'SimStackEntry *'> <inline: true> | targetReg mergedRegister | spilled = targetEntry spilled ifTrue: [self assert: ((self isSameEntryAs: targetEntry) or: [(targetEntry spilled not and: [targetEntry registerOrNone ~= NoReg]) or: [spilled and: [type = SSConstant and: [offset = targetEntry offset]]]]). (targetReg := targetEntry registerOrNone) = NoReg ifTrue: [liveRegister := NoReg. ^false]. mergedRegister := false. type caseOf: { [SSBaseOffset] -> [liveRegister ~= targetReg ifTrue: [cogit MoveMw: offset r: register R: targetReg. mergedRegister := true]. targetEntry type caseOf: { [SSBaseOffset] -> [liveRegister := targetReg. (self isSameEntryAs: targetEntry) ifFalse: [type := SSSpill. offset := spillOffset]]. [SSSpill] -> [liveRegister := targetReg. type := SSSpill. offset := spillOffset]. [SSConstant] -> [liveRegister := targetReg. type := SSSpill. offset := spillOffset]. [SSRegister] -> [register := targetReg. type := SSRegister] }]. [SSSpill] -> [cogit MoveMw: offset r: register R: targetReg. liveRegister := targetReg. mergedRegister := true]. + [SSConstant] -> [liveRegister = NoReg + ifTrue: [cogit genMoveConstant: constant R: targetReg] + ifFalse: [cogit MoveR: liveRegister R: targetReg]. - [SSConstant] -> [cogit genMoveConstant: constant R: targetReg. type := SSRegister. register := targetReg. liveRegister := NoReg. mergedRegister := true]. [SSRegister] -> [targetReg ~= register ifTrue: [cogit MoveR: register R: targetReg. register := targetReg. mergedRegister := true]] }. ^mergedRegister]. targetReg := targetEntry registerOrNone. spillOrUnspillBlock value: targetReg. (type = SSConstant and: [targetEntry type ~= SSConstant or: [targetEntry constant ~= constant]]) ifTrue: [type := SSSpill. offset := spillOffset. register := FPReg]. liveRegister ~= targetReg ifTrue: [liveRegister := NoReg]. ^false! Item was changed: ----- Method: RegisterAllocatingCogit>>assertCorrectSimStackPtr (in category 'compile abstract instructions') ----- assertCorrectSimStackPtr <inline: true> "generates nothing anyway" "self simStackPrintString" self cCode: '' inSmalltalk: [deadCode ifFalse: [self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1]) + = (self debugStackPointerFor: bytecodePC). + self assert: (simSpillBase >= methodOrBlockNumTemps + or: [self maybeCompilingFirstPassOfBlockWithInitialPushNil and: [simSpillBase > methodOrBlockNumArgs]]). + (needsFrame and: [simSpillBase > 0]) ifTrue: + [self assert: (self simStackAt: simSpillBase - 1) spilled == true. + self assert: (simSpillBase > simStackPtr or: [(self simStackAt: simSpillBase) spilled == false])]]. - = (self debugStackPointerFor: bytecodePC)]. self deny: self duplicateRegisterAssignmentsInTemporaries]! 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 generate stack merging code if required." | fixup | <var: #fixup type: #'BytecodeFixup *'> self assert: targetPC > bytecodePC. self cCode: '' inSmalltalk: [self assert: simStackPtr + (needsFrame ifTrue: [0] ifFalse: [1]) = (self debugStackPointerFor: targetPC)]. fixup := self fixupAt: targetPC. "If a non-merge fixup has already been defined then where-ever that was done didn't realise there needed to be a merge and forgot to save the stack state for that merge." self deny: fixup isNonMergeFixup. fixup needsFixup ifTrue: [fixup mergeSimStack ifNil: [self setMergeSimStackOf: fixup] ifNotNil: [self copySimStackToScratch: simSpillBase. self mergeCurrentSimStackWith: fixup. self restoreSimStackFromScratch]] ifFalse: [self assert: (fixup mergeSimStack isNil or: [compilationPass = 2]). fixup mergeSimStack ifNil: [self setMergeSimStackOf: fixup] ifNotNil: + [self assert: (self simStack: simStack isIdenticalTo: fixup mergeSimStack)]]. - [self moveVolatileSimStackEntriesToRegisters. - self assert: (self simStack: simStack isIdenticalTo: fixup mergeSimStack)]]. ^super ensureFixupAt: targetPC! Item was changed: ----- Method: RegisterAllocatingCogit>>ensureNonMergeFixupAt: (in category 'compile abstract instructions') ----- ensureNonMergeFixupAt: targetPC + "RegisterAllocatingCogit insists on merging." + self shouldNotImplement! - "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" - true - ifTrue: [self shouldNotImplement] - ifFalse: - [| fixup | - fixup := super ensureNonMergeFixupAt: targetPC. - fixup mergeSimStack - ifNil: [self setMergeSimStackOf: fixup] - ifNotNil: - [self assert: simStackPtr = fixup simStackPtr. - self deny: (self mergeRequiredToTarget: fixup mergeSimStack)]. - ^fixup]! 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 | <var: #branchDescriptor type: #'BytecodeDescriptor *'> <var: #toContinueLabel type: #'AbstractInstruction *'> <var: #toTargetLabel type: #'AbstractInstruction *'> <var: #comparison type: #'AbstractInstruction *'> <var: #retry type: #'AbstractInstruction *'> self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := 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]. self assert: (unforwardArg or: [unforwardRcvr]). + self ssPop: 2. "If we had moveAllButTop: 2 volatileSimStackEntriesToRegistersPreserving: we could avoid the extra ssPop:s" + self moveVolatileSimStackEntriesToRegistersPreserving: + (self allocatedRegisters bitOr: (argReg = NoReg + ifTrue: [self registerMaskFor: rcvrReg] + ifFalse: [self registerMaskFor: rcvrReg and: argReg])). - retry := self Label. + self ssPop: -2. 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" "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 ensureFixupAt: postBranchPC]. comparison := self JumpZero: (needMergeToTarget ifTrue: [0] "comparison will be fixed up to to-target merge code" ifFalse: [self ensureFixupAt: 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 ensureFixupAt: targetPC]. comparison := self JumpZero: (needMergeToContinue ifTrue: [0] "comparison will be fixed up to to-continue merge code" ifFalse: [self ensureFixupAt: postBranchPC])]. "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)]]. deadCode ifFalse: "duplicate the merge fixup's top of stack so as to avoid a false confict." [self ssPushDesc: ((self fixupAt: nextPC) mergeSimStack at: simStackPtr + 1)]. ^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. + self moveVolatileSimStackEntriesToRegisters. + (self stackEntryIsBoolean: desc) 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: [self receiverIsInReceiverResultReg])]]) 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 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>>genJumpTo: (in category 'bytecode generator support') ----- genJumpTo: targetBytecodePC "Overriden to avoid the flush because in this cogit stack state is merged at merge point." | eventualTarget generator fixup | + self moveVolatileSimStackEntriesToRegisters. eventualTarget := self eventualTargetOf: targetBytecodePC. (eventualTarget > bytecodePC and: [self stackTopIsBoolean and: [(generator := self generatorForPC: eventualTarget) isConditionalBranch]]) ifTrue: [eventualTarget := eventualTarget + generator numBytes + (generator isBranchTrue == (self ssTop constant = objectMemory trueObject) ifTrue: [self spanFor: generator at: eventualTarget exts: 0 in: methodObj] ifFalse: [0]). self ssPop: 1. fixup := self ensureFixupAt: eventualTarget. self ssPop: -1] ifFalse: [fixup := self ensureFixupAt: eventualTarget]. deadCode := true. "can't fall through" self Jump: fixup. ^0! Item was changed: ----- Method: RegisterAllocatingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') ----- genSpecialSelectorComparison | nextPC postBranchPC targetPC primDescriptor branchDescriptor rcvrIsInt rcvrIsConst argIsIntConst argInt jumpNotSmallInts inlineCAB index rcvrReg argReg branchToTarget needMergeToContinue needMergeToTarget | <var: #primDescriptor type: #'BytecodeDescriptor *'> <var: #branchDescriptor type: #'BytecodeDescriptor *'> <var: #jumpNotSmallInts type: #'AbstractInstruction *'> primDescriptor := self generatorAt: byte0. argIsIntConst := self ssTop type = SSConstant and: [objectMemory isIntegerObject: (argInt := self ssTop constant)]. rcvrIsInt := ((rcvrIsConst := (self ssValue: 1) type = SSConstant) and: [objectMemory isIntegerObject: (self ssValue: 1) constant]) or: [self mclassIsSmallInteger and: [(self ssValue: 1) isSameEntryAs: self simSelf]]. (argIsIntConst and: [rcvrIsInt and: [rcvrIsConst]]) ifTrue: [^self genStaticallyResolvedSpecialSelectorComparison]. self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetPC := 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 := argIsIntConst 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." argIsIntConst ifTrue: [rcvrReg := self allocateRegForStackEntryAt: 1. (self ssValue: 1) popToReg: rcvrReg. argReg := NoReg] ifFalse: [self allocateRegForStackTopTwoEntriesInto: [:rTop :rNext| argReg := rTop. rcvrReg := rNext]. self ssTop popToReg: argReg. (self ssValue: 1) popToReg: rcvrReg]. self ssPop: 2. + self moveVolatileSimStackEntriesToRegistersPreserving: + (self allocatedRegisters bitOr: (argReg = NoReg + ifTrue: [self registerMaskFor: rcvrReg] + ifFalse: [self registerMaskFor: rcvrReg and: argReg])). + jumpNotSmallInts := (rcvrIsInt and: [argIsIntConst]) ifFalse: [argIsIntConst ifTrue: [objectRepresentation genJumpNotSmallInteger: rcvrReg] ifFalse: [rcvrIsInt ifTrue: [objectRepresentation genJumpNotSmallInteger: argReg] ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg and: argReg scratch: TempReg]]]. argIsIntConst 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 ensureFixupAt: 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 ensureFixupAt: 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 ensureFixupAt: targetPC) asUnsignedInteger. self Jump: (self ensureFixupAt: postBranchPC)]. jumpNotSmallInts ifNil: [self annotateInstructionForBytecode. deadCode := true. ^0]. jumpNotSmallInts jmpTarget: self Label. self ssFlushTo: simStackPtr. rcvrReg = Arg0Reg ifTrue: [argReg = ReceiverResultReg ifTrue: [self SwapR: Arg0Reg R: Arg0Reg Scratch: TempReg. argReg := Arg0Reg] ifFalse: [self MoveR: rcvrReg R: ReceiverResultReg]. rcvrReg := ReceiverResultReg]. argIsIntConst 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>>genVanillaInlinedIdenticalOrNotIf: (in category 'bytecode generators') ----- genVanillaInlinedIdenticalOrNotIf: orNot | nextPC postBranchPC targetBytecodePC branchDescriptor rcvrReg argReg argIsConstant rcvrIsConstant | <var: #branchDescriptor type: #'BytecodeDescriptor *'> self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ]. argIsConstant := self ssTop type = SSConstant. "They can't be both constants to use correct machine opcodes. However annotable constants can't be resolved statically, hence we need to careful." rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant]. self allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not rcvrNeedsReg: rcvrIsConstant not into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ]. "If not followed by a branch, resolve to true or false." (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse: [^ self genIdenticalNoBranchArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg orNotIf: orNot]. - self genCmpArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. + self moveVolatileSimStackEntriesToRegistersPreserving: + (self allocatedRegisters bitOr: (argReg = NoReg + ifTrue: [self registerMaskFor: rcvrReg] + ifFalse: [self registerMaskFor: rcvrReg and: argReg])). + self genCmpArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg. + "For now just deny we're in the situation we have yet to implement ;-)" self deny: (self mergeRequiredForJumpTo: targetBytecodePC). self deny: (self mergeRequiredForJumpTo: 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" self genConditionalBranch: (orNot == branchDescriptor isBranchTrue ifTrue: [JumpNonZero] ifFalse: [JumpZero]) operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. "If the branch is dead, then we can just fall through postBranchPC (only a nop in-between), else we need to jump over the code of the branch" deadCode ifFalse: [self Jump: (self ensureNonMergeFixupAt: postBranchPC). "duplicate the merge fixup's top of stack so as to avoid a false confict." self ssPushDesc: ((self fixupAt: nextPC) mergeSimStack at: simStackPtr + 1)]. ^0! Item was changed: ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') ----- mergeCurrentSimStackWith: fixup "At a merge point the cogit expects the stack to be in the same state as fixup's mergeSimStack. mergeSimStack is the state as of some jump forward or backward 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. Generate code to merge the current simStack with that of the target fixup, the goal being to keep as many registers live as possible." "self printSimStack; printSimStack: fixup mergeSimStack" "self simStackPrintString-> fixup simStackPrintString" "abstractOpcodes object copyFrom: startIndex to: opcodeIndex" <var: #fixup type: #'BytecodeFixup *'> | currentRegisters targetRegisters mergeSimStack current target spillOffset | (mergeSimStack := fixup mergeSimStack) ifNil: [^self]. self assert: simStackPtr = fixup simStackPtr. currentRegisters := self liveRegistersFrom: 0 to: simStackPtr in: simStack. targetRegisters := self liveRegistersFrom: 0 to: simStackPtr in: mergeSimStack. self resolveConflicts: (currentRegisters bitAnd: targetRegisters) with: fixup mergeSimStack to: fixup simStackPtr. self assert: (self conflictsResolvedBetweenSimStackAnd: mergeSimStack). (self pushForMergeWith: mergeSimStack) ifTrue: [0 to: simStackPtr do: [:i| spillOffset := i > methodOrBlockNumTemps ifTrue: [self frameOffsetOfTemporary: i - 1] ifFalse: [0]. ((current := self simStack: simStack at: i) reconcileWith: (target := self simStack: mergeSimStack at: i) spillOffset: spillOffset onSpillOrUnspill: [:targetReg| self deny: current spilled. self assert: spillOffset ~= 0. current ensureSpilledAt: spillOffset from: FPReg]) ifTrue: [i > methodOrBlockNumTemps ifTrue: [self deassignRegister: current registerOrNone in: mergeSimStack. self deassignRegister: current registerOrNone in: simStack. self deny: (self register: current registerOrNone isInMask: self liveRegistersInSelfAndTemps)]]]] ifFalse: [simStackPtr to: 0 by: -1 do: [:i| spillOffset := i > methodOrBlockNumTemps ifTrue: [self frameOffsetOfTemporary: i - 1] ifFalse: [0]. ((current := self simStack: simStack at: i) reconcileWith: (target := self simStack: mergeSimStack at: i) spillOffset: spillOffset onSpillOrUnspill: [:targetReg| self assert: current spilled. self assert: spillOffset ~= 0. targetReg ~= NoReg ifTrue: [self PopR: targetReg] + ifFalse: [self AddCq: objectRepresentation wordSize R: SPReg]. + current type ~= SSSpill ifTrue: + [current spilled: false. + simSpillBase > i ifTrue: + [simSpillBase := i]]]) ifTrue: - ifFalse: [self AddCq: objectRepresentation wordSize R: SPReg]]) ifTrue: [i > methodOrBlockNumTemps ifTrue: [self deassignRegister: current registerOrNone in: mergeSimStack. self deassignRegister: current registerOrNone in: simStack. self deny: (self register: current registerOrNone isInMask: self liveRegistersInSelfAndTemps)]]]]. self updateSimSpillBase! Item was changed: ----- Method: RegisterAllocatingCogit>>moveVolatileSimStackEntriesToRegisters (in category 'bytecode generator support') ----- moveVolatileSimStackEntriesToRegisters + self moveVolatileSimStackEntriesToRegistersPreserving: self allocatedRegisters! - "When jumping forward to a merge point the stack must 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. - First of all, if the constant requires an annotation then it is difficult to deal with. But if the constant - does not require an annotation one way would be for a SimStackEntry for an SSConstant to refer to - the loading instruction and then at the merge simply change the loading instruction to a Label if the - constant is the same on both branches]. - Volatile contents are anything not spilled to the stack, because as yet we can only merge registers." - <inline: true> - | allocatedRegs | - <var: #desc type: #'SimStackEntry *'> - allocatedRegs := self allocatedRegisters. - self assert: simSpillBase >= 0. - simSpillBase to: simStackPtr do: - [:i| | desc reg | - desc := self simStackAt: i. - desc spilled - ifTrue: [simSpillBase := i] - ifFalse: - [desc registerOrNone = NoReg ifTrue: - [reg := self allocateRegNotConflictingWith: allocatedRegs. - reg = NoReg - ifTrue: [self halt] "have to spill" - ifFalse: - [desc storeToReg: reg. - allocatedRegs := allocatedRegs bitOr: (self registerMaskFor: reg)]]]]. - self deny: self duplicateRegisterAssignmentsInTemporaries! Item was added: + ----- Method: RegisterAllocatingCogit>>moveVolatileSimStackEntriesToRegistersPreserving: (in category 'bytecode generator support') ----- + moveVolatileSimStackEntriesToRegistersPreserving: registerSet + "When jumping forward to a merge point the stack must 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. + First of all, if the constant requires an annotation then it is difficult to deal with. But if the constant + does not require an annotation one way would be for a SimStackEntry for an SSConstant to refer to + the loading instruction and then at the merge simply change the loading instruction to a Label if the + constant is the same on both branches]. + Volatile contents are anything not spilled to the stack, because as yet we can only merge registers." + <inline: true> + | allocatedRegs | + <var: #desc type: #'SimStackEntry *'> + allocatedRegs := registerSet. + self assert: simSpillBase >= 0. + simSpillBase to: simStackPtr do: + [:i| | desc reg | + desc := self simStackAt: i. + desc spilled + ifTrue: [simSpillBase := i] + ifFalse: + [desc registerOrNone = NoReg ifTrue: + [reg := self allocateRegNotConflictingWith: allocatedRegs. + reg = NoReg + ifTrue: [self halt] "have to spill" + ifFalse: + [desc storeToReg: reg. + allocatedRegs := allocatedRegs bitOr: (self registerMaskFor: reg)]]]]. + self deny: self duplicateRegisterAssignmentsInTemporaries! Item was changed: ----- Method: RegisterAllocatingCogit>>setMergeSimStackOf: (in category 'bytecode generator support') ----- setMergeSimStackOf: fixup <var: #fixup type: #'BytecodeFixup *'> - self moveVolatileSimStackEntriesToRegisters. fixup mergeSimStack ifNil: [self assert: nextFixup <= numFixups. self cCode: [fixup mergeSimStack: mergeSimStacksBase + (nextFixup * self simStackSlots * (self sizeof: CogSimStackEntry))]. nextFixup := nextFixup + 1] ifNotNil: [self assert: fixup simStackPtr = simStackPtr. 0 to: simStackPtr do: [:i| self assert: ((self simStackAt: i) isSameEntryAs: (self addressOf: (fixup mergeSimStack at: i))). (self simStackAt: i) liveRegister ~= (self addressOf: (fixup mergeSimStack at: i)) liveRegister ifTrue: [(self simStackAt: i) liveRegister: NoReg]]]. fixup simStackPtr: simStackPtr. self cCode: [self mem: fixup mergeSimStack cp: simStack y: self simStackSlots * (self sizeof: CogSimStackEntry)] inSmalltalk: [fixup mergeSimStack: self copySimStack]! |
Free forum by Nabble | Edit this page |