Skip to content

Commit

Permalink
1. It refactor the semantics analyzer to not rely on #isLocalVariable…
Browse files Browse the repository at this point in the history
… message and use a dispatch to the variable instead: #analyzeRead:by: and analyzeWrite:by:

The changes are based on recently introduced visit~ConcreteTypeOf~Variable: methods in AST visitors.  
Related to this idea several renames are introduced: #analyseEscapingRead: and #analyseEscapingWrite:  are replaced by #analyzeLocalVariableRead: and #analyzeLocalVariableWrite: accordingly
The driver for this refactoring is DoItVariable issue (recently fixed #8774) when it represents the external temp during a compilation. Compiler is trying to call some locals specific code during doIt compilation and it was failing because DoItVariable is not a local for newly compiled doIt methods. The Marcus fix introduced missing methods. But this PR allows to avoid it completely. 
2. It optimizes how variables are represented in doIt expressions. The idea is that only variables which can't be used directly in doIts needs to be converted. And it is only local variables. 
Therefore Variable>>#asDoItVariable will returns self as default behaviour. And local variables will be converted to DoItVariable instances.
  • Loading branch information
dionisiydk committed Apr 20, 2021
1 parent 93d6505 commit 65c21d3
Show file tree
Hide file tree
Showing 7 changed files with 106 additions and 79 deletions.
5 changes: 0 additions & 5 deletions src/Kernel/DoItVariable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -68,11 +68,6 @@ DoItVariable >> actualVariable: aVariable [
name := actualVariable name
]

{ #category : #converting }
DoItVariable >> asDoItVariableFrom: aContext [
^self
]

{ #category : #accessing }
DoItVariable >> doItContext [
^ doItContext
Expand Down
7 changes: 6 additions & 1 deletion src/Kernel/Variable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,12 @@ Variable >> acceptVisitor: aProgramNodeVisitor node: aNode [

{ #category : #converting }
Variable >> asDoItVariableFrom: aContext [
^ DoItVariable fromContext: aContext variable: self
"Specific kind of variables may require special logic to be visible in DoIt expressions.
For example local variables can't be accessed directly in DoIt expressions in the debugger:
- DoIt is executed using new process where there are no temps from the original context.
In such cases subclasses should return adapter variable here to represent receiver in DoIt method.
DoItVariable class is implemented with this purpose (see the class comment and tests)"
^ self
]

{ #category : #queries }
Expand Down
21 changes: 20 additions & 1 deletion src/OpalCompiler-Core/LocalVariable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,25 @@ LocalVariable >> acceptVisitor: aProgramNodeVisitor node: aNode [
^ aProgramNodeVisitor visitLocalVariableNode: aNode
]

{ #category : #'read/write usage' }
LocalVariable >> analyzeRead: aVariableNode by: aSemanticAnalyzer [
super analyzeRead: aVariableNode by: aSemanticAnalyzer.

aSemanticAnalyzer analyzeLocalVariableRead: self
]

{ #category : #'read/write usage' }
LocalVariable >> analyzeWrite: aVariableNode by: aSemanticAnalyzer [
super analyzeWrite: aVariableNode by: aSemanticAnalyzer.

aSemanticAnalyzer analyzeLocalVariableWrite: self
]

{ #category : #converting }
LocalVariable >> asDoItVariableFrom: aContext [
^ DoItVariable fromContext: aContext variable: self
]

{ #category : #converting }
LocalVariable >> asString [

Expand Down Expand Up @@ -201,7 +220,7 @@ LocalVariable >> markEscapingRead [
{ #category : #escaping }
LocalVariable >> markEscapingWrite [
escaping := #escapingWrite.
self isRepeatedWrite ifFalse:[usage := #write]
self isRepeatedWrite ifFalse: [usage := #write]
]

{ #category : #'read/write usage' }
Expand Down
26 changes: 12 additions & 14 deletions src/OpalCompiler-Core/OCASTClosureAnalyzer.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ Class {
OCASTClosureAnalyzer >> lookupAndFixBinding: aVariableNode [
| var |
var := scope lookupVar: aVariableNode name.
aVariableNode binding: var.
aVariableNode variable: var.
^var
]

Expand All @@ -35,6 +35,17 @@ OCASTClosureAnalyzer >> visitBlockNode: aBlockNode [
scope := scope popScope.
]

{ #category : #visiting }
OCASTClosureAnalyzer >> visitLocalVariableNode: aVariableNode [
"re-lookup local variables..."
| var |
var := self lookupAndFixBinding: aVariableNode.
var isTempVectorTemp ifTrue: [ | vectorVar |
vectorVar := scope lookupVar: var vectorName.
scope addCopyingTempToAllScopesUpToDefTemp: vectorVar].
var isCopying ifTrue: [scope addCopyingTempToAllScopesUpToDefTemp: var].
]

{ #category : #visiting }
OCASTClosureAnalyzer >> visitMethodNode: aMethodNode [
"here look at the temps and make copying vars / tempVector out of them"
Expand All @@ -45,16 +56,3 @@ OCASTClosureAnalyzer >> visitMethodNode: aMethodNode [
self visitNode: aMethodNode body.
aMethodNode temporaries do: [ :each | self lookupAndFixBinding: each ]
]

{ #category : #visiting }
OCASTClosureAnalyzer >> visitVariableNode: aVariableNode [
"re-lookup the temorary variables..."

| var |
aVariableNode isLocalVariable ifFalse: [^self].
var := self lookupAndFixBinding: aVariableNode.
var isTempVectorTemp ifTrue: [ | vectorVar |
vectorVar := scope lookupVar: var vectorName.
scope addCopyingTempToAllScopesUpToDefTemp: vectorVar].
var isCopying ifTrue: [scope addCopyingTempToAllScopesUpToDefTemp: var].
]
97 changes: 39 additions & 58 deletions src/OpalCompiler-Core/OCASTSemanticAnalyzer.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -7,44 +7,44 @@ Class {
#superclass : #RBProgramNodeVisitor,
#instVars : [
'scope',
'blockcounter',
'compilationContext'
'compilationContext',
'blockCounter'
],
#category : #'OpalCompiler-Core-Semantics'
}

{ #category : #variables }
OCASTSemanticAnalyzer >> analyseEscapingRead: var [
var markRead.
(var scope outerNotOptimizedScope ~= scope outerNotOptimizedScope ) ifFalse: [ ^self ].
{ #category : #api }
OCASTSemanticAnalyzer >> analyze: aNode [
self visitNode: aNode.
OCASTClosureAnalyzer new visitNode: aNode.
OCASTMethodMetadataAnalyser new visitNode: aNode
]

{ #category : #visiting }
OCASTSemanticAnalyzer >> analyzeLocalVariableRead: aLocalVariable [
aLocalVariable markRead.
(aLocalVariable scope outerNotOptimizedScope ~= scope outerNotOptimizedScope ) ifFalse: [ ^self ].
"only escaping when they will end up in different closures"
var markEscapingRead.
aLocalVariable markEscapingRead.
"if we read a variable in a loop that is a repeated write, it need to be marked as escaping write"
(scope isInsideOptimizedLoop and: [var isRepeatedWrite])
ifTrue: [var markEscapingWrite]
(scope isInsideOptimizedLoop and: [aLocalVariable isRepeatedWrite])
ifTrue: [aLocalVariable markEscapingWrite]
]

{ #category : #variables }
OCASTSemanticAnalyzer >> analyseEscapingWrite: var [
(var scope outerNotOptimizedScope ~= scope outerNotOptimizedScope)
{ #category : #visiting }
OCASTSemanticAnalyzer >> analyzeLocalVariableWrite: aLocalVariable [
(aLocalVariable scope outerNotOptimizedScope ~= scope outerNotOptimizedScope)
"only escaping when they will end up in different closures"
ifTrue: [ var markEscapingWrite].
ifTrue: [ aLocalVariable markEscapingWrite].
"if we write a variable in a loop, mark it as a repeated Write"
scope isInsideOptimizedLoop
ifTrue: [ var markRepeatedWrite ]
ifFalse: [ var markWrite ]
]

{ #category : #api }
OCASTSemanticAnalyzer >> analyze: aNode [
self visitNode: aNode.
OCASTClosureAnalyzer new visitNode: aNode.
OCASTMethodMetadataAnalyser new visitNode: aNode
ifTrue: [ aLocalVariable markRepeatedWrite ]
ifFalse: [ aLocalVariable markWrite ]
]

{ #category : #accessing }
OCASTSemanticAnalyzer >> blockcounter [
^blockcounter ifNil: [0]
OCASTSemanticAnalyzer >> blockCounter [
^blockCounter ifNil: [0]
]

{ #category : #accessing }
Expand Down Expand Up @@ -82,28 +82,11 @@ OCASTSemanticAnalyzer >> declareVariableNode: aVariableNode as: anOCTempVariable
]

{ #category : #variables }
OCASTSemanticAnalyzer >> lookupVariableForRead: aVariableNode [

| var |

var := scope lookupVar: aVariableNode name.

var ifNil: [^var].
var isLocalVariable ifTrue: [ self analyseEscapingRead: var].
^var
]

{ #category : #variables }
OCASTSemanticAnalyzer >> lookupVariableForWrite: aVariableNode [

| var |

var := scope lookupVar: aVariableNode name.

var ifNil: [^var].
var isReservedVariable ifTrue: [ self storeIntoReservedVariable: aVariableNode ].
var isWritable ifFalse: [ self storeIntoReadOnlyVariable: aVariableNode ].
var isLocalVariable ifTrue: [ self analyseEscapingWrite: var ].
OCASTSemanticAnalyzer >> resolveVariableNode: aVariableNode [
| var |
var := (scope lookupVar: aVariableNode name)
ifNil: [ self undeclaredVariable: aVariableNode ].
aVariableNode variable: var.
^var
]

Expand Down Expand Up @@ -167,18 +150,18 @@ OCASTSemanticAnalyzer >> variable: variableNode shadows: semVar [
{ #category : #visiting }
OCASTSemanticAnalyzer >> visitAssignmentNode: anAssignmentNode [
| var |
self visitNode: anAssignmentNode value.
var := (self lookupVariableForWrite: anAssignmentNode variable)
ifNil: [ self undeclaredVariable: anAssignmentNode variable ].
anAssignmentNode variable binding: var
self visitNode: anAssignmentNode value.
var := self resolveVariableNode: anAssignmentNode variable.
var analyzeWrite: anAssignmentNode variable by: self
]

{ #category : #visiting }
OCASTSemanticAnalyzer >> visitBlockNode: aBlockNode [
blockcounter := self blockcounter + 1.
blockCounter := self blockCounter + 1.

aBlockNode isInlined ifTrue: [^ self visitInlinedBlockNode: aBlockNode ].
scope := scope newBlockScope: blockcounter.
scope := scope newBlockScope: blockCounter.
aBlockNode scope: scope. scope node: aBlockNode.

aBlockNode arguments do: [:node | self declareArgumentNode: node ].
Expand All @@ -189,7 +172,7 @@ OCASTSemanticAnalyzer >> visitBlockNode: aBlockNode [
{ #category : #visiting }
OCASTSemanticAnalyzer >> visitInlinedBlockNode: aBlockNode [

scope := scope newOptimizedBlockScope: blockcounter.
scope := scope newOptimizedBlockScope: blockCounter.
aBlockNode isInlinedLoop ifTrue: [scope markInlinedLoop].
aBlockNode scope: scope. scope node: aBlockNode.
aBlockNode arguments do: [:node | self declareArgumentNode: node ].
Expand Down Expand Up @@ -236,9 +219,7 @@ OCASTSemanticAnalyzer >> visitSequenceNode: aSequenceNode [

{ #category : #visiting }
OCASTSemanticAnalyzer >> visitVariableNode: aVariableNode [
| var |
var := (self lookupVariableForRead: aVariableNode)
ifNil: [(self undeclaredVariable: aVariableNode)].
aVariableNode binding: var.
var isUninitialized ifTrue: [self uninitializedVariable: aVariableNode].
| var |
var := self resolveVariableNode: aVariableNode.
var analyzeRead: aVariableNode by: self
]
15 changes: 15 additions & 0 deletions src/OpalCompiler-Core/Variable.extension.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Extension { #name : #Variable }

{ #category : #'*OpalCompiler-Core' }
Variable >> analyzeRead: aVariableNode by: aSemanticAnalyzer [

self isUninitialized ifTrue: [ aSemanticAnalyzer uninitializedVariable: aVariableNode ]
]

{ #category : #'*OpalCompiler-Core' }
Variable >> analyzeWrite: aVariableNode by: aSemanticAnalyzer [

self isReservedVariable ifTrue: [ aSemanticAnalyzer storeIntoReservedVariable: aVariableNode ].

self isWritable ifFalse: [ aSemanticAnalyzer storeIntoReadOnlyVariable: aVariableNode ]
]
14 changes: 14 additions & 0 deletions src/Slot-Tests/DoItVariableTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,20 @@ DoItVariableTest >> testCreationFromAnotherVariable [
self assert: var actualVariable identicalTo: targetTemp
]

{ #category : #tests }
DoItVariableTest >> testDoItCompilation [
| temp var doIt |
temp := 100.
var := DoItVariable named: #temp fromContext: thisContext.
doIt := thisContext class compiler
source: 'temp + 2';
context: thisContext;
noPattern: true;
bindings: { var };
compile.
self assert: (doIt valueWithReceiver: self arguments: {thisContext}) equals: 102
]

{ #category : #tests }
DoItVariableTest >> testFromInstVarVariable [

Expand Down

0 comments on commit 65c21d3

Please sign in to comment.