Skip to content

Commit

Permalink
Merge pull request #1200 from MarcusDenker/21709-add-compiler-option-…
Browse files Browse the repository at this point in the history
…embedded-source

21709-add-compiler-option-embedded-source
  • Loading branch information
MarcusDenker committed Apr 16, 2018
2 parents 9f33329 + fb104e1 commit 244850d
Show file tree
Hide file tree
Showing 3 changed files with 48 additions and 10 deletions.
18 changes: 18 additions & 0 deletions src/OpalCompiler-Core/CompilationContext.class.st
Expand Up @@ -125,6 +125,16 @@ CompilationContext class >> initialize [
BytecodeBackend := EncoderForV3PlusClosures.
]

{ #category : #'options - settings API' }
CompilationContext class >> optionEmbeddSources [
^ self readDefaultOption: #optionEmbeddSources
]

{ #category : #'options - settings API' }
CompilationContext class >> optionEmbeddSources: aBoolean [
^ self writeDefaultOption: #optionEmbeddSources value: aBoolean
]

{ #category : #'options - settings API' }
CompilationContext class >> optionFullBlockClosure [
^ self readDefaultOption: #optionFullBlockClosure
Expand Down Expand Up @@ -286,6 +296,8 @@ CompilationContext class >> optionsDescription [
(- optionInlineRepeat 'Inline repeat if specific conditions are met (See isInlineRepeat)')
(- optionInlineNone 'To turn off all inlining options. Overrides the others')
(- optionEmbeddSources 'Embedd sources into CompiledMethod instead of storing in .changes')
(- optionReadOnlyLiterals 'Compiler sets literals as read-only')
(- optionFullBlockClosure 'Compiler compiles closure creation to use FullBlockClosure instead of BlockClosure')
(- optionLongIvarAccessBytecodes 'Specific inst var accesses to Maybe context objects')
Expand Down Expand Up @@ -461,6 +473,12 @@ CompilationContext >> noPattern: anObject [
noPattern := anObject
]
{ #category : #options }
CompilationContext >> optionEmbeddSources [
^ options includes: #optionEmbeddSources
]
{ #category : #options }
CompilationContext >> optionFullBlockClosure [
^ options includes: #optionFullBlockClosure
Expand Down
5 changes: 4 additions & 1 deletion src/OpalCompiler-Core/OpalCompiler.class.st
Expand Up @@ -198,7 +198,10 @@ OpalCompiler >> compile [
self source: notification newSourceCode.
notification retry.
].
cm := ast generate: self compilationContext compiledMethodTrailer
cm := compilationContext optionEmbeddSources
ifTrue: [ ast generateWithSource ]
ifFalse: [ast generate: self compilationContext compiledMethodTrailer ]

] on: SyntaxErrorNotification
do: [ :exception |
self compilationContext requestor
Expand Down
35 changes: 26 additions & 9 deletions src/OpalCompiler-Tests/OpalCompilerTests.class.st
Expand Up @@ -8,28 +8,45 @@ Class {
OpalCompilerTests >> testBindingsWithUppercaseNameDoNotOverwriteGlobals [
| result |
result := Smalltalk compiler
bindings: { #UndefinedObject -> Object } asDictionary;
bindings: {(#UndefinedObject -> Object)} asDictionary;
evaluate: 'UndefinedObject class'.

self assert: result = UndefinedObject class.
self assert: result equals: UndefinedObject class
]

{ #category : #tests }
OpalCompilerTests >> testCompileEmbeddsSource [
| result |
result := Smalltalk compiler
class: UndefinedObject;
options: #( + #optionEmbeddSources );
compile: 'tt ^3+4'.
self assert: (result valueWithReceiver: nil arguments: #()) equals: 7.
self deny: result trailer hasSourcePointer. "no sourcePointer"
self assert: result trailer hasSource. "but source embedded"

result := Smalltalk compiler
class: UndefinedObject;
options: #( - #optionEmbeddSources );
compile: 'tt ^3+4'.
self assert: (result valueWithReceiver: nil arguments: #()) equals: 7.
self deny: result trailer hasSourcePointer. "no sourcePointer"
self deny: result trailer hasSource. "and source embedded"
]

{ #category : #tests }
OpalCompilerTests >> testEvaluateWithBindings [
| result |
result := Smalltalk compiler
bindings: { #a -> 3 } asDictionary;
bindings: {(#a -> 3)} asDictionary;
evaluate: '1+a'.

self assert: result = 4.
self assert: result equals: 4
]

{ #category : #tests }
OpalCompilerTests >> testEvaluateWithBindingsWithUppercaseName [
| result |
result := Smalltalk compiler
bindings: { #MyVar -> 3 } asDictionary;
bindings: {(#MyVar -> 3)} asDictionary;
evaluate: '1+MyVar'.

self assert: result = 4.
self assert: result equals: 4
]

0 comments on commit 244850d

Please sign in to comment.