From 5c2086f95247a6f51572d71b7c2623bf460287b8 Mon Sep 17 00:00:00 2001 From: Marcus Denker Date: Sat, 13 Jun 2020 09:59:32 +0200 Subject: [PATCH] #isReferenced for TemporaryVariables need to check if the var is really accessed. This implementation does it using the AST: if there are no astNodes for this variables, it is not used. - Implement isReferenced - add test - move implementation isReferenced from Variable to Slo - add isReferenced as subclassResponsability in Variable --- src/Kernel/Slot.class.st | 5 +++++ src/Kernel/TemporaryVariable.class.st | 5 +++++ src/Kernel/Variable.class.st | 3 +-- src/Slot-Core/CompiledMethod.extension.st | 2 +- src/Slot-Tests/TemporaryVariableTest.class.st | 9 +++++++++ 5 files changed, 21 insertions(+), 3 deletions(-) diff --git a/src/Kernel/Slot.class.st b/src/Kernel/Slot.class.st index 87b31602706..66bc58fbba2 100644 --- a/src/Kernel/Slot.class.st +++ b/src/Kernel/Slot.class.st @@ -231,6 +231,11 @@ Slot >> isReadIn: aCompiledCode [ anySatisfy: [ :node | node binding slot == self ] ] +{ #category : #testing } +Slot >> isReferenced [ + ^self usingMethods isNotEmpty +] + { #category : #testing } Slot >> isSelfEvaluating [ ^true diff --git a/src/Kernel/TemporaryVariable.class.st b/src/Kernel/TemporaryVariable.class.st index ef516cc53e7..12d68e60ed5 100644 --- a/src/Kernel/TemporaryVariable.class.st +++ b/src/Kernel/TemporaryVariable.class.st @@ -79,6 +79,11 @@ TemporaryVariable >> isFromBlock [ ^startpc isNotNil ] +{ #category : #testing } +TemporaryVariable >> isReferenced [ + ^self astNodes isNotEmpty +] + { #category : #accessing } TemporaryVariable >> method [ ^ method diff --git a/src/Kernel/Variable.class.st b/src/Kernel/Variable.class.st index 749a50fd268..0258135eeb3 100644 --- a/src/Kernel/Variable.class.st +++ b/src/Kernel/Variable.class.st @@ -66,8 +66,7 @@ Variable >> hash [ { #category : #testing } Variable >> isReferenced [ - "Subclasses can implement optimized version avoiding all methods collections" - ^self usingMethods isNotEmpty + ^ self subclassResponsibility ] { #category : #accessing } diff --git a/src/Slot-Core/CompiledMethod.extension.st b/src/Slot-Core/CompiledMethod.extension.st index f2ca54f6303..9e5d99fa238 100644 --- a/src/Slot-Core/CompiledMethod.extension.st +++ b/src/Slot-Core/CompiledMethod.extension.st @@ -35,6 +35,6 @@ CompiledMethod >> temporaryVariableNamed: aName [ { #category : #'*Slot-Core' } CompiledMethod >> temporaryVariables [ - ^self tempNames collect: [ :name | TemporaryVariable new name: name ] + ^self tempNames collect: [ :name | TemporaryVariable name: name method: self] ] diff --git a/src/Slot-Tests/TemporaryVariableTest.class.st b/src/Slot-Tests/TemporaryVariableTest.class.st index 8207459e5ec..09616c2f523 100644 --- a/src/Slot-Tests/TemporaryVariableTest.class.st +++ b/src/Slot-Tests/TemporaryVariableTest.class.st @@ -21,6 +21,15 @@ TemporaryVariableTest >> testHasTemporaryVariablesMethod [ self assert: (method hasTemporaryVariableNamed: #method) ] +{ #category : #tests } +TemporaryVariableTest >> testIsReferenced [ + | method notReferenced | + "The temp notReferenced is not used as we test exactly that here" + method := self class >> #testIsReferenced. + self assert: method temporaryVariables first isReferenced. + self deny: method temporaryVariables second isReferenced. +] + { #category : #properties } TemporaryVariableTest >> testPropertyAtPut [