Skip to content

Commit

Permalink
Copied temps are copied from the defining context into all the contexts.
Browse files Browse the repository at this point in the history
If we now change the var in the debugger, it calls #tempNamed:put: on the context.

-> make sure to walk up the context to the definition context of the temp and set the value in the copy

fixes #4782
  • Loading branch information
MarcusDenker committed Oct 1, 2019
1 parent 88b9405 commit 4c5dee5
Show file tree
Hide file tree
Showing 4 changed files with 33 additions and 3 deletions.
15 changes: 15 additions & 0 deletions src/OpalCompiler-Core/OCAbstractMethodScope.class.st
Expand Up @@ -263,6 +263,21 @@ OCAbstractMethodScope >> removeTemp: tempVar [
tempVars removeKey: tempVar name
]

{ #category : #'temp vars - copying' }
OCAbstractMethodScope >> setCopyingTempToAllScopesUpToDefTemp: aVar to: aValue from: aContext [
| copiedVar |
"we need to update all the copies if we change the value of a copied temp"

self = aVar scope
ifTrue: [ ^ self ].
copiedVar := self lookupVar: aVar name.
aContext tempAt: copiedVar indexFromIR put: aValue.
self outerScope
setCopyingTempToAllScopesUpToDefTemp: aVar
to: aValue
from: (self nextOuterScopeContextOf: aContext)
]

{ #category : #'temp vars' }
OCAbstractMethodScope >> tempVarNames [

Expand Down
6 changes: 3 additions & 3 deletions src/OpalCompiler-Core/OCCopyingTempVariable.class.st
Expand Up @@ -54,10 +54,10 @@ OCCopyingTempVariable >> writeFromContext: aContext scope: contextScope value: a

| definitionContext |
definitionContext := contextScope lookupDefiningContextForVariable: self startingFrom: aContext.
originalVar writeFromContext: aContext scope: contextScope value: aValue.

self flag: #FIXME.
"we need to change all the copies, too"
contextScope setCopyingTempToAllScopesUpToDefTemp: originalVar to: aValue from: aContext.
"and the original temp"
originalVar writeFromContext: aContext scope: contextScope value: aValue.

^definitionContext
tempAt: self indexFromIR
Expand Down
8 changes: 8 additions & 0 deletions src/OpalCompiler-Tests/MethodMapExamples.class.st
Expand Up @@ -55,6 +55,14 @@ MethodMapExamples >> exampleTempNamedPutCopying2 [
a := b .thisContext tempNamed: 'b' put: 2. thisContext outerContext tempNamed: 'b' ] value
]

{ #category : #examples }
MethodMapExamples >> exampleTempNamedPutCopying3 [
| b |
b := 1.
^[[ | a |
a := b .thisContext tempNamed: 'b' put: 2. thisContext outerContext tempNamed: 'b' ] value ] value
]

{ #category : #examples }
MethodMapExamples >> exampleTempNamedPutTempVector [
| b |
Expand Down
7 changes: 7 additions & 0 deletions src/OpalCompiler-Tests/MethodMapTest.class.st
Expand Up @@ -127,6 +127,13 @@ MethodMapTest >> testExampleTempNamedPutCopying2 [
self assert: (self compileAndRunExample: #exampleTempNamedPutCopying2) equals: 2
]

{ #category : #'testing - temp access' }
MethodMapTest >> testExampleTempNamedPutCopying3 [
"modifying a copied temp variable will modify the value in the outer context"

self assert: (self compileAndRunExample: #exampleTempNamedPutCopying3) equals: 2
]

{ #category : #'testing - temp access' }
MethodMapTest >> testExampleTempNamedPutTempVector [
self assert: (self compileAndRunExample: #exampleTempNamedPutTempVector) equals: 3.
Expand Down

0 comments on commit 4c5dee5

Please sign in to comment.