Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions src/Kernel-CodeModel/Context.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1244,9 +1244,9 @@ Context >> objectSize: anObject [
{ #category : 'accessing' }
Context >> outerContext [
"Answer the context within which the receiver is nested."

<reflection: 'Stack Manipulation - Context'>
^closureOrNil ifNotNil:
[closureOrNil outerContext ifNil: ["if the outer is nil, this is a CleanBlock" self sender]]
^ closureOrNil ifNotNil: [ closureOrNil outerContext ]
]

{ #category : 'accessing' }
Expand Down
5 changes: 4 additions & 1 deletion src/OpalCompiler-Core/OCAbstractMethodScope.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -143,8 +143,11 @@ OCAbstractMethodScope >> localTemps [
OCAbstractMethodScope >> lookupDefiningContextForVariable: var startingFrom: aContext [
"Is this the definition context for var? If it not, we look in the outer context using the corresponding outer scope. If found, we return the context"

| nextContext |
nextContext := self nextOuterScopeContextOf: aContext.
nextContext ifNil: [ self error: var name, ' optimized out' ].
^self = var scope
ifFalse: [ self outerScope lookupDefiningContextForVariable: var startingFrom: (self nextOuterScopeContextOf: aContext) ]
ifFalse: [ self outerScope lookupDefiningContextForVariable: var startingFrom: nextContext ]
ifTrue: [ aContext ]
]

Expand Down
2 changes: 1 addition & 1 deletion src/OpalCompiler-Core/OCBlockScope.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -41,5 +41,5 @@ OCBlockScope >> nextOuterScopeContextOf: aContext [
"Returns the next context to lookup a variable name from within outer scope.
If it is block context then we return outer context for lookup.
But if it is method context lookup will continue in same context but within outer scope"
^ aContext outerContext ifNil: [ aContext ]
^ aContext outerContext
]
8 changes: 8 additions & 0 deletions src/OpalCompiler-Tests/MethodMapExamples.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,14 @@ MethodMapExamples >> exampleAccessOuterFromCleanBlock [
^[ thisContext tempNamed: 'b' ] value
]

{ #category : 'examples' }
MethodMapExamples >> exampleAccessOuterFromFullBlock [
<compilerOptions: #(- optionCleanBlockClosure)>
| b |
b := 1.
^[ thisContext tempNamed: 'b' ] value
]

{ #category : 'examples' }
MethodMapExamples >> exampleConstantBlock [

Expand Down
11 changes: 10 additions & 1 deletion src/OpalCompiler-Tests/MethodMapTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,16 @@ MethodMapTest >> testDeadContextSourceNode [

{ #category : 'tests - temp access' }
MethodMapTest >> testExampleAccessOuterFromCleanBlock [
self assert: (self compileAndRunExample: #exampleAccessOuterFromCleanBlock) equals: 1
"Should rise an exception since we are trying to access outerContext from a clean block"
self should: [(self compileAndRunExample: #exampleAccessOuterFromCleanBlock)] raise: Exception.

]

{ #category : 'tests - temp access' }
MethodMapTest >> testExampleAccessOuterFromFullBLock [

self assert: (self compileAndRunExample: #exampleAccessOuterFromFullBlock) equals: 1

]

{ #category : 'tests - temp access' }
Expand Down
4 changes: 2 additions & 2 deletions src/OpalCompiler-Tests/OCContextTempMappingTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -33,15 +33,15 @@ OCContextTempMappingTest >> fetchArgFromOptimizedBlockInsideFullBlock: anArg ext

{ #category : 'tests' }
OCContextTempMappingTest >> testAccessingArgOfOuterBlockFromAnotherDeepBlock [

<compilerOptions: #(- optionCleanBlockClosure)>
| actual |

"Check the source code availability to do not fail on images without sources"
thisContext method hasSourceCode ifFalse: [ ^ self skip ].

actual := [:outerArg |
outerArg asString.
[ :innerArg | innerArg asString. thisContext tempNamed: #outerArg ] value: #innerValue.
[ :innerArg | innerArg asString.thisContext tempNamed: #outerArg ] value: #innerValue.
] value: #outerValue.

self assert: actual equals: #outerValue
Expand Down