Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscogSPC-eem.2124.mcz ==================== Summary ==================== Name: VMMaker.oscogSPC-eem.2124 Author: eem Time: 7 February 2017, 6:30:18.710736 pm UUID: 22d143af-9360-4d0d-9f4a-598e85c9970b Ancestors: VMMaker.oscogSPC-eem.2123 Cogit: Refactor sends of ensure[NonMerge]FixupAt:, moving the ever-present "- initialPC" into ensure[NonMerge]FixupAt:. =============== Diff against VMMaker.oscogSPC-eem.2123 =============== Item was changed: ----- Method: Cogit>>ensureFixupAt: (in category 'compile abstract instructions') ----- + ensureFixupAt: targetPC + "Make sure there's a flagged fixup at the target pc in fixups. - ensureFixupAt: 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: targetPC - initialPC. - fixup := self fixupAt: targetIndex. fixup notAFixup ifTrue: [fixup becomeFixup]. fixup recordBcpc: bytecodePC. ^fixup! 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." - ensureFixupAt: targetIndex | fixup | <var: #fixup type: #'BytecodeFixup *'> + fixup := self fixupAt: targetPC - initialPC. - fixup := self fixupAt: targetIndex. fixup needsFixup ifTrue: [fixup mergeSimStack ifNil: [self setMergeSimStackOf: fixup] ifNotNil: [self mergeCurrentSimStackWith: fixup]] ifFalse: [self assert: fixup mergeSimStack isNil. + self moveVolatileSimStackEntriesToRegisters. + self setMergeSimStackOf: fixup]. + ^super ensureFixupAt: targetPC! - self moveVolatileSimStackEntriesToRegisters. - self setMergeSimStackOf: fixup]. - ^super ensureFixupAt: targetIndex! 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 tyeh target, if required." - 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." | fixup | + fixup := super ensureNonMergeFixupAt: targetPC. - fixup := super ensureNonMergeFixupAt: targetIndex. fixup mergeSimStack ifNil: [self setMergeSimStackOf: fixup]. ^fixup! Item was changed: ----- Method: RegisterAllocatingCogit>>genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode (in category 'bytecode generators') ----- genExtJumpIfNotInstanceOfBehaviorsOrPopBytecode "SistaV1: * 254 11111110 kkkkkkkk jjjjjjjj branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)" | reg literal distance targetFixUp | reg := self allocateRegForStackEntryAt: 0. self ssTop popToReg: reg. literal := self getLiteral: (extA * 256 + byte1). extA := 0. distance := extB * 256 + byte2. extB := 0. numExtB := 0. "Because ensureFixupAt: will generate code to merge with the target simStack when required, it is necessary to tease apart the jump and the merge so that the merge code is only executed if the branch is taken. i.e. if merge code is required we generate jump not cond Lcontinue ... merge code ... jump Ltarget Lcontinue: instead of the incorrect ... merge code ... jump cond Ltarget" + (self mergeRequiredForJumpTo: bytecodePC + 3 + distance) ifTrue: - (self mergeRequiredForJumpTo: bytecodePC + 3 + distance - initialPC) ifTrue: [self shouldBeImplemented]. + targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance) to: #'AbstractInstruction *'. - targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'. (objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp]. self ssPop: 1. ^0! Item was changed: ----- Method: RegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') ----- genForwardersInlinedIdenticalOrNotIf: orNot | nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC 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]. label := self Label. self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. + "For now just deny we're in the situation we have yet to implement ;-) + self printSimStack; printSimStack: (self fixupAt: postBranchPC - initialPC) mergeSimStack" - "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 - initialPC) notAFixup ifTrue: "The next instruction is dead. we can skip it." [deadCode := true. + self ensureFixupAt: targetBytecodePC. + self ensureFixupAt: postBranchPC] - self ensureFixupAt: targetBytecodePC - initialPC. - self ensureFixupAt: postBranchPC - initialPC] ifFalse: [self deny: deadCode]. "push dummy value below" 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 ] - [ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ] ifTrue: + [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ]. - [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) 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>>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. - fixup := self ensureFixupAt: eventualTarget - initialPC. 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" - [self JumpZero: (self ensureFixupAt: eventualTarget - initialPC). "generates merge code" ok jmpTarget: (self annotateBytecode: self lastOpcode). ^0]. mbb := self JumpNonZero: 0. + self Jump: (self ensureFixupAt: eventualTarget). "generates merge code" - self Jump: (self ensureFixupAt: eventualTarget - initialPC). "generates merge code" mbb jmpTarget: self Label] ifFalse: [self genSubConstant: boolean R: reg. + self JumpZero: (self ensureFixupAt: eventualTarget). - self JumpZero: (self ensureFixupAt: eventualTarget - initialPC). 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." deadCode := true. "can't fall through" + self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC)). - self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC) - initialPC). ^ 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 | <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] 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]. 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]. "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). - operand: (self ensureFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - self Jump: (self ensureFixupAt: 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! 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. "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 - initialPC) notAFixup ifTrue: "The next instruction is dead. we can skip it." [deadCode := true. + self ensureFixupAt: targetBytecodePC. + self ensureFixupAt: postBranchPC] - self ensureFixupAt: targetBytecodePC - initialPC. - self ensureFixupAt: postBranchPC - initialPC] ifFalse: [self deny: deadCode]. "push dummy value below" self genConditionalBranch: (orNot == branchDescriptor isBranchTrue ifTrue: [JumpNonZero] ifFalse: [JumpZero]) + operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. - operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) 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). - [self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC). self ssPushConstant: objectMemory trueObject]. "dummy value" ^0! Item was changed: ----- Method: RegisterAllocatingCogit>>mergeRequiredForJumpTo: (in category 'bytecode generator support') ----- + mergeRequiredForJumpTo: targetPC - mergeRequiredForJumpTo: target "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." self flag: 'be lazy for now; this needs more work to ignore compatible sim stacks'. + ^(self fixupAt: targetPC - initialPC) hasMergeSimStack! - ^(self fixupAt: target - initialPC) hasMergeSimStack! Item was changed: ----- Method: SimpleStackBasedCogit>>genJumpIf:to: (in category 'bytecode generator support') ----- genJumpIf: boolean to: targetBytecodePC <inline: false> "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." | ok | <var: #ok type: #'AbstractInstruction *'> extA := 0. self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject. self PopR: TempReg. self genSubConstant: boolean R: TempReg. + self JumpZero: (self ensureFixupAt: targetBytecodePC). - self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC). self CmpCq: (boolean == objectMemory falseObject ifTrue: [objectMemory trueObject - objectMemory falseObject] ifFalse: [objectMemory falseObject - objectMemory trueObject]) R: TempReg. ok := self JumpZero: 0. self genCallMustBeBooleanFor: boolean. ok jmpTarget: (self annotateBytecode: self Label). ^0! Item was changed: ----- Method: SimpleStackBasedCogit>>genJumpTo: (in category 'bytecode generator support') ----- genJumpTo: targetBytecodePC + self Jump: (self ensureFixupAt: targetBytecodePC). - self Jump: (self ensureFixupAt: targetBytecodePC - initialPC). ^0! Item was changed: ----- Method: SistaCogit>>genBinaryInlineComparison:opFalse:destReg: (in category 'inline primitive generators') ----- genBinaryInlineComparison: opTrue opFalse: opFalse destReg: destReg "Inlined comparison. opTrue = jump for true and opFalse = jump for false" <var: #branchDescriptor type: #'BytecodeDescriptor *'> | nextPC branchDescriptor targetBytecodePC postBranchPC | self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ]. (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifTrue: "This is the path where the inlined comparison is followed immediately by a branch" [ (self fixupAt: nextPC - initialPC) notAFixup ifTrue: "The next instruction is dead. we can skip it." [deadCode := true. + self ensureFixupAt: targetBytecodePC. + self ensureFixupAt: postBranchPC ] - self ensureFixupAt: targetBytecodePC - initialPC. - self ensureFixupAt: postBranchPC - initialPC ] ifFalse: [self ssPushConstant: objectMemory trueObject]. "dummy value" self genConditionalBranch: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse]) + operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. - operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. "We can only elide the jump if the pc after nextPC is the same as postBranchPC. Branch following means it may not be." self nextDescriptorExtensionsAndNextPCInto: [:iguana1 :iguana2 :iguana3 :followingPC| nextPC := followingPC]. (deadCode and: [nextPC = postBranchPC]) ifFalse: + [ self Jump: (self ensureNonMergeFixupAt: postBranchPC) ] ] - [ self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC) ] ] ifFalse: "This is the path where the inlined comparison is *not* followed immediately by a branch" [| condJump jump | condJump := self genConditionalBranch: opTrue operand: 0. self genMoveFalseR: destReg. jump := self Jump: 0. condJump jmpTarget: (self genMoveTrueR: destReg). jump jmpTarget: self Label]. ^ 0! Item was changed: ----- Method: SistaCogit>>genCounterTripOnlyJumpIf:to: (in category 'bytecode generator support') ----- genCounterTripOnlyJumpIf: boolean to: targetBytecodePC "Specific version if the branch is only reached while falling through if the counter trips after an inlined #== branch. We do not regenerate the counter logic in this case to avoid 24 bytes instructions." <var: #ok type: #'AbstractInstruction *'> <var: #mustBeBooleanTrampoline type: #'AbstractInstruction *'> | ok mustBeBooleanTrampoline | extA := 0. self ssFlushTo: simStackPtr - 1. self ssTop popToReg: TempReg. self ssPop: 1. counterIndex := counterIndex + 1. "counters are increased / decreased in the inlined branch" "We need SendNumArgsReg because of the mustBeBooleanTrampoline" self ssAllocateRequiredReg: SendNumArgsReg. self MoveCq: 1 R: SendNumArgsReg. "The first time this is reached, it calls necessarily the counter trip for the trampoline because SendNumArgsReg is non zero" mustBeBooleanTrampoline := self genCallMustBeBooleanFor: boolean. self annotateBytecode: self Label. "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. self genSubConstant: boolean R: TempReg. + self JumpZero: (self ensureFixupAt: targetBytecodePC). - self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC). self CmpCq: (boolean = objectMemory falseObject ifTrue: [objectMemory trueObject - objectMemory falseObject] ifFalse: [objectMemory falseObject - objectMemory trueObject]) R: TempReg. ok := self JumpZero: 0. self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip." self Jump: mustBeBooleanTrampoline. ok jmpTarget: self Label. ^0! Item was changed: ----- Method: SistaCogit>>genExtJumpIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') ----- genExtJumpIfNotInstanceOfBehaviorsBytecode "SistaV1: * 254 11111110 kkkkkkkk jjjjjjjj branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)" | reg literal distance targetFixUp inverse | "We lose the information of in which register is stack top when jitting the branch target so we need to flush everything. We could use a fixed register here...." reg := self allocateRegForStackEntryAt: 0. self ssTop popToReg: reg. self ssPop: 1. self ssFlushTo: simStackPtr. "flushed but the value is still in reg" literal := self getLiteral: (extA * 256 + byte1). (inverse := extB < 0) ifTrue: [extB := extB + 128]. distance := extB * 256 + byte2. extA := extB := numExtB := 0. + targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance) to: #'AbstractInstruction *'. - targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'. inverse ifFalse: [(objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp] ] ifTrue: [(objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg instanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg instanceOfBehavior: literal target: targetFixUp]]. ^0! Item was changed: ----- Method: SistaCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') ----- genForwardersInlinedIdenticalOrNotIf: orNot "Override to count inlined branches if followed by a conditional branch. We borrow the following conditional branch's counter and when about to inline the comparison we decrement the counter (without writing it back) and if it trips simply abort the inlining, falling back to the normal send which will then continue to the conditional branch which will trip and enter the abort." | nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask | <var: #fixup type: #'BytecodeFixup *'> <var: #countTripped type: #'AbstractInstruction *'> <var: #label type: #'AbstractInstruction *'> <var: #branchDescriptor type: #'BytecodeDescriptor *'> <var: #jumpEqual type: #'AbstractInstruction *'> <var: #jumpNotEqual type: #'AbstractInstruction *'> ((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue: [^super genForwardersInlinedIdenticalOrNotIf: orNot]. regMask := 0. self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ]. unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not. unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not. "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)." rcvrReg:= argReg := NoReg. self allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg rcvrNeedsReg: unforwardRcvr into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ]. argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ]. rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ]. "Only interested in inlining if followed by a conditional branch." (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. unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ]. unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ]. counterReg := self allocateRegNotConflictingWith: regMask. self genExecutionCountLogicInto: [ :cAddress :countTripBranch | counterAddress := cAddress. countTripped := countTripBranch ] counterReg: counterReg. self assert: (unforwardArg or: [ unforwardRcvr ]). self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. orNot == branchDescriptor isBranchTrue "orNot is true for ~~" ifFalse: + [ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ] - [ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ] ifTrue: + [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ]. - [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ]. self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress. self Jump: fixup. countTripped jmpTarget: self Label. "inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer" self ssPop: -2. self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. "This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. We therefore directly assign the result to TempReg to save one move instruction" jumpEqual := orNot ifFalse: [self JumpZero: 0] ifTrue: [self JumpNonZero: 0]. self genMoveFalseR: TempReg. jumpNotEqual := self Jump: 0. jumpEqual jmpTarget: (self genMoveTrueR: TempReg). jumpNotEqual jmpTarget: self Label. self ssPushRegister: TempReg. (self fixupAt: nextPC - initialPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ]. ^ 0! Item was changed: ----- Method: SistaCogit>>genJumpIf:to: (in category 'bytecode generator support') ----- genJumpIf: boolean to: targetBytecodePC "The heart of performance counting in Sista. Conditional branches are 6 times less frequent than sends and can provide basic block frequencies (send counters can't). Each conditional has a 32-bit counter split into an upper 16 bits counting executions and a lower half counting untaken executions of the branch. Executing the branch decrements the upper half, tripping if the count goes negative. Not taking the branch decrements the lower half. N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:) so that scanning for send and branch data is simplified and that branch data is correct." <inline: false> | ok counterAddress countTripped retry nextPC nextDescriptor desc eventualTarget | <var: #ok type: #'AbstractInstruction *'> <var: #desc type: #'CogSimStackEntry *'> <var: #retry type: #'AbstractInstruction *'> <var: #countTripped type: #'AbstractInstruction *'> <var: #nextDescriptor type: #'BytecodeDescriptor *'> "In optimized code we don't generate counters to improve performance" (coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. "If the branch is reached only for the counter trip trampoline (typically, var1 == var2 ifTrue: falls through to the branch only for the trampoline) we generate a specific path to drastically reduce the number of machine instructions" branchReachedOnlyForCounterTrip ifTrue: [ branchReachedOnlyForCounterTrip := false. ^ self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC ]. "We detect and: / or:, if found, we don't generate the counters to avoid pathological counter slow down" boolean = objectMemory falseObject ifTrue: [ nextPC := bytecodePC + (self generatorAt: byte0) numBytes. nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset. nextDescriptor generator == #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset. nextDescriptor generator == #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. ]. extA := 0. "We ignore the noMustBeBoolean flag. It should not be present in methods with counters, and if it is we don't care." "We don't generate counters on branches on true/false, the basicblock usage can be inferred" desc := self ssTop. (desc type == SSConstant and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. eventualTarget := self eventualTargetOf: targetBytecodePC. self ssFlushTo: simStackPtr - 1. desc popToReg: TempReg. self ssPop: 1. "We need SendNumArgsReg because of the mustBeBooleanTrampoline" self ssAllocateRequiredReg: SendNumArgsReg. retry := self Label. self genExecutionCountLogicInto: [ :cAddress :countTripBranch | counterAddress := cAddress. countTripped := countTripBranch ] counterReg: SendNumArgsReg. counterIndex := counterIndex + 1. "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. self genSubConstant: boolean R: TempReg. + self JumpZero: (self ensureFixupAt: eventualTarget). - self JumpZero: (self ensureFixupAt: eventualTarget - initialPC). self genFallsThroughCountLogicCounterReg: SendNumArgsReg counterAddress: counterAddress. self CmpCq: (boolean = objectMemory falseObject ifTrue: [objectMemory trueObject - objectMemory falseObject] ifFalse: [objectMemory falseObject - objectMemory trueObject]) R: TempReg. ok := self JumpZero: 0. self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip." countTripped jmpTarget: (self genCallMustBeBooleanFor: boolean). "If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped: trampoline will return directly to machine code, returning the boolean. So the code should jump back to the retry point. The trampoline makes sure that TempReg has been reloaded." "Clément: For some reason if I write self annotateBytecode: (self Jump: retry) the annotation is not at the correct place." "Eliot: Annotations apply the the address following an instruction, and the annotation must be for the return address of the call (since this is the address the run-time sees), so it must be on a label before the jump, not after the jump." self annotateBytecode: self Label. self Jump: retry. ok jmpTarget: self Label. ^0! Item was changed: ----- Method: SistaCogit>>genSpecialSelectorComparison (in category 'bytecode generators') ----- genSpecialSelectorComparison "Override to count inlined branches if followed by a conditional branch. We borrow the following conditional branch's counter and when about to inline the comparison we decrement the counter (without writing it back) and if it trips simply abort the inlining, falling back to the normal send which will then continue to the conditional branch which will trip and enter the abort." | nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB counterAddress countTripped counterReg index | <var: #countTripped type: #'AbstractInstruction *'> <var: #primDescriptor type: #'BytecodeDescriptor *'> <var: #jumpNotSmallInts type: #'AbstractInstruction *'> <var: #branchDescriptor type: #'BytecodeDescriptor *'> (coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self genSpecialSelectorComparisonWithoutCounters ]. 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]. "short-cut the jump if operands are SmallInteger constants." (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 MoveR: ReceiverResultReg R: TempReg] ifFalse: [self marshallSendArguments: 1. self MoveR: Arg0Reg R: TempReg]. jumpNotSmallInts := (argIsInt or: [rcvrIsInt]) ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg] ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: ReceiverResultReg andScratch: TempReg scratch: ClassReg]. counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg). self genExecutionCountLogicInto: [ :cAddress :countTripBranch | counterAddress := cAddress. countTripped := countTripBranch ] counterReg: counterReg. 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. - operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress. + self Jump: (self ensureNonMergeFixupAt: postBranchPC). - self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC). countTripped jmpTarget: (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: SistaCogitClone>>genBinaryInlineComparison:opFalse:destReg: (in category 'inline primitive generators') ----- genBinaryInlineComparison: opTrue opFalse: opFalse destReg: destReg "Inlined comparison. opTrue = jump for true and opFalse = jump for false" <var: #branchDescriptor type: #'BytecodeDescriptor *'> | nextPC branchDescriptor targetBytecodePC postBranchPC | self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ]. (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifTrue: "This is the path where the inlined comparison is followed immediately by a branch" [ (self fixupAt: nextPC - initialPC) notAFixup ifTrue: "The next instruction is dead. we can skip it." [deadCode := true. + self ensureFixupAt: targetBytecodePC. + self ensureFixupAt: postBranchPC ] - self ensureFixupAt: targetBytecodePC - initialPC. - self ensureFixupAt: postBranchPC - initialPC ] ifFalse: [self ssPushConstant: objectMemory trueObject]. "dummy value" self genConditionalBranch: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse]) + operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. + deadCode ifFalse: [ self Jump: (self ensureNonMergeFixupAt: postBranchPC) ] ] - operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - deadCode ifFalse: [ self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC) ] ] ifFalse: "This is the path where the inlined comparison is *not* followed immediately by a branch" [| condJump jump | condJump := self genConditionalBranch: opTrue operand: 0. self genMoveFalseR: destReg. jump := self Jump: 0. condJump jmpTarget: (self genMoveTrueR: destReg). jump jmpTarget: self Label]. ^ 0! Item was changed: ----- Method: SistaCogitClone>>genExtJumpIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') ----- genExtJumpIfNotInstanceOfBehaviorsBytecode "SistaV1: * 254 11111110 kkkkkkkk jjjjjjjj branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)" | reg literal distance targetFixUp inverse | "We lose the information of in which register is stack top when jitting the branch target so we need to flush everything. We could use a fixed register here...." reg := self allocateRegForStackEntryAt: 0. self ssTop popToReg: reg. self ssFlushTo: simStackPtr. "flushed but the value is still in reg" self ssPop: 1. literal := self getLiteral: (extA * 256 + byte1). (inverse := extB < 0) ifTrue: [extB := extB + 128]. distance := extB * 256 + byte2. extA := extB := numExtB := 0. + targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance) to: #'AbstractInstruction *'. - targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'. inverse ifFalse: [(objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp] ] ifTrue: [(objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg instanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg instanceOfBehavior: literal target: targetFixUp]]. ^0! Item was changed: ----- Method: SistaRegisterAllocatingCogit>>genCounterTripOnlyJumpIf:to: (in category 'bytecode generator support') ----- genCounterTripOnlyJumpIf: boolean to: targetBytecodePC "Specific version if the branch is only reached while falling through if the counter trips after an inlined #== branch. We do not regenerate the counter logic in this case to avoid 24 bytes instructions." <var: #ok type: #'AbstractInstruction *'> <var: #mustBeBooleanTrampoline type: #'AbstractInstruction *'> | ok mustBeBooleanTrampoline | extA := 0. self ssTop popToReg: TempReg. self ssPop: 1. counterIndex := counterIndex + 1. "counters are increased / decreased in the inlined branch" "We need SendNumArgsReg because of the mustBeBooleanTrampoline" self ssAllocateRequiredReg: SendNumArgsReg. self MoveCq: 1 R: SendNumArgsReg. "The first time this is reached, it calls necessarily the counter trip for the trampoline because SendNumArgsReg is non zero" mustBeBooleanTrampoline := self genCallMustBeBooleanFor: boolean. self annotateBytecode: self Label. "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. self genSubConstant: boolean R: TempReg. + self JumpZero: (self ensureFixupAt: targetBytecodePC). - self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC). self CmpCq: (boolean = objectMemory falseObject ifTrue: [objectMemory trueObject - objectMemory falseObject] ifFalse: [objectMemory falseObject - objectMemory trueObject]) R: TempReg. ok := self JumpZero: 0. self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip." self Jump: mustBeBooleanTrampoline. ok jmpTarget: self Label. ^0! Item was changed: ----- Method: SistaRegisterAllocatingCogit>>genExtJumpIfNotInstanceOfBehaviorsBytecode (in category 'bytecode generators') ----- genExtJumpIfNotInstanceOfBehaviorsBytecode "SistaV1: * 254 11111110 kkkkkkkk jjjjjjjj branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)" | reg literal distance targetFixUp inverse | "We lose the information of in which register is stack top when jitting the branch target so we need to flush everything. We could use a fixed register here...." reg := self allocateRegForStackEntryAt: 0. self ssTop popToReg: reg. self ssPop: 1. literal := self getLiteral: (extA * 256 + byte1). (inverse := extB < 0) ifTrue: [extB := extB + 128]. distance := extB * 256 + byte2. extA := extB := numExtB := 0. "For now just deny we're in the situation we have yet to implement ;-)" self deny: (self mergeRequiredForJumpTo: bytecodePC + 3 + distance). + targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance) to: #'AbstractInstruction *'. - targetFixUp := self cCoerceSimple: (self ensureFixupAt: bytecodePC + 3 + distance - initialPC) to: #'AbstractInstruction *'. inverse ifFalse: [(objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg notInstanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg notInstanceOfBehavior: literal target: targetFixUp] ] ifTrue: [(objectMemory isArrayNonImm: literal) ifTrue: [objectRepresentation branchIf: reg instanceOfBehaviors: literal target: targetFixUp] ifFalse: [objectRepresentation branchIf: reg instanceOfBehavior: literal target: targetFixUp]]. ^0! Item was changed: ----- Method: SistaRegisterAllocatingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') ----- genForwardersInlinedIdenticalOrNotIf: orNot "Override to count inlined branches if followed by a conditional branch. We borrow the following conditional branch's counter and when about to inline the comparison we decrement the counter (without writing it back) and if it trips simply abort the inlining, falling back to the normal send which will then continue to the conditional branch which will trip and enter the abort." | nextPC postBranchPC targetBytecodePC branchDescriptor counterReg fixup jumpEqual jumpNotEqual counterAddress countTripped unforwardArg unforwardRcvr argReg rcvrReg regMask | <var: #fixup type: #'BytecodeFixup *'> <var: #countTripped type: #'AbstractInstruction *'> <var: #label type: #'AbstractInstruction *'> <var: #branchDescriptor type: #'BytecodeDescriptor *'> <var: #jumpEqual type: #'AbstractInstruction *'> <var: #jumpNotEqual type: #'AbstractInstruction *'> ((coInterpreter isOptimizedMethod: methodObj) or: [needsFrame not]) ifTrue: [^super genForwardersInlinedIdenticalOrNotIf: orNot]. regMask := 0. self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ]. unforwardRcvr := (objectRepresentation isUnannotatableConstant: (self ssValue: 1)) not. unforwardArg := (objectRepresentation isUnannotatableConstant: self ssTop) not. "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)." rcvrReg:= argReg := NoReg. self allocateEqualsEqualsRegistersArgNeedsReg: unforwardArg rcvrNeedsReg: unforwardRcvr into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ]. argReg ~= NoReg ifTrue: [ regMask := self registerMaskFor: argReg ]. rcvrReg ~= NoReg ifTrue: [ regMask := regMask bitOr: (self registerMaskFor: rcvrReg) ]. "Only interested in inlining if followed by a conditional branch." (branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse: [^ self genIdenticalNoBranchArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg orNotIf: orNot]. unforwardArg ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: argReg scratchReg: TempReg ]. unforwardRcvr ifTrue: [ objectRepresentation genEnsureOopInRegNotForwarded: rcvrReg scratchReg: TempReg ]. counterReg := self allocateRegNotConflictingWith: regMask. self genExecutionCountLogicInto: [ :cAddress :countTripBranch | counterAddress := cAddress. countTripped := countTripBranch ] counterReg: counterReg. self assert: (unforwardArg or: [ unforwardRcvr ]). self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. orNot == branchDescriptor isBranchTrue "orNot is true for ~~" ifFalse: + [ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ] - [ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ] ifTrue: + [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ]. - [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger ]. self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress. self Jump: fixup. countTripped jmpTarget: self Label. "inlined version of #== ignoring the branchDescriptor if the counter trips to have normal state for the optimizer" self ssPop: -2. self genCmpArgIsConstant: unforwardArg not rcvrIsConstant: unforwardRcvr not argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. "This code necessarily directly falls through the jumpIf: code which pops the top of the stack into TempReg. We therefore directly assign the result to TempReg to save one move instruction" jumpEqual := orNot ifFalse: [self JumpZero: 0] ifTrue: [self JumpNonZero: 0]. self genMoveFalseR: TempReg. jumpNotEqual := self Jump: 0. jumpEqual jmpTarget: (self genMoveTrueR: TempReg). jumpNotEqual jmpTarget: self Label. self ssPushRegister: TempReg. (self fixupAt: nextPC - initialPC) notAFixup ifTrue: [ branchReachedOnlyForCounterTrip := true ]. ^ 0! Item was changed: ----- Method: SistaRegisterAllocatingCogit>>genJumpIf:to: (in category 'bytecode generator support') ----- genJumpIf: boolean to: targetBytecodePC "The heart of performance counting in Sista. Conditional branches are 6 times less frequent than sends and can provide basic block frequencies (send counters can't). Each conditional has a 32-bit counter split into an upper 16 bits counting executions and a lower half counting untaken executions of the branch. Executing the branch decrements the upper half, tripping if the count goes negative. Not taking the branch decrements the lower half. N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:) so that scanning for send and branch data is simplified and that branch data is correct." <inline: false> | ok counterAddress countTripped retry nextPC nextDescriptor desc eventualTarget reg | <var: #ok type: #'AbstractInstruction *'> <var: #desc type: #'CogSimStackEntry *'> <var: #retry type: #'AbstractInstruction *'> <var: #countTripped type: #'AbstractInstruction *'> <var: #nextDescriptor type: #'BytecodeDescriptor *'> "In optimized code we don't generate counters to improve performance" (coInterpreter isOptimizedMethod: methodObj) ifTrue: [^super genJumpIf: boolean to: targetBytecodePC]. "If the branch is reached only for the counter trip trampoline (typically, var1 == var2 ifTrue: falls through to the branch only for the trampoline) we generate a specific path to drastically reduce the number of machine instructions" branchReachedOnlyForCounterTrip ifTrue: [branchReachedOnlyForCounterTrip := false. ^self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC]. "We detect and: / or:, if found, we don't generate the counters to avoid pathological counter slow down" boolean = objectMemory falseObject ifTrue: [ nextPC := bytecodePC + (self generatorAt: byte0) numBytes. nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset. nextDescriptor generator == #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset. nextDescriptor generator == #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. ]. extA := 0. "We ignore the noMustBeBoolean flag. It should not be present in methods with counters, and if it is we don't care." "We don't generate counters on branches on true/false, the basicblock usage can be inferred" desc := self ssTop. (desc type == SSConstant and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ]. eventualTarget := self eventualTargetOf: targetBytecodePC. self flag: 'Because of the restriction on x64 that absolute loads must target %rax, it would perhaps be a better choice to use TempReg (%rax) for the counter reg and SendNumArgsReg for the boolean.'. "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. self ssPop: 1. "We need SendNumArgsReg because of the mustBeBooleanTrampoline" self ssAllocateRequiredReg: SendNumArgsReg. retry := self Label. self genExecutionCountLogicInto: [ :cAddress :countTripBranch | counterAddress := cAddress. countTripped := countTripBranch ] counterReg: SendNumArgsReg. counterIndex := counterIndex + 1. "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. self genSubConstant: boolean R: reg. + self JumpZero: (self ensureFixupAt: eventualTarget). - self JumpZero: (self ensureFixupAt: eventualTarget - initialPC). self genFallsThroughCountLogicCounterReg: SendNumArgsReg counterAddress: counterAddress. self CmpCq: (boolean = objectMemory falseObject ifTrue: [objectMemory trueObject - objectMemory falseObject] ifFalse: [objectMemory falseObject - objectMemory trueObject]) R: reg. ok := self JumpZero: 0. self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip." reg ~= TempReg ifTrue: [self MoveR: reg R: TempReg]. countTripped jmpTarget: self Label. self copySimStackToScratch: simSpillBase. self ssFlushTo: simStackPtr. self genCallMustBeBooleanFor: boolean. "If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped: trampoline will return directly to machine code, returning the boolean. So the code should jump back to the retry point. The trampoline preserves register state when taking the ceCounterTripped: path." "Clément: For some reason if I write self annotateBytecode: (self Jump: retry) the annotation is not at the correct place." "Eliot: Annotations apply the the address following an instruction, and the annotation must be for the return address of the call (since this is the address the run-time sees), so it must be on a label before the jump, not after the jump." self annotateBytecode: self Label. simSpillBase ~= scratchSpillBase ifTrue: [self assert: simSpillBase > scratchSpillBase. self AddCq: simSpillBase - scratchSpillBase * objectMemory wordSize R: SPReg]. self Jump: retry. ok jmpTarget: self Label. self restoreSimStackFromScratch. ^0! Item was changed: ----- Method: SistaRegisterAllocatingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') ----- genSpecialSelectorComparison "Override to count inlined branches if followed by a conditional branch. We borrow the following conditional branch's counter and when about to inline the comparison we decrement the counter (without writing it back) and if it trips simply abort the inlining, falling back to the normal send which will then continue to the conditional branch which will trip and enter the abort." | nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB counterAddress countTripped counterReg index rcvrReg argReg | <var: #countTripped type: #'AbstractInstruction *'> <var: #primDescriptor type: #'BytecodeDescriptor *'> <var: #jumpNotSmallInts type: #'AbstractInstruction *'> <var: #branchDescriptor type: #'BytecodeDescriptor *'> (coInterpreter isOptimizedMethod: methodObj) ifTrue: [^self genSpecialSelectorComparisonWithoutCounters]. 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]. "short-cut the jump if operands are SmallInteger constants." (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. counterReg := self allocateRegNotConflictingWith: (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. counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: rcvrReg and: argReg)]. jumpNotSmallInts := (argIsInt or: [rcvrIsInt]) ifTrue: [objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg] ifFalse: [objectRepresentation genJumpNotSmallIntegersIn: rcvrReg andScratch: TempReg scratch: ClassReg]. self genExecutionCountLogicInto: [ :cAddress :countTripBranch | counterAddress := cAddress. countTripped := countTripBranch ] counterReg: counterReg. 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) asUnsignedInteger. - operand: (self ensureFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress. + self Jump: (self ensureFixupAt: postBranchPC). - self Jump: (self ensureFixupAt: postBranchPC - initialPC). countTripped jmpTarget: (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: StackToRegisterMappingCogit>>ensureFixupAt: (in category 'compile abstract instructions') ----- + ensureFixupAt: targetPC + "Make sure there's a flagged fixup at the target pc in fixups. - ensureFixupAt: 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: targetPC - initialPC. - fixup := self fixupAt: targetIndex. self traceFixup: fixup. self cCode: '' inSmalltalk: + [self assert: simStackPtr = (self debugStackPointerFor: targetPC). - [self assert: simStackPtr = (self debugStackPointerFor: targetIndex + initialPC). (fixup isMergeFixupOrIsFixedUp and: [fixup isBackwardBranchFixup not]) ifTrue: "ignore backward branch targets" [self assert: fixup simStackPtr = simStackPtr]]. fixup isNonMergeFixupOrNotAFixup ifTrue: "convert a non-merge into a merge" [fixup becomeMergeFixup. fixup simStackPtr: simStackPtr. LowcodeVM ifTrue: [ fixup simNativeStackPtr: simNativeStackPtr. fixup simNativeStackSize: simNativeStackSize]] ifFalse: [fixup isBackwardBranchFixup ifTrue: "this is the target of a backward branch and so doesn't have a simStackPtr assigned yet." [fixup simStackPtr: simStackPtr. LowcodeVM ifTrue: [fixup simNativeStackPtr: simNativeStackPtr. fixup simNativeStackSize: simNativeStackSize]] ifFalse: [self assert: fixup simStackPtr = simStackPtr. LowcodeVM ifTrue: [self assert: fixup simNativeStackPtr = simNativeStackPtr. self assert: fixup simNativeStackSize = simNativeStackSize]]]. fixup recordBcpc: bytecodePC. ^fixup! Item was changed: ----- Method: StackToRegisterMappingCogit>>ensureNonMergeFixupAt: (in category 'compile abstract instructions') ----- + ensureNonMergeFixupAt: targetPC + "Make sure there's a flagged fixup at the target pc in fixups. - 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: targetPC - initialPC. - fixup := self fixupAt: targetIndex. fixup notAFixup ifTrue: [fixup becomeNonMergeFixup]. self cCode: '' inSmalltalk: [fixup isMergeFixupOrIsFixedUp ifTrue: [self assert: (fixup isBackwardBranchFixup + or: [fixup simStackPtr = (self debugStackPointerFor: targetPC)])]]. - or: [fixup simStackPtr = (self debugStackPointerFor: targetIndex + initialPC)])]]. fixup recordBcpc: bytecodePC. ^fixup! Item was changed: ----- Method: StackToRegisterMappingCogit>>genForwardersInlinedIdenticalOrNotIf: (in category 'bytecode generators') ----- genForwardersInlinedIdenticalOrNotIf: orNot | nextPC branchDescriptor unforwardRcvr argReg targetBytecodePC 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. "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 - initialPC) notAFixup ifTrue: "The next instruction is dead. we can skip it." [deadCode := true. + self ensureFixupAt: targetBytecodePC. + self ensureFixupAt: postBranchPC] - self ensureFixupAt: targetBytecodePC - initialPC. - self ensureFixupAt: postBranchPC - initialPC] ifFalse: [self deny: deadCode]. "push dummy value below" self assert: (unforwardArg or: [unforwardRcvr]). orNot == branchDescriptor isBranchTrue "orNot is true for ~~" ifFalse: + [ fixup := (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger ] - [ fixup := (self ensureNonMergeFixupAt: postBranchPC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger ] ifTrue: + [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. + self JumpZero: (self ensureNonMergeFixupAt: postBranchPC) asUnsignedInteger ]. - [ fixup := (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - self JumpZero: (self ensureNonMergeFixupAt: postBranchPC - initialPC) 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: StackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generator support') ----- genJumpIf: boolean to: targetBytecodePC <inline: false> | desc fixup ok eventualTarget | <var: #desc type: #'CogSimStackEntry *'> <var: #fixup type: #'BytecodeFixup *'> <var: #ok type: #'AbstractInstruction *'> eventualTarget := self eventualTargetOf: targetBytecodePC. self ssFlushTo: simStackPtr - 1. desc := self ssTop. self ssPop: 1. (desc type == SSConstant and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue: ["Must arrange there's a fixup at the target whether it is jumped to or not so that the simStackPtr can be kept correct." + fixup := self ensureFixupAt: eventualTarget. - fixup := self ensureFixupAt: eventualTarget - initialPC. "Must annotate the bytecode for correct pc mapping." self annotateBytecode: (desc constant = boolean ifTrue: [self Jump: fixup] ifFalse: [self prevInstIsPCAnnotated ifTrue: [self Nop] ifFalse: [self Label]]). extA := 0. ^0]. desc popToReg: TempReg. "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. self genSubConstant: boolean R: TempReg. + self JumpZero: (self ensureFixupAt: eventualTarget). - self JumpZero: (self ensureFixupAt: eventualTarget - initialPC). self extASpecifiesNoMustBeBoolean ifTrue: [ extA := 0. self annotateBytecode: self lastOpcode. ^ 0]. extA := 0. self CmpCq: (boolean = objectMemory falseObject ifTrue: [objectMemory trueObject - objectMemory falseObject] ifFalse: [objectMemory falseObject - objectMemory trueObject]) R: TempReg. ok := self JumpZero: 0. self genCallMustBeBooleanFor: boolean. ok jmpTarget: (self annotateBytecode: self Label). ^0! Item was changed: ----- Method: StackToRegisterMappingCogit>>genJumpTo: (in category 'bytecode generator support') ----- genJumpTo: targetBytecodePC self ssFlushTo: simStackPtr. deadCode := true. "can't fall through" + self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC)). - self Jump: (self ensureFixupAt: (self eventualTargetOf: targetBytecodePC) - initialPC). ^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 MoveR: ReceiverResultReg R: TempReg] ifFalse: [self marshallSendArguments: 1. self MoveR: Arg0Reg R: TempReg]. jumpNotSmallInts := (argIsInt or: [rcvrIsInt]) 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). - operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. - self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC). 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>>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]. "If branching the stack must be flushed for the merge" self ssFlushTo: simStackPtr - 2. self genCmpArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg. self ssPop: 2. "Further since there is a following conditional jump bytecode, define non-merge fixups and leave the cond bytecode to set the mergeness." (self fixupAt: nextPC - initialPC) notAFixup ifTrue: "The next instruction is dead. we can skip it." [deadCode := true. + self ensureFixupAt: targetBytecodePC. + self ensureFixupAt: postBranchPC] - self ensureFixupAt: targetBytecodePC - initialPC. - self ensureFixupAt: postBranchPC - initialPC] ifFalse: [self deny: deadCode]. "push dummy value below" self genConditionalBranch: (orNot == branchDescriptor isBranchTrue ifTrue: [JumpNonZero] ifFalse: [JumpZero]) + operand: (self ensureNonMergeFixupAt: targetBytecodePC) asUnsignedInteger. - operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) 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). - [self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC). self ssPushConstant: objectMemory trueObject]. "dummy value" ^0! |
Free forum by Nabble | Edit this page |