diff --git a/Druid-Tests/DRDeadCodeEliminationTest.class.st b/Druid-Tests/DRDeadCodeEliminationTest.class.st index a8fd5c1f..8f8f5dbe 100644 --- a/Druid-Tests/DRDeadCodeEliminationTest.class.st +++ b/Druid-Tests/DRDeadCodeEliminationTest.class.st @@ -4,13 +4,17 @@ Class { #category : #'Druid-Tests-Optimizations' } +{ #category : #test } +DRDeadCodeEliminationTest >> setUp [ + + super setUp. + optimisation := DRDeadCodeElimination new +] + { #category : #tests } DRDeadCodeEliminationTest >> testDCEOnConditionalJump [ - | cfg copy1 copy2 copy3 copy4 copy5 copy6 jump add1 add2 phi| - optimisation := DRDeadCodeElimination new. - copy1 := DRCopy operands: { (DRConstantValue value: 1) } result: (DRTemporaryRegister id: 1). @@ -58,10 +62,7 @@ DRDeadCodeEliminationTest >> testDCEOnConditionalJump [ { #category : #tests } DRDeadCodeEliminationTest >> testDCEOnDeadEndInstruction [ - | cfg copy1 copy2 phi1| - - optimisation := DRDeadCodeElimination new. - + | cfg copy1 copy2 phi1| cfg := self setUpCFG: 2. cfg b1 addInstruction: (DRCopy operands: { DRConstantValue value: 1 } result: (DRTemporaryRegister id: 1)). @@ -87,9 +88,6 @@ DRDeadCodeEliminationTest >> testDCEOnDeadEndInstruction [ DRDeadCodeEliminationTest >> testDCEOnSeveralBlocs [ | b1 b2 cfg copy1 | - - optimisation := DRDeadCodeElimination new. - cfg := self setUpCFG: 2. b1 := cfg b1. @@ -107,13 +105,28 @@ DRDeadCodeEliminationTest >> testDCEOnSeveralBlocs [ self assert: cfg instructions size equals: 4. ] +{ #category : #test } +DRDeadCodeEliminationTest >> testNotRemoveUnusedMandatoryInstruction [ + + | cfg copy addition | + cfg := self setUpCFG: 2. + + cfg b2 addInstruction: (copy := DRObjectReferenceCopy + operands: + { (DRObjectReferenceValue expression: 'methodObj') } + result: (DRTemporaryRegister id: 1)). + addition := cfg b2 add: copy to: 1. + + optimisation applyTo: cfg. + + self denyCollection: cfg instructions includesAny: { addition }. + self assertCollection: cfg instructions includesAny: { copy } +] + { #category : #test } DRDeadCodeEliminationTest >> testRemoveUnusedNoop [ | cfg | - - optimisation := DRDeadCodeElimination new. - cfg := self setUpCFG: 2. cfg b2 addInstruction: (DRNoop new result: DRNoRegister new). diff --git a/Druid-Tests/DRLoopTest.class.st b/Druid-Tests/DRLoopTest.class.st index 469ddc54..0fc0aa59 100644 --- a/Druid-Tests/DRLoopTest.class.st +++ b/Druid-Tests/DRLoopTest.class.st @@ -47,7 +47,7 @@ DRLoopTest >> testCanRetrieveLoopGraphWithMultipleBodyBlocks [ loopSubgraph := loop loopGraph. - loopBlocksIds := { 6. 11. 12. 7 }. + loopBlocksIds := { 6. 12. 13 . 7 }. self assertCollection: (loopSubgraph blocks collect: #id) hasSameElements: loopBlocksIds. ] @@ -78,3 +78,31 @@ DRLoopTest >> testCanRetrieveLoopGraphWithSingleBodyBlock [ loopBlocksIds := { 6. 7 }. self assertCollection: (loopSubgraph blocks collect: #id) hasSameElements: loopBlocksIds. ] + +{ #category : #tests } +DRLoopTest >> testFixBackjumpsIgnoreInnerRecursivePhis [ + + | cfg innerPhi loopHeaderPhi loopBody addition1 addition2 | + cfg := self setUpCFGWithConditionalWithPhi. + + loopHeaderPhi := cfg b1 phiWithVariables: { }. + addition1 := cfg b2 add: loopHeaderPhi to: 7. + + innerPhi := cfg b4 phiFunctions unique. + innerPhi replaceOperandAtIndex: 1 by: addition1. + + loopBody := cfg newBasicBlock. "5" + addition2 := loopBody add: innerPhi to: 8. + cfg b4 jumpIfTrueTo: loopBody ifFalseTo: cfg newBasicBlock. + loopBody backJumpTo: cfg b1. + loopHeaderPhi mergeOperands: { DRNullValue new. addition2 }. + cfg validate. + + self assert: loopHeaderPhi hasRecursiveUse. + self assert: innerPhi hasRecursiveUse. + self assert: cfg allBackJumps unique equals: loopBody endInstruction. + + cfg fixBackJumps. + + self assert: cfg allBackJumps unique equals: loopBody endInstruction +] diff --git a/Druid-Tests/DRPathGenerationTest.class.st b/Druid-Tests/DRPathGenerationTest.class.st index 56694691..a9d33edc 100644 --- a/Druid-Tests/DRPathGenerationTest.class.st +++ b/Druid-Tests/DRPathGenerationTest.class.st @@ -199,6 +199,29 @@ DRPathGenerationTest >> testConstraintsInferenceFromInnerBranches [ self assertConstraint: falseConstraint includes: (DRGreaterOrEqualsConstraint withValue: 20) ] +{ #category : #constraints } +DRPathGenerationTest >> testConstraintsInferenceFromJITExpressions [ + + | cfg jitExpression copy | + cfg := self setUpCFGWithConditional. + + "Put the JIT expression in a register" + jitExpression := cfg b1 jitCompileTimeVariable: 'extB'. + copy := cfg b1 copy: jitExpression. + + "Same comparison" + cfg b1 endInstruction replaceOperandAtIndex: 1 by: copy. + cfg b4 + jumpIf: copy + to: cfg newBasicBlock + ifFalseTo: cfg newBasicBlock. + + cfg generatePaths. + + "Sand clock pattern have half of the paths dead" + self assert: cfg deadPaths size equals: cfg pathsSize / 2 +] + { #category : #constraints } DRPathGenerationTest >> testConstraintsInferenceFromLoop [ diff --git a/Druid-Tests/DRProductionBytecodeTest.class.st b/Druid-Tests/DRProductionBytecodeTest.class.st index 69ddb7e1..f3f9c7e9 100644 --- a/Druid-Tests/DRProductionBytecodeTest.class.st +++ b/Druid-Tests/DRProductionBytecodeTest.class.st @@ -1810,9 +1810,11 @@ DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecode7 [ { #category : #tests } DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecode: index [ - | object storeCheckTrampoline | - storeCheckTrampoline := self compile: [ cogit RetN: 0 ]. - cogit ceStoreCheckTrampoline: storeCheckTrampoline. + | object fakeTrampoline | + fakeTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceStoreCheckTrampoline: fakeTrampoline. + cogit ceDeoptimiseFrameTrampoline: fakeTrampoline. + cogit bytecodePC: 87. self compileBytecode: 200 + index @@ -1835,13 +1837,58 @@ DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecode: index [ self assert: (memory fetchPointer: index ofObject: object) equals: memory trueObject ] +{ #category : #tests } +DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeCallImmutableTrampoline [ + + | object value immutableTrampoline fakeTrampoline bytecodePC | + + fakeTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceStoreCheckTrampoline: fakeTrampoline. + immutableTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceDeoptimiseFrameTrampoline: immutableTrampoline. + bytecodePC := 87. + cogit bytecodePC: bytecodePC. + + self + compileBytecode: 200 + selector: #storeAndPopReceiverVariableBytecode + thenDo: [ :generator | + cogit ssPushRegister: TempReg. + + "Execute the druid's compiled code" + generator value. + + "Then return without druid's compiled code" + cogit genUpArrowReturn ]. + + object := self newObjectWithSlots: 1. + memory setIsImmutableOf: object to: true. + + value := self newObjectWithSlots: 0. + + machineSimulator temporaryRegisterValue: value. + + self + prepareStackForPrimitiveReceiver: object + arguments: #( ) + method: 0. + + "Should arrive to trampoline to put the object in the remembered set" + self runFrom: cogInitialAddress until: immutableTrampoline. + + self assert: machineSimulator receiverRegisterValue equals: bytecodePC +] + { #category : #tests } DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeCallRememberTrampoline [ - | object value storeCheckTrampoline | + | object value storeCheckTrampoline fakeTrampoline | storeCheckTrampoline := self compile: [ cogit RetN: 0 ]. cogit ceStoreCheckTrampoline: storeCheckTrampoline. + fakeTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceDeoptimiseFrameTrampoline: fakeTrampoline. + cogit bytecodePC: 87. self compileBytecode: 200 @@ -1871,13 +1918,52 @@ DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeCallRememberT self assert: machineSimulator receiverRegisterValue equals: object ] +{ #category : #tests } +DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeImmutable [ + + | object value storeCheckTrampoline fakeTrampoline | + + storeCheckTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceStoreCheckTrampoline: storeCheckTrampoline. + fakeTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceDeoptimiseFrameTrampoline: fakeTrampoline. + cogit bytecodePC: 87. + + self + compileBytecode: 200 + selector: #storeAndPopReceiverVariableBytecode + thenDo: [ :generator | + cogit ssPushRegister: TempReg. + + "Execute the druid's compiled code" + generator value. + + "Then return without druid's compiled code" + cogit genUpArrowReturn ]. + + object := self newObjectWithSlots: 1. + memory setIsImmutableOf: object to: true. + + value := self newObjectWithSlots: 0. + + machineSimulator temporaryRegisterValue: value. + + self executePrimitiveWithReceiver: object. + + self assert: machineSimulator receiverRegisterValue equals: 87. + self assert: (memory fetchPointer: 0 ofObject: object) equals: memory nilObject +] + { #category : #tests } DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeNotRemember [ - | object value storeCheckTrampoline | + | object value storeCheckTrampoline fakeTrampoline | storeCheckTrampoline := self compile: [ cogit RetN: 0 ]. cogit ceStoreCheckTrampoline: storeCheckTrampoline. + fakeTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceDeoptimiseFrameTrampoline: fakeTrampoline. + cogit bytecodePC: 87. self compileBytecode: 200 @@ -1905,10 +1991,13 @@ DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeNotRemember [ { #category : #tests } DRProductionBytecodeTest >> testStoreAndPopReceiverVariableBytecodeRemember [ - | object value storeCheckTrampoline | + | object value storeCheckTrampoline fakeTrampoline | storeCheckTrampoline := self compile: [ cogit RetN: 0 ]. cogit ceStoreCheckTrampoline: storeCheckTrampoline. + fakeTrampoline := self compile: [ cogit RetN: 0 ]. + cogit ceDeoptimiseFrameTrampoline: fakeTrampoline. + cogit bytecodePC: 87. self compileBytecode: 200 diff --git a/Druid-Tests/DRSCCPConstantFoldingTest.class.st b/Druid-Tests/DRSCCPConstantFoldingTest.class.st index dd35dee6..d18233a3 100644 --- a/Druid-Tests/DRSCCPConstantFoldingTest.class.st +++ b/Druid-Tests/DRSCCPConstantFoldingTest.class.st @@ -566,6 +566,30 @@ DRSCCPConstantFoldingTest >> testFoldingLoadWithOperation [ self assert: cfg instructions nextToLast operand1 equals: load ] +{ #category : #tests } +DRSCCPConstantFoldingTest >> testFoldingObjectReferenceIntoJITExpression [ + + | cfg copy addition | + cfg := self setUpCFG: 1. + + cfg b1 addInstruction: (copy := DRObjectReferenceCopy + operands: + { (DRObjectReferenceValue expression: 'methodObj') } + result: (DRTemporaryRegister id: 999)). + addition := cfg b1 add: copy to: 1. + cfg b1 return: addition. + + optimisation applyTo: cfg. + + "Object references should keep to be annotated for GC" + self assert: cfg instructions first equals: copy. + "Anyway, users are folded" + self assert: cfg instructions second isCopy. + self assert: cfg instructions second operand1 expression equals: '(methodObj + 1)'. + + +] + { #category : #tests } DRSCCPConstantFoldingTest >> testNonConstantFoldingOf: aClass between: aDROperand1 and: aDROperand2 [ | cfg | diff --git a/Druid-Tests/DruidTestRTLCompiler.class.st b/Druid-Tests/DruidTestRTLCompiler.class.st index 88b3d9e7..3d572f05 100644 --- a/Druid-Tests/DruidTestRTLCompiler.class.st +++ b/Druid-Tests/DruidTestRTLCompiler.class.st @@ -203,42 +203,32 @@ DruidTestRTLCompiler >> gen_extPushIntegerBytecode [ DruidTestRTLCompiler >> gen_extSendSuperBytecode [ "AutoGenerated by Druid" - | live r5 r43 currentBlock | + | live r5 r46 currentBlock | live := 0. r5 := extA. extA := 0. BytecodeSetHasDirectedSuperSend=true ifTrue: [ - | r12 r43 | + | r12 r46 | r12 := extB. r12>=64 ifTrue: [ - | r17 | - r17 := extB. - extB := 0. - numExtB := 0. - self marshallSendArguments: ((byte1 bitAnd: 7) + ((r17 - 64) << 3)). - self - genMarshalledSend: ((byte1 >> 3) + (r5 << 5)) - numArgs: ((byte1 bitAnd: 7) + ((r17 - 64) << 3)) - sendTable: (directedSendUsesBinding - ifTrue: [directedSuperBindingSendTrampolines] - ifFalse: [directedSuperSendTrampolines]). + self deoptimize. ^ 0 ]. - r43 := extB. + r46 := extB. extB := 0. numExtB := 0. - self marshallSendArguments: ((byte1 bitAnd: 7) + (r43 << 3)). + self marshallSendArguments: ((byte1 bitAnd: 7) + (r46 << 3)). self genMarshalledSend: ((byte1 >> 3) + (r5 << 5)) - numArgs: ((byte1 bitAnd: 7) + (r43 << 3)) + numArgs: ((byte1 bitAnd: 7) + (r46 << 3)) sendTable: superSendTrampolines. ^ 0 ]. - r43 := extB. + r46 := extB. extB := 0. numExtB := 0. - self marshallSendArguments: ((byte1 bitAnd: 7) + (r43 << 3)). + self marshallSendArguments: ((byte1 bitAnd: 7) + (r46 << 3)). self genMarshalledSend: ((byte1 >> 3) + (r5 << 5)) - numArgs: ((byte1 bitAnd: 7) + (r43 << 3)) + numArgs: ((byte1 bitAnd: 7) + (r46 << 3)) sendTable: superSendTrampolines. ^ 0 ] @@ -341,67 +331,59 @@ DruidTestRTLCompiler >> gen_extendedPushBytecode [ ifNone: [ ^ self unknownBytecode ]. live := live bitOr: (self registerMaskFor: t0). self genMoveConstant: methodObj R: t0. - self - ssPushBase: t0 - offset: (byte1 bitAnd: 63) + LiteralStart << 3 + 8. + self ssPushConstant: + (coInterpreter int64AtPointer: ((methodObj + 8) + (((byte1 bitAnd: 63) + LiteralStart) << 3))). ^ 0 ]. ((byte1 >> 6) bitAnd: 3)=3 ifTrue: [ - | t0 b322 jumpTrue jump1 jumpNext t1 jump3 jump2 t2 | + | t0 | t0 := self allocateRegNotConflictingWith: live ifNone: [ ^ self unknownBytecode ]. live := live bitOr: (self registerMaskFor: t0). self genMoveConstant: methodObj R: t0. - self MoveM64: (byte1 bitAnd: 63) + LiteralStart << 3 + 8 r: t0 R: t0. - t1 := self - allocateRegNotConflictingWith: live - ifNone: [ ^ self unknownBytecode ]. - live := live bitOr: (self registerMaskFor: t1). - self MoveM64: 0 r: t0 R: t1. - self AndCq: 16r3FFFF7 R: t1. - self CmpCq: 0 R: t1. - jump1 := self JumpZero: 0. - self MoveR: t0 R: t1. - jump2 := self Jump: 0. - currentBlock := self Label. - jump1 jmpTarget: currentBlock. - self MoveM64: 8 r: t0 R: t1. - self MoveR: t1 R: t0. - b322 := self Label. - self MoveR: t0 R: t1. - self AndCq: 7 R: t1. - self CmpCq: 0 R: t1. - jump1 := self JumpNonZero: 0. - self MoveM64: 0 r: t0 R: t1. - self AndCq: 16r3FFFF7 R: t1. - t2 := self - allocateRegNotConflictingWith: live - ifNone: [ ^ self unknownBytecode ]. - live := live bitOr: (self registerMaskFor: t2). - self MoveR: t1 R: t2. - self CmpCq: 0 R: t2. - jumpTrue := self JumpZero: 0. - self MoveCq: 0 R: t2. - jumpNext := self Jump: 0. - jumpTrue jmpTarget: self Label. - self MoveCq: 1 R: t2. - jumpNext jmpTarget: self Label. - self CmpCq: 0 R: t1. - jump3 := self JumpZero: 0. - currentBlock := self Label. - jump1 jmpTarget: currentBlock. - self MoveR: t0 R: t1. - currentBlock := self Label. - jump2 jmpTarget: currentBlock. - self ssPushBase: t1 offset: ValueIndex << 3 + 8. - jump2 := self Jump: 0. - currentBlock := self Label. - jump3 jmpTarget: currentBlock. - self MoveM64: 8 r: t0 R: t2. - self MoveR: t2 R: t0. - jump3 := self Jump: b322. - currentBlock := self Label. - jump2 jmpTarget: currentBlock. + 0=((coInterpreter int64AtPointer: (coInterpreter int64AtPointer: ((methodObj + 8) + (((byte1 bitAnd: 63) + LiteralStart) << 3)))) bitAnd: 4194295) + ifTrue: [ + | jumpTrue jumpNext jump1 jump3 b316 t1 jump2 t2 | + self + MoveCq: + (coInterpreter int64AtPointer: (((coInterpreter int64AtPointer: ((methodObj + 8) + (((byte1 bitAnd: 63) + LiteralStart) << 3))) + 8) + 0)) + R: t0. + b316 := self Label. + t1 := self + allocateRegNotConflictingWith: live + ifNone: [ ^ self unknownBytecode ]. + live := live bitOr: (self registerMaskFor: t1). + self MoveR: t0 R: t1. + self AndCq: 7 R: t1. + self CmpCq: 0 R: t1. + jump1 := self JumpNonZero: 0. + self MoveM64: 0 r: t0 R: t1. + self AndCq: 16r3FFFF7 R: t1. + t2 := self + allocateRegNotConflictingWith: live + ifNone: [ ^ self unknownBytecode ]. + live := live bitOr: (self registerMaskFor: t2). + self MoveR: t1 R: t2. + self CmpCq: 0 R: t2. + jumpTrue := self JumpZero: 0. + self MoveCq: 0 R: t2. + jumpNext := self Jump: 0. + jumpTrue jmpTarget: self Label. + self MoveCq: 1 R: t2. + jumpNext jmpTarget: self Label. + self CmpCq: 0 R: t1. + jump2 := self JumpNonZero: 0. + self MoveM64: 8 r: t0 R: t2. + self MoveR: t2 R: t0. + jump3 := self Jump: b316. + currentBlock := self Label. + jump1 jmpTarget: currentBlock. + jump2 jmpTarget: currentBlock. + self ssPushConstant: + (coInterpreter int64AtPointer: (((coInterpreter int64AtPointer: ((methodObj + 8) + (((byte1 bitAnd: 63) + LiteralStart) << 3))) + 8) + (ValueIndex << 3))). + ^ 0 ]. + self ssPushConstant: + (coInterpreter int64AtPointer: (((coInterpreter int64AtPointer: ((methodObj + 8) + (((byte1 bitAnd: 63) + LiteralStart) << 3))) + 8) + (ValueIndex << 3))). ^ 0 ]. ^ 0 ] @@ -1309,9 +1291,9 @@ DruidTestRTLCompiler >> gen_primitiveDivideByConstant [ self DivR: ClassReg R: TempReg - Quo: ClassReg - Rem: TempReg. - self MoveR: ClassReg R: ReceiverResultReg. + Quo: TempReg + Rem: ClassReg. + self MoveR: TempReg R: ReceiverResultReg. self genPrimReturn. ^ CompletePrimitive ] @@ -2244,9 +2226,9 @@ DruidTestRTLCompiler >> gen_primitiveMod [ self DivR: ClassReg R: TempReg - Quo: TempReg - Rem: ClassReg. - self MoveR: ClassReg R: ReceiverResultReg. + Quo: ClassReg + Rem: TempReg. + self MoveR: TempReg R: ReceiverResultReg. self genPrimReturn. ^ CompletePrimitive ] @@ -2660,11 +2642,11 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ self DivR: Extra2Reg R: ClassReg - Quo: Extra2Reg - Rem: ClassReg. + Quo: ClassReg + Rem: Extra2Reg. self AndCq: 1 R: TempReg. self AddR: TempReg R: SendNumArgsReg. - self MoveCq: 0 R: ClassReg. + self MoveCq: 0 R: Extra2Reg. self CmpCq: 0 R: Extra0Reg. jump12 := self JumpZero: 0. jump13 := self Jump: 0. @@ -2673,32 +2655,29 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ jump12 := self Jump: 0. currentBlock := self Label. jump7 jmpTarget: currentBlock. - self MoveR: TempReg R: ClassReg. - self CmpCq: 2 R: ClassReg. + self MoveR: TempReg R: Extra2Reg. + self CmpCq: 2 R: Extra2Reg. jumpTrue := self JumpNonZero: 0. - self MoveCq: 0 R: ClassReg. + self MoveCq: 0 R: Extra2Reg. jumpNext := self Jump: 0. jumpTrue jmpTarget: self Label. - self MoveCq: 1 R: ClassReg. + self MoveCq: 1 R: Extra2Reg. jumpNext jmpTarget: self Label. self CmpCq: 2 R: TempReg. jump7 := self JumpNonZero: 0. - self MoveR: TempReg R: ClassReg. - self AddCq: 1 R: ClassReg. - self MoveCq: 2 R: Extra2Reg. + self MoveR: TempReg R: Extra2Reg. + self AddCq: 1 R: Extra2Reg. + self MoveCq: 2 R: ClassReg. self - DivR: Extra2Reg - R: ClassReg + DivR: ClassReg + R: Extra2Reg Quo: ClassReg Rem: Extra2Reg. self AndCq: 1 R: TempReg. self AddR: TempReg R: SendNumArgsReg. - self MoveCq: 0 R: TempReg. - self MoveR: ClassReg R: Extra2Reg. - self MoveR: TempReg R: ClassReg. + self MoveCq: 0 R: Extra2Reg. currentBlock := self Label. jump13 jmpTarget: currentBlock. - self MoveR: Extra2Reg R: TempReg. jump13 := self Jump: 0. currentBlock := self Label. jump6 jmpTarget: currentBlock. @@ -2708,15 +2687,15 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ jump5 jmpTarget: currentBlock. self AndCq: 16rFFFF R: ClassReg. self AddR: TempReg R: ClassReg. - self MoveCq: objectMemory nilObject R: TempReg. - self MoveR: TempReg R: Extra1Reg. + self MoveCq: objectMemory nilObject R: Extra2Reg. + self MoveR: Extra2Reg R: Extra1Reg. jump5 := self Jump: 0. currentBlock := self Label. jump4 jmpTarget: currentBlock. self AndCq: 16rFFFF R: ClassReg. self AddR: TempReg R: ClassReg. - self MoveCq: objectMemory nilObject R: TempReg. - self MoveR: TempReg R: Extra1Reg. + self MoveCq: objectMemory nilObject R: Extra2Reg. + self MoveR: Extra2Reg R: Extra1Reg. jump4 := self Jump: 0. currentBlock := self Label. jump3 jmpTarget: currentBlock. @@ -2732,21 +2711,19 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ jump4 jmpTarget: currentBlock. self CmpCq: 0 R: Extra0Reg. jump4 := self JumpZero: 0. - self MoveR: ClassReg R: TempReg. - self MoveR: Extra1Reg R: ClassReg. + self MoveR: Extra1Reg R: Extra2Reg. currentBlock := self Label. jump13 jmpTarget: currentBlock. - self MoveR: TempReg R: Extra3Reg. + self MoveR: ClassReg R: Extra3Reg. self MoveR: Extra3Reg Mw: 8 r: SPReg. self MoveR: SendNumArgsReg R: Extra3Reg. self MoveR: Extra3Reg Mw: 16 r: SPReg. - self MoveR: ClassReg R: Extra3Reg. + self MoveR: Extra2Reg R: Extra3Reg. self MoveR: Extra3Reg Mw: 24 r: SPReg. jump13 := self Jump: 0. currentBlock := self Label. jump4 jmpTarget: currentBlock. - self MoveR: ClassReg R: Extra2Reg. - self MoveR: Extra1Reg R: ClassReg. + self MoveR: Extra1Reg R: Extra2Reg. currentBlock := self Label. jump12 jmpTarget: currentBlock. self MoveM32: 4 r: ReceiverResultReg R: Extra0Reg. @@ -2756,15 +2733,15 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ jump12 := self JumpZero: 0. self CmpCq: 0 R: Extra0Reg. jump4 := self JumpBelow: 0. - self MoveR: Extra2Reg R: Extra3Reg. + self MoveR: ClassReg R: Extra3Reg. self MoveR: Extra3Reg Mw: 8 r: SPReg. self MoveR: SendNumArgsReg R: Extra3Reg. self MoveR: Extra3Reg Mw: 16 r: SPReg. - self MoveR: ClassReg R: Extra3Reg. + self MoveR: Extra2Reg R: Extra3Reg. self MoveR: Extra3Reg Mw: 24 r: SPReg. currentBlock := self Label. jump13 jmpTarget: currentBlock. - self MoveR: Arg0Reg R: TempReg. + self MoveR: Arg0Reg R: ClassReg. self MoveR: ReceiverResultReg R: Extra1Reg. self MoveMw: 8 r: SPReg R: Extra3Reg. self CmpCq: 255 R: Extra3Reg. @@ -2772,28 +2749,28 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ self MoveMw: 8 r: SPReg R: Extra3Reg. self CmpCq: 1 R: Extra3Reg. jump5 := self JumpLess: 0. - self MoveCq: 8 R: Extra2Reg. + self MoveCq: 8 R: TempReg. self MoveMw: 8 r: SPReg R: Extra3Reg. - self MulR: Extra3Reg R: Extra2Reg. + self MulR: Extra3Reg R: TempReg. jump6 := self Jump: 0. currentBlock := self Label. jump5 jmpTarget: currentBlock. - self MoveCq: 8 R: Extra2Reg. + self MoveCq: 8 R: TempReg. currentBlock := self Label. jump6 jmpTarget: currentBlock. - self AddCq: 8 R: Extra2Reg. + self AddCq: 8 R: TempReg. jump6 := self Jump: 0. currentBlock := self Label. jump13 jmpTarget: currentBlock. self MoveMw: 8 r: SPReg R: Extra3Reg. - self MoveR: Extra3Reg R: Extra2Reg. - self ArithmeticShiftRightCq: 56 R: Extra2Reg. - self CmpCq: 0 R: Extra2Reg. + self MoveR: Extra3Reg R: TempReg. + self ArithmeticShiftRightCq: 56 R: TempReg. + self CmpCq: 0 R: TempReg. jump13 := self JumpAbove: 0. - self MoveCq: 8 R: Extra2Reg. + self MoveCq: 8 R: TempReg. self MoveMw: 8 r: SPReg R: Extra3Reg. - self MulR: Extra3Reg R: Extra2Reg. - self AddCq: 16 R: Extra2Reg. + self MulR: Extra3Reg R: TempReg. + self AddCq: 16 R: TempReg. currentBlock := self Label. jump6 jmpTarget: currentBlock. self MoveAw: objectMemory freeStartAddress R: SendNumArgsReg. @@ -2801,24 +2778,24 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ self CmpCq: 255 R: Extra3Reg. jump6 := self JumpGreaterOrEqual: 0. self MoveMw: 8 r: SPReg R: Extra3Reg. - self MoveR: Extra3Reg R: ClassReg. - self LogicalShiftLeftCq: 56 R: ClassReg. + self MoveR: Extra3Reg R: Extra2Reg. + self LogicalShiftLeftCq: 56 R: Extra2Reg. self MoveMw: 16 r: SPReg R: Extra3Reg. self LogicalShiftLeftCq: 24 R: Extra3Reg. self MoveR: Extra3Reg Mw: 16 r: SPReg. self MoveMw: 16 r: SPReg R: Extra3Reg. - self AddR: Extra3Reg R: ClassReg. - self AddR: Extra0Reg R: ClassReg. - self OrCq: 0 R: ClassReg. - self MoveR: ClassReg M64: 0 r: SendNumArgsReg. - self MoveR: SendNumArgsReg R: ClassReg. + self AddR: Extra3Reg R: Extra2Reg. + self AddR: Extra0Reg R: Extra2Reg. + self OrCq: 0 R: Extra2Reg. + self MoveR: Extra2Reg M64: 0 r: SendNumArgsReg. + self MoveR: SendNumArgsReg R: Extra2Reg. jump5 := self Jump: 0. currentBlock := self Label. jump6 jmpTarget: currentBlock. self MoveMw: 8 r: SPReg R: Extra3Reg. - self MoveR: Extra3Reg R: ClassReg. - self AddCq: 16rFF00000000000000 R: ClassReg. - self MoveR: ClassReg M64: 0 r: SendNumArgsReg. + self MoveR: Extra3Reg R: Extra2Reg. + self AddCq: 16rFF00000000000000 R: Extra2Reg. + self MoveR: Extra2Reg M64: 0 r: SendNumArgsReg. self MoveMw: 16 r: SPReg R: Extra3Reg. self LogicalShiftLeftCq: 24 R: Extra3Reg. self MoveR: Extra3Reg Mw: 16 r: SPReg. @@ -2834,13 +2811,13 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ self MoveMw: 16 r: SPReg R: Extra3Reg. self MoveR: Extra3Reg M64: 8 r: SendNumArgsReg. self AddCq: 8 R: SendNumArgsReg. - self MoveR: SendNumArgsReg R: ClassReg. + self MoveR: SendNumArgsReg R: Extra2Reg. currentBlock := self Label. jump5 jmpTarget: currentBlock. self MoveAw: objectMemory freeStartAddress R: SendNumArgsReg. - self AddR: Extra2Reg R: SendNumArgsReg. + self AddR: TempReg R: SendNumArgsReg. self MoveR: SendNumArgsReg Aw: objectMemory freeStartAddress. - self MoveR: ClassReg R: Extra3Reg. + self MoveR: Extra2Reg R: Extra3Reg. self MoveR: Extra3Reg Mw: 32 r: SPReg. jump5 := self Jump: 0. currentBlock := self Label. @@ -2854,39 +2831,39 @@ DruidTestRTLCompiler >> gen_primitiveNewWithArg [ self CmpCq: 0 R: Extra3Reg. jump5 := self JumpZero: 0. self MoveMw: 32 r: SPReg R: Extra3Reg. - self MoveR: Extra3Reg R: ClassReg. - self AddCq: 8 R: ClassReg. - self MoveCq: 8 R: Extra2Reg. + self MoveR: Extra3Reg R: Extra2Reg. + self AddCq: 8 R: Extra2Reg. + self MoveCq: 8 R: TempReg. self MoveMw: 8 r: SPReg R: Extra3Reg. - self MulR: Extra3Reg R: Extra2Reg. + self MulR: Extra3Reg R: TempReg. self MoveMw: 32 r: SPReg R: Extra3Reg. self MoveR: Extra3Reg R: Extra0Reg. - self AddR: Extra2Reg R: Extra0Reg. + self AddR: TempReg R: Extra0Reg. self AddCq: 8 R: Extra0Reg. self SubCq: 1 R: Extra0Reg. b986 := self Label. - self CmpR: ClassReg R: Extra0Reg. + self CmpR: Extra2Reg R: Extra0Reg. jump13 := self JumpGreaterOrEqual: 0. - self MoveR: TempReg R: Extra2Reg. + self MoveR: ClassReg R: TempReg. self MoveR: Extra1Reg R: SendNumArgsReg. jump6 := self Jump: 0. currentBlock := self Label. jump13 jmpTarget: currentBlock. self MoveMw: 24 r: SPReg R: Extra3Reg. - self MoveR: Extra3Reg M64: 0 r: ClassReg. - self MoveR: ClassReg R: SendNumArgsReg. + self MoveR: Extra3Reg M64: 0 r: Extra2Reg. + self MoveR: Extra2Reg R: SendNumArgsReg. self AddCq: 8 R: SendNumArgsReg. - self MoveR: SendNumArgsReg R: ClassReg. + self MoveR: SendNumArgsReg R: Extra2Reg. jump13 := self Jump: b986. currentBlock := self Label. jump5 jmpTarget: currentBlock. - self MoveR: TempReg R: Extra2Reg. + self MoveR: ClassReg R: TempReg. self MoveR: Extra1Reg R: SendNumArgsReg. currentBlock := self Label. jump6 jmpTarget: currentBlock. self MoveMw: 32 r: SPReg R: Extra3Reg. self MoveR: Extra3Reg R: Extra1Reg. - self MoveR: Extra2Reg R: SendNumArgsReg. + self MoveR: TempReg R: SendNumArgsReg. self MoveR: SendNumArgsReg R: ClassReg. currentBlock := self Label. jump11 jmpTarget: currentBlock. @@ -3547,7 +3524,8 @@ DruidTestRTLCompiler >> gen_pushLiteralConstantBytecode [ ifNone: [ ^ self unknownBytecode ]. live := live bitOr: (self registerMaskFor: t0). self genMoveConstant: methodObj R: t0. - self ssPushBase: t0 offset: 1 + LiteralStart << 3 + 8. + self ssPushConstant: + (coInterpreter int64AtPointer: ((methodObj + 8) + ((1 + LiteralStart) << 3))). ^ 0 ] @@ -3555,63 +3533,56 @@ DruidTestRTLCompiler >> gen_pushLiteralConstantBytecode [ DruidTestRTLCompiler >> gen_pushLiteralVariable16CasesBytecode [ "AutoGenerated by Druid" - | jump1 jumpNext b232 t1 jump3 currentBlock t0 jumpTrue jump2 t2 live | + | live currentBlock t0 | live := 0. t0 := self allocateRegNotConflictingWith: live ifNone: [ ^ self unknownBytecode ]. live := live bitOr: (self registerMaskFor: t0). self genMoveConstant: methodObj R: t0. - self MoveM64: 0 + LiteralStart << 3 + 8 r: t0 R: t0. - t1 := self - allocateRegNotConflictingWith: live - ifNone: [ ^ self unknownBytecode ]. - live := live bitOr: (self registerMaskFor: t1). - self MoveM64: 0 r: t0 R: t1. - self AndCq: 16r3FFFF7 R: t1. - self CmpCq: 0 R: t1. - jump1 := self JumpZero: 0. - self MoveR: t0 R: t1. - jump2 := self Jump: 0. - currentBlock := self Label. - jump1 jmpTarget: currentBlock. - self MoveM64: 8 r: t0 R: t1. - self MoveR: t1 R: t0. - b232 := self Label. - self MoveR: t0 R: t1. - self AndCq: 7 R: t1. - self CmpCq: 0 R: t1. - jump1 := self JumpNonZero: 0. - self MoveM64: 0 r: t0 R: t1. - self AndCq: 16r3FFFF7 R: t1. - t2 := self - allocateRegNotConflictingWith: live - ifNone: [ ^ self unknownBytecode ]. - live := live bitOr: (self registerMaskFor: t2). - self MoveR: t1 R: t2. - self CmpCq: 0 R: t2. - jumpTrue := self JumpZero: 0. - self MoveCq: 0 R: t2. - jumpNext := self Jump: 0. - jumpTrue jmpTarget: self Label. - self MoveCq: 1 R: t2. - jumpNext jmpTarget: self Label. - self CmpCq: 0 R: t1. - jump3 := self JumpZero: 0. - currentBlock := self Label. - jump1 jmpTarget: currentBlock. - self MoveR: t0 R: t1. - currentBlock := self Label. - jump2 jmpTarget: currentBlock. - self ssPushBase: t1 offset: ValueIndex << 3 + 8. - jump2 := self Jump: 0. - currentBlock := self Label. - jump3 jmpTarget: currentBlock. - self MoveM64: 8 r: t0 R: t2. - self MoveR: t2 R: t0. - jump3 := self Jump: b232. - currentBlock := self Label. - jump2 jmpTarget: currentBlock. + 0=((coInterpreter int64AtPointer: (coInterpreter int64AtPointer: ((methodObj + 8) + ((0 + LiteralStart) << 3)))) bitAnd: 4194295) + ifTrue: [ + | jumpTrue jumpNext jump1 jump3 t1 jump2 b227 t2 | + self + MoveCq: + (coInterpreter int64AtPointer: (((coInterpreter int64AtPointer: ((methodObj + 8) + ((0 + LiteralStart) << 3))) + 8) + 0)) + R: t0. + b227 := self Label. + t1 := self + allocateRegNotConflictingWith: live + ifNone: [ ^ self unknownBytecode ]. + live := live bitOr: (self registerMaskFor: t1). + self MoveR: t0 R: t1. + self AndCq: 7 R: t1. + self CmpCq: 0 R: t1. + jump1 := self JumpNonZero: 0. + self MoveM64: 0 r: t0 R: t1. + self AndCq: 16r3FFFF7 R: t1. + t2 := self + allocateRegNotConflictingWith: live + ifNone: [ ^ self unknownBytecode ]. + live := live bitOr: (self registerMaskFor: t2). + self MoveR: t1 R: t2. + self CmpCq: 0 R: t2. + jumpTrue := self JumpZero: 0. + self MoveCq: 0 R: t2. + jumpNext := self Jump: 0. + jumpTrue jmpTarget: self Label. + self MoveCq: 1 R: t2. + jumpNext jmpTarget: self Label. + self CmpCq: 0 R: t1. + jump2 := self JumpNonZero: 0. + self MoveM64: 8 r: t0 R: t2. + self MoveR: t2 R: t0. + jump3 := self Jump: b227. + currentBlock := self Label. + jump1 jmpTarget: currentBlock. + jump2 jmpTarget: currentBlock. + self ssPushConstant: + (coInterpreter int64AtPointer: (((coInterpreter int64AtPointer: ((methodObj + 8) + ((0 + LiteralStart) << 3))) + 8) + (ValueIndex << 3))). + ^ 0 ]. + self ssPushConstant: + (coInterpreter int64AtPointer: (((coInterpreter int64AtPointer: ((methodObj + 8) + ((0 + LiteralStart) << 3))) + 8) + (ValueIndex << 3))). ^ 0 ] @@ -3838,7 +3809,7 @@ DruidTestRTLCompiler >> gen_shortUnconditionalJump [ DruidTestRTLCompiler >> gen_storeAndPopReceiverVariableBytecode [ "AutoGenerated by Druid" - | jump1 jump7 jumpNext t1 jump6 jump3 currentBlock t0 jump5 jump2 jumpTrue live t2 jump4 | + | jump1 jump7 jumpNext t1 jump6 jump3 currentBlock t0 jump5 jump2 jumpTrue jump8 live t2 jump4 | live := 0. self annotateBytecode: self Label. self ensureReceiverResultRegContainsSelf. @@ -3857,27 +3828,32 @@ DruidTestRTLCompiler >> gen_storeAndPopReceiverVariableBytecode [ allocateRegNotConflictingWith: live ifNone: [ ^ self unknownBytecode ]. live := live bitOr: (self registerMaskFor: t2). + self MoveM64: 0 r: t0 R: t2. + self ArithmeticShiftRightCq: 23 R: t2. + self AndCq: 1 R: t2. + self CmpCq: 0 R: t2. + jump1 := self JumpNonZero: 0. self MoveR: t0 R: t2. self AndCq: 7 R: t2. self ssFlushStack. self CmpCq: 0 R: t2. - jump1 := self JumpNonZero: 0. + jump2 := self JumpNonZero: 0. self MoveR: t0 R: t2. self AndCq: objectMemory getMemoryMap getSpaceMaskToUse R: t2. self CmpCq: objectMemory getMemoryMap getOldSpaceMask R: t2. - jump2 := self JumpNonZero: 0. + jump3 := self JumpNonZero: 0. self MoveR: t1 R: t2. self AndCq: 7 R: t2. self CmpCq: 0 R: t2. - jump3 := self JumpNonZero: 0. + jump4 := self JumpNonZero: 0. self MoveR: t1 R: t2. self AndCq: objectMemory getMemoryMap getSpaceMaskToUse R: t2. self CmpCq: objectMemory getMemoryMap getNewSpaceMask R: t2. - jump4 := self JumpZero: 0. + jump5 := self JumpZero: 0. self MoveCq: 0 R: t2. - jump5 := self Jump: 0. + jump6 := self Jump: 0. currentBlock := self Label. - jump4 jmpTarget: currentBlock. + jump5 jmpTarget: currentBlock. self MoveR: t1 R: t2. self CmpCq: objectMemory getMemoryMap getNewSpaceStart R: t2. jumpTrue := self JumpGreaterOrEqual: 0. @@ -3887,39 +3863,39 @@ DruidTestRTLCompiler >> gen_storeAndPopReceiverVariableBytecode [ self MoveCq: 1 R: t2. jumpNext jmpTarget: self Label. self CmpCq: 1 R: t2. - jump4 := self JumpZero: 0. + jump5 := self JumpZero: 0. currentBlock := self Label. - jump5 jmpTarget: currentBlock. - jump5 := self Jump: 0. + jump6 jmpTarget: currentBlock. + jump6 := self Jump: 0. currentBlock := self Label. - jump4 jmpTarget: currentBlock. + jump5 jmpTarget: currentBlock. self MoveM64: 0 r: t0 R: t2. self ArithmeticShiftRightCq: 29 R: t2. self AndCq: 1 R: t2. self CmpCq: 0 R: t2. - jump4 := self JumpNonZero: 0. + jump5 := self JumpNonZero: 0. self MoveR: t0 R: TempReg. backEnd saveAndRestoreLinkRegAround: [ self CallRT: ceStoreCheckTrampoline ]. self TstCq: 7 R: t1. - jump6 := self JumpNonZero: 0. - jump7 := self JumpZero: 0. + jump7 := self JumpNonZero: 0. + jump8 := self JumpZero: 0. currentBlock := self Label. - jump1 jmpTarget: currentBlock. jump2 jmpTarget: currentBlock. jump3 jmpTarget: currentBlock. - jump5 jmpTarget: currentBlock. jump4 jmpTarget: currentBlock. + jump6 jmpTarget: currentBlock. + jump5 jmpTarget: currentBlock. self TstCq: 7 R: t1. - jump4 := self JumpNonZero: 0. + jump5 := self JumpNonZero: 0. currentBlock := self Label. - jump7 jmpTarget: currentBlock. + jump8 jmpTarget: currentBlock. self CmpCq: objectMemory nilObject R: t1. - jump7 := self JumpAboveOrEqual: 0. + jump8 := self JumpAboveOrEqual: 0. self MoveCq: 0 R: t2. - jump5 := self Jump: 0. + jump6 := self Jump: 0. currentBlock := self Label. - jump7 jmpTarget: currentBlock. + jump8 jmpTarget: currentBlock. self MoveR: t1 R: t2. self CmpCq: objectMemory trueObject R: t2. jumpTrue := self JumpLessOrEqual: 0. @@ -3929,24 +3905,24 @@ DruidTestRTLCompiler >> gen_storeAndPopReceiverVariableBytecode [ self MoveCq: 1 R: t2. jumpNext jmpTarget: self Label. currentBlock := self Label. - jump5 jmpTarget: currentBlock. + jump6 jmpTarget: currentBlock. self CmpCq: 1 R: t2. - jump5 := self JumpZero: 0. + jump6 := self JumpZero: 0. self CmpCq: objectMemory getMemoryMap getNewSpaceStart R: t1. - jump7 := self JumpLess: 0. + jump8 := self JumpLess: 0. self MoveM64: 0 r: t0 R: t2. self ArithmeticShiftRightCq: 29 R: t2. self AndCq: 1 R: t2. self CmpCq: 0 R: t2. - jump3 := self JumpNonZero: 0. + jump4 := self JumpNonZero: 0. self MoveR: t0 R: t2. self AndCq: 7 R: t2. self CmpCq: 0 R: t2. - jump2 := self JumpZero: 0. + jump3 := self JumpZero: 0. self MoveCq: 0 R: t2. - jump1 := self Jump: 0. + jump2 := self Jump: 0. currentBlock := self Label. - jump2 jmpTarget: currentBlock. + jump3 jmpTarget: currentBlock. self MoveR: t0 R: t2. self AndCq: objectMemory getMemoryMap getSpaceMaskToUse R: t2. self CmpCq: objectMemory getMemoryMap getPermSpaceMask R: t2. @@ -3957,25 +3933,31 @@ DruidTestRTLCompiler >> gen_storeAndPopReceiverVariableBytecode [ self MoveCq: 1 R: t2. jumpNext jmpTarget: self Label. currentBlock := self Label. - jump1 jmpTarget: currentBlock. + jump2 jmpTarget: currentBlock. self CmpCq: 1 R: t2. - jump1 := self JumpNonZero: 0. + jump2 := self JumpNonZero: 0. self MoveR: t1 R: t2. self AndCq: objectMemory getMemoryMap getSpaceMaskToUse R: t2. self CmpCq: objectMemory getMemoryMap getPermSpaceMask R: t2. - jump2 := self JumpZero: 0. + jump3 := self JumpZero: 0. self MoveR: t0 R: TempReg. backEnd saveAndRestoreLinkRegAround: [ self CallRT: ceStoreCheckTrampoline ]. currentBlock := self Label. + jump7 jmpTarget: currentBlock. + jump5 jmpTarget: currentBlock. jump6 jmpTarget: currentBlock. + jump8 jmpTarget: currentBlock. jump4 jmpTarget: currentBlock. - jump5 jmpTarget: currentBlock. - jump7 jmpTarget: currentBlock. - jump3 jmpTarget: currentBlock. - jump1 jmpTarget: currentBlock. jump2 jmpTarget: currentBlock. + jump3 jmpTarget: currentBlock. self MoveR: t1 M64: 8 r: t0. + jump3 := self Jump: 0. + currentBlock := self Label. + jump1 jmpTarget: currentBlock. + self deoptimize. + currentBlock := self Label. + jump3 jmpTarget: currentBlock. ^ 0 ] diff --git a/Druid/DRBranchIfCondition.class.st b/Druid/DRBranchIfCondition.class.st index a5f3b03c..10c5772d 100644 --- a/Druid/DRBranchIfCondition.class.st +++ b/Druid/DRBranchIfCondition.class.st @@ -30,7 +30,7 @@ DRBranchIfCondition >> beBackJumpTo: aDRBasicBlock [ { #category : #accessing } DRBranchIfCondition >> beForwardJumpTo: aDRBasicBlock [ - backJumps remove: aDRBasicBlock + backJumps remove: aDRBasicBlock ifAbsent: nil ] { #category : #accessing } diff --git a/Druid/DRBytecodeIRGenerator.class.st b/Druid/DRBytecodeIRGenerator.class.st index 41ee9014..822852a6 100644 --- a/Druid/DRBytecodeIRGenerator.class.st +++ b/Druid/DRBytecodeIRGenerator.class.st @@ -154,10 +154,14 @@ DRBytecodeIRGenerator >> interpretDirectSuperSendWith: aRBMessageNode [ { #category : #'as yet unclassified' } DRBytecodeIRGenerator >> interpretDruidForceIntepretationWith: aRBMessageNode [ - ^ self - addInstructionFrom: aRBMessageNode - instructionKind: DRDeoptimize - operands: #( ) + self + addInstructionFrom: aRBMessageNode + instructionKind: DRDeoptimize + operands: #( ). + + "Cut control flow" + self popOperand. + ^ (RBReturnNode value: (RBLiteralNode value: 0)) acceptVisitor: self ] { #category : #'special-cases' } @@ -512,10 +516,13 @@ DRBytecodeIRGenerator >> visitClassVariableNode: aRBVariableNode [ | value mappings | value := aRBVariableNode variable name. - mappings := { 'FoxIFReceiver' -> 'FrameReceiverOffset' } asDictionary. + mappings := { + ('FoxIFReceiver' -> 'FrameReceiverOffset'). + ('IMMUTABILITY' -> 'true') } asDictionary. value := mappings at: value ifAbsent: [ value ]. ^ self addInstructionFrom: aRBVariableNode instructionKind: DRCopy - operands: { (DRConstantCompileTimeExpression new expression: value) } + operands: + { (DRConstantCompileTimeExpression new expression: value) } ] diff --git a/Druid/DRCPSEdge.class.st b/Druid/DRCPSEdge.class.st index 0fac4fe9..6a7cb169 100644 --- a/Druid/DRCPSEdge.class.st +++ b/Druid/DRCPSEdge.class.st @@ -133,10 +133,7 @@ DRCPSEdge >> operandDomainFromInstruction: aDRInstruction inBranch: branch [ | constraint | constraint := self constraintFor: aDRInstruction result name. ^ constraint - ifNil: [ - self - operandDomainFromInstruction: aDRInstruction operand1 - inBranch: branch ] + ifNil: [ branch condition acceptVisitor: self withBranch: branch ] ifNotNil: [ DRRegisterDomain reg: aDRInstruction constraint: constraint ] ]. @@ -144,7 +141,9 @@ DRCPSEdge >> operandDomainFromInstruction: aDRInstruction inBranch: branch [ ^ self operandDomainFromPhi: aDRInstruction ]. aDRInstruction isSetConditionCode ifTrue: [ - ^ aDRInstruction condition acceptVisitor: self withBranch: aDRInstruction ]. + ^ aDRInstruction condition + acceptVisitor: self + withBranch: aDRInstruction ]. ^ nil ] @@ -322,6 +321,12 @@ DRCPSEdge >> visitCopy: aDRCopy [ ^ self addConstraint: constraint to: aDRCopy result name ] +{ #category : #visiting } +DRCPSEdge >> visitDeoptimize: aDRDeoptimize [ + + ^ nil +] + { #category : #visiting } DRCPSEdge >> visitDivision: aDRDivision [ diff --git a/Druid/DRConstantValue.class.st b/Druid/DRConstantValue.class.st index 036363b5..0b162aff 100644 --- a/Druid/DRConstantValue.class.st +++ b/Druid/DRConstantValue.class.st @@ -32,7 +32,6 @@ DRConstantValue >> acceptVisitor: aVisitor [ { #category : #converting } DRConstantValue >> asJitCompileTimeExpression [ -1haltIf: [ self value asString = 'method' ]. ^ DRConstantCompileTimeExpression expression: self value asString ] diff --git a/Druid/DRControlFlowGraph.class.st b/Druid/DRControlFlowGraph.class.st index 7837d1c5..bd6503fc 100644 --- a/Druid/DRControlFlowGraph.class.st +++ b/Druid/DRControlFlowGraph.class.st @@ -315,19 +315,16 @@ DRControlFlowGraph >> firstBasicBlock [ { #category : #edges } DRControlFlowGraph >> fixBackJumps [ - self blocks do: [ :block | - block successors do: [ :succ | - (block endInstruction isBackJumpTo: succ) ifTrue: [ "If back-jump to block a recursive phi should exist" - (succ endInstruction isBackJump or: [ - (succ phiFunctions anySatisfy: [ :phi | phi hasRecursiveUse ]) - not ]) ifTrue: [ "If not, then is a forward-jump" - block endInstruction beForwardJumpTo: succ ] ] ]. - - block endInstruction isBackJump ifFalse: [ "Check if has a back-jump to this block" - (block phiFunctions anySatisfy: [ :phi | phi hasRecursiveUse ]) - ifTrue: [ - block backJumpPredecessors do: [ :pred | - pred endInstruction beBackJumpTo: block ] ] ] ] + self buildDominatorTree. + self blocks do: [ :block | + | jump | + jump := block endInstruction. + block successors do: [ :succ | + | shouldBeBackjump | + shouldBeBackjump := block isDominatedBy: succ. + shouldBeBackjump + ifTrue: [ jump beBackJumpTo: succ ] + ifFalse: [ jump beForwardJumpTo: succ ] ] ] ] { #category : #edges } diff --git a/Druid/DRFrameReturn.class.st b/Druid/DRFrameReturn.class.st index 2127b5d7..b576f27b 100644 --- a/Druid/DRFrameReturn.class.st +++ b/Druid/DRFrameReturn.class.st @@ -4,8 +4,22 @@ Class { #category : #'Druid-IR' } +{ #category : #testing } +DRFrameReturn >> isCopy [ + + ^ self shouldKeepInCFG not +] + { #category : #testing } DRFrameReturn >> isFrameReturn [ ^ true ] + +{ #category : #SCCP } +DRFrameReturn >> sccpLatticeValueFor: sccp [ + + self shouldKeepInCFG ifTrue: [ ^ sccp bottom ]. + + ^ super sccpLatticeValueFor: sccp +] diff --git a/Druid/DRIRGenerator.class.st b/Druid/DRIRGenerator.class.st index 0cdfd375..eeaed77f 100644 --- a/Druid/DRIRGenerator.class.st +++ b/Druid/DRIRGenerator.class.st @@ -255,7 +255,8 @@ DRIRGenerator >> initializeSpecialCases [ specialCases at: #ifTrue: put: #interpretIfTrueWith:. specialCases at: #whileTrue: put: #interpretWhileTrueWith:. specialCases at: #caseOf:otherwise: put: #interpretCaseOfWith:. - + specialCases at: #cppIf:ifTrue: put: #interpretCppIfWith:. + specialCases at: #= put: #interpretEqualityComparisonWith:. specialCases at: #~= put: #interpretInequalityComparisonWith:. specialCases at: #< put: #interpretLessThanComparisonWith:. @@ -737,6 +738,16 @@ DRIRGenerator >> interpretCondition: aRBMessageNode conditionKind: conditionKind operand2 } ] +{ #category : #interpreting } +DRIRGenerator >> interpretCppIfWith: aRBMessageNode [ + + | jitExpressionCopy | + jitExpressionCopy := self visitOperand: aRBMessageNode arguments first. + jitExpressionCopy simpleConstantFold expression = 'true' ifTrue: [ + (RBMessageNode receiver: aRBMessageNode arguments second selector: #value) + acceptVisitor: self ] +] + { #category : #'special cases' } DRIRGenerator >> interpretDivisionWith: aRBMessageNode [ diff --git a/Druid/DRInstruction.class.st b/Druid/DRInstruction.class.st index 61650413..c240e534 100644 --- a/Druid/DRInstruction.class.st +++ b/Druid/DRInstruction.class.st @@ -645,6 +645,8 @@ DRInstruction >> removeUser: anInstruction [ { #category : #replacing } DRInstruction >> replaceBy: anotherInstruction [ + self = anotherInstruction ifTrue: [ ^ self ]. + basicBlock replace: self by: anotherInstruction. self replaceUsesBy: anotherInstruction. @@ -871,17 +873,3 @@ DRInstruction >> veryDeepCopyWith: deepCopier [ deepCopier references at: origin ifAbsentPut: [nil]. ^ super veryDeepCopyWith: deepCopier ] - -{ #category : #dependencies } -DRInstruction >> withAllDependenciesExcept: alreadyComputedDependencies [ - - | dependencies | - (alreadyComputedDependencies includes: self) - ifTrue: [ ^ alreadyComputedDependencies ]. - - dependencies := OrderedCollection new. - dependencies add: self. - self dependencies do: [ :e | - dependencies addAll: e withAllDependencies ]. - ^ dependencies -] diff --git a/Druid/DRPhiFunction.class.st b/Druid/DRPhiFunction.class.st index 96bbf90e..87eb3d13 100644 --- a/Druid/DRPhiFunction.class.st +++ b/Druid/DRPhiFunction.class.st @@ -45,7 +45,7 @@ DRPhiFunction >> addValue: anInstruction forPredecessor: aDRBasicBlock [ operands addLast: anInstruction ] -{ #category : #accessing } +{ #category : #'loop-invariance' } DRPhiFunction >> canMoveOutsideLoop: backJump [ ^ false @@ -68,7 +68,7 @@ DRPhiFunction >> hasRecursiveUse [ ^ false ] -{ #category : #accessing } +{ #category : #testing } DRPhiFunction >> initialize [ super initialize. @@ -190,7 +190,7 @@ DRPhiFunction >> rtlOperandQualifier [ ^ 'R:' ] -{ #category : #enumerating } +{ #category : #SCCP } DRPhiFunction >> sccpLatticeValueFor: sccp [ ^ sccp latticeValueOfPhiFunction: self @@ -217,11 +217,11 @@ DRPhiFunction >> simpleConstantFold [ ^ super simpleConstantFold ] -{ #category : #simplification } +{ #category : #transforming } DRPhiFunction >> simplify [ - | simplifiedOperands worklist seen | - operands asSet size = 0 ifTrue: [ ^ DRNullValue new ]. + | simplifiedOperands | + operands asSet isEmpty ifTrue: [ ^ DRNullValue new ]. "Use a worklist algorithm to iterate over the phi graph. Ignore Phis and cut if we see a duplicated phi, this may happen in loops" @@ -243,7 +243,7 @@ DRPhiFunction >> supportConstantOperand [ ^ false ] -{ #category : #simplification } +{ #category : #types } DRPhiFunction >> type [ (self operands copyWithout: self) do: [ :o | diff --git a/Druid/DRSCCP.class.st b/Druid/DRSCCP.class.st index f3f47464..6f5edf1a 100644 --- a/Druid/DRSCCP.class.st +++ b/Druid/DRSCCP.class.st @@ -196,12 +196,14 @@ DRSCCP >> latticeValue: aValue [ ^ latticeValues at: aValue ifAbsent: [ self top ] ] -{ #category : #executing } -DRSCCP >> latticeValueOfPhiFunction: operation [ +{ #category : #lattice } +DRSCCP >> latticeValueOfPhiFunction: phiFunction [ | values | + "Recursive phi cannot determine the lattice (it is involved in a loop)" + phiFunction hasRecursiveUse ifTrue: [ ^ self bottom ]. - values := operation operands collect: [ :e | + values := phiFunction operands collect: [ :e | self latticeValue: e ] as: Set. values remove: self top ifAbsent: [ "Nothing" ]. values size = 1 ifTrue: [ ^ values anyOne ]. @@ -335,7 +337,12 @@ DRSCCP >> tryReplaceInstructionByFoldedValue: i [ replacement := lattice result isNoResult ifTrue: [ lattice ] ifFalse: [ - DRCopy operands: { lattice asDRValue } result: i result ]. + i isCopy + ifTrue: [ i "Take care of subclasses!" ] + ifFalse: [ + DRCopy + operands: { lattice asDRValue } + result: i result ] ]. "We tell the lattice values that the new instruction has the same vlue as the old one" latticeValues at: replacement put: (latticeValues at: i). diff --git a/Druid/DRStrongCopy.class.st b/Druid/DRStrongCopy.class.st index f136ffc4..59cc6686 100644 --- a/Druid/DRStrongCopy.class.st +++ b/Druid/DRStrongCopy.class.st @@ -4,26 +4,12 @@ Class { #category : #'Druid-IR' } -{ #category : #testing } -DRStrongCopy >> isCopy [ - - ^ self shouldKeepInCFG not -] - { #category : #testing } DRStrongCopy >> isMandatoryInstruction [ ^ self shouldKeepInCFG ] -{ #category : #SCCP } -DRStrongCopy >> sccpLatticeValueFor: sccp [ - - self shouldKeepInCFG ifTrue: [ ^ sccp bottom ]. - - ^ super sccpLatticeValueFor: sccp -] - { #category : #testing } DRStrongCopy >> shouldKeepInCFG [