12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028 |
- Smalltalk createPackage: 'Compiler-Tests'!
- TestCase subclass: #ASTMethodRunningTest
- slots: {#receiver}
- package: 'Compiler-Tests'!
- !ASTMethodRunningTest methodsFor: 'accessing'!
- receiver
- ^ receiver
- ! !
- !ASTMethodRunningTest methodsFor: 'initialization'!
- setUp
- receiver := DoIt new
- ! !
- !ASTMethodRunningTest methodsFor: 'testing'!
- should: aString class: aClass receiver: anObject return: aResult
- receiver := anObject.
- self while: aString inClass: aClass should: [ :runBlock |
- self assert: runBlock value equals: aResult ]
- !
- should: aString receiver: anObject raise: anErrorClass
- receiver := anObject.
- self while: aString should: [ :runBlock |
- self should: runBlock raise: anErrorClass ]
- !
- should: aString receiver: anObject return: aResult
- receiver := anObject.
- self should: aString return: aResult
- !
- should: aString return: anObject
- self while: aString should: [ :runBlock |
- self assert: runBlock value equals: anObject ]
- ! !
- ASTMethodRunningTest subclass: #AbstractCompilerTest
- slots: {}
- package: 'Compiler-Tests'!
- !AbstractCompilerTest methodsFor: 'tests'!
- testAfterInliningNonLocalBlockReturnIndexSend
- self should: 'foo [ ^ true ifTrue: [ self class ] ] value. self class' return: DoIt.
- !
- testAfterInliningNonLocalBlockReturnSuperSend
- self should: 'foo [ ^ true ifTrue: [ super class ] ] value' return: DoIt.
- !
- testAssignment
- self should: 'foo | a | a := true ifTrue: [ 1 ]. ^ a' return: 1.
- self should: 'foo | a | a := false ifTrue: [ 1 ]. ^ a' return: nil.
- self should: 'foo | a | ^ a := true ifTrue: [ 1 ]' return: 1
- !
- testBackslashSelectors
-
- self should: '\ arg ^ 4' return: 4.
- self should: '\\ arg ^ 42' return: 42
- !
- testBlockReturn
- self should: 'foo ^ #(1 2 3) collect: [ :each | true ifTrue: [ each + 1 ] ]' return: #(2 3 4).
- self should: 'foo ^ #(1 2 3) collect: [ :each | false ifFalse: [ each + 1 ] ]' return: #(2 3 4).
- self should: 'foo ^ #(1 2 3) collect: [ :each | each odd ifTrue: [ each + 1 ] ifFalse: [ each - 1 ] ]' return: #(2 1 4).
- !
- testCascades
-
- self should: 'foo ^ Array new add: 3; add: 4; yourself' return: #(3 4)
- !
- testCascadesInDynamicArray
- self should: 'foo | x | x := 1. ^ {x. [x:=2] value; in: [x]}' return: #(1 2)
- !
- testCascadesInDynamicDictioary
- self should: 'foo | x | x := 1. ^ #{''one'' -> x. ''two'' -> ([x:=2] value; in: [x])}' return: #{'one' -> 1. 'two' -> 2}
- !
- testCascadesInSend
- self should: 'foo | x | x := 1. ^ Array with: x with: ([x:=2] value; in: [x])' return: #(1 2)
- !
- testCascadesWithInlining
-
- self should: 'foo ^ true class; ifTrue: [ 1 ] ifFalse: [ 2 ]' return: 1.
- self should: 'foo ^ false class; ifTrue: [ 1 ] ifFalse: [ 2 ]' return: 2
- !
- testDynamicArrayElementsOrdered
- self should: 'foo
- | x |
- x := 1.
- ^ { x. x := 2 }
- ' return: #(1 2).
- self should: 'foo
- | x |
- x := 1.
- ^ { x. true ifTrue: [ x := 2 ] }
- ' return: #(1 2).
- !
- testDynamicDictionaryElementsOrdered
- self should: 'foo
- | x |
- x := ''foo''.
- ^ #{ x->1. ''bar''->(true ifTrue: [ 2 ]) }
- ' return: #{'foo'->1. 'bar'->2}.
- !
- testDynamicDictionaryWithMoreArrows
- self should: 'foo ^ #{1->2->3}' return: (HashedCollection with: 1->2->3)
- !
- testGlobalVar
- self should: 'foo ^ eval class' return: BlockClosure.
- self should: 'foo ^ Math cos: 0' return: 1.
- self should: 'foo ^ NonExistingVar' return: nil
- !
- testInnerTemporalDependentElementsOrdered
- self should: 'foo
- | x |
- x := Array.
- ^ x with: ''foo''->x with: ''bar''->(x := 2)
- ' return: {'foo'->Array. 'bar'->2}.
- self should: 'foo
- | x |
- x := Array.
- ^ x with: ''foo''->x with: ''bar''->(true ifTrue: [ x := 2 ])
- ' return: {'foo'->Array. 'bar'->2}.
- self should: 'foo
- | x |
- x := 1.
- ^ Array with: ''foo''->x with: ''bar''->(true ifTrue: [ x := 2 ])
- ' return: {'foo'->1. 'bar'->2}.
- self should: 'foo
- | x |
- x := 1.
- ^ { ''foo''->x. ''bar''->(true ifTrue: [ x := 2 ]) }
- ' return: {'foo'->1. 'bar'->2}.
- self should: 'foo
- | x |
- x := 1.
- ^ #{ ''foo''->x. ''bar''->(true ifTrue: [ x := 2 ]) }
- ' return: #{'foo'->1. 'bar'->2}.
- !
- testLexicalScope
- self should: 'foo | a | a := 1. [ a := 2 ] value. ^ a' return: 2
- !
- testLiterals
- self should: 'foo ^ 1' return: 1.
- self should: 'foo ^ ''hello''' return: 'hello'.
- self should: 'foo ^ #(1 2 3 4)' return: #(1 2 3 4).
- self should: 'foo ^ {1. [:x | x ] value: 2. 3. [4] value}' return: #(1 2 3 4).
- self should: 'foo ^ true' return: true.
- self should: 'foo ^ false' return: false.
- self should: 'foo ^ #{1->2. 3->4}' return: #{1->2. 3->4}.
- self should: 'foo ^ #hello' return: #hello.
- self should: 'foo ^ $h' return: 'h'.
- self should: 'foo ^ -123.456' return: -123.456.
- self should: 'foo ^ -2.5e4' return: -25000.
- !
- testLocalReturn
- self should: 'foo ^ 1' return: 1.
- self should: 'foo ^ 1 + 1' return: 2.
- self should: 'foo ' return: receiver.
- self should: 'foo self asString' return: receiver.
- self should: 'foo | a b | a := 1. b := 2. ^ a + b' return: 3
- !
- testMessageSends
- self should: 'foo ^ 1 asString' return: '1'.
- self should: 'foo ^ 1 + 1' return: 2.
- self should: 'foo ^ 1 + 2 * 3' return: 9.
- self should: 'foo ^ 1 to: 3' return: #(1 2 3).
- self should: 'foo ^ 1 to: 5 by: 2' return: #(1 3 5)
- !
- testMultipleSequences
- self should: 'foo | a b c | a := 2. b := 3. c := a + b. ^ c * 6' return: 30
- !
- testMutableLiterals
- "Mutable literals must be aliased in cascades.
- See https://lolg.it/amber/amber/issues/428"
-
- self
- should: 'foo ^ #( 1 2 ) at: 1 put: 3; yourself'
- return: #(3 2)
- !
- testNestedIfTrue
- self should: 'foo ^ true ifTrue: [ false ifFalse: [ 1 ] ]' return: 1.
- self should: 'foo ^ true ifTrue: [ false ifTrue: [ 1 ] ]' return: nil.
- self should: 'foo true ifTrue: [ false ifFalse: [ ^ 1 ] ]' return: 1.
- self should: 'foo true ifTrue: [ false ifTrue: [ ^ 1 ] ]' return: receiver.
- !
- testNestedSends
- self should: 'foo ^ (Point x: (Point x: 2 y: 3) y: 4) asString' return: (Point x: (2@3) y: 4) asString
- !
- testNilPerform
- self should: 'foo ^ nil perform: #yourself' return: nil
- !
- testNonLocalReturn
- self should: 'foo [ ^ 1 ] value' return: 1.
- self should: 'foo [ ^ 1 + 1 ] value' return: 2.
- self should: 'foo | a b | a := 1. b := 2. [ ^ a + b ] value. self halt' return: 3.
- self should: 'foo [ :x | ^ x + x ] value: 4. ^ 2' return: 8
- !
- testPascalCaseGlobal
- self should: 'foo ^Object' return: (Smalltalk globals at: 'Object').
- self should: 'foo ^NonExistent' return: nil
- !
- testPragmaJSStatement
- self should: 'foo < inlineJS: ''return 2+3'' >' return: 5
- !
- testReceiverEvaluatedOnceInSpecials
- self should: 'foo |x| x := 1. ^ {[ x := x+1 ] value ifNil: []. x}' return: {2. 2}.
- self should: 'foo |xs| xs := {nil. nil}. ^ {[ xs removeLast ] value ifNotNil: []. xs}' return: {nil. {nil}}.
- !
- testRegression1242
- self should: '
- foo
- |x|
- x := 2.
- x := nil ifNil: [].
- ^ x
- ' return: nil.
-
- self should: '
- foo
- |x|
- x := 2.
- x := 1 ifNotNil: [].
- ^ x
- ' return: nil.
-
- self should: '
- foo
- |x|
- x := 2.
- x := false ifFalse: [].
- ^ x
- ' return: nil.
-
- self should: '
- foo
- |x|
- x := 2.
- x := true ifTrue: [].
- ^ x
- ' return: nil.
- !
- testRegression1242ForReturn
- self should: 'foo [ ^ nil ifNil: [] ] value' return: nil.
- self should: 'foo [ ^ 1 ifNotNil: [] ] value' return: nil.
- self should: 'foo [ ^ false ifFalse: [] ] value' return: nil.
- self should: 'foo [ ^ true ifTrue: [] ] value' return: nil.
- !
- testRegression1244
- self should: 'foo [ ^ true ifTrue: [1] ifFalse: [2] ] value' return: 1
- !
- testRootSuperSend
- self
- should: 'foo ^ super class'
- receiver: ProtoObject new
- raise: MessageNotUnderstood
- !
- testSendReceiverAndArgumentsOrdered
- self should: 'foo
- | x |
- x := 1.
- ^ Array with: x with: (true ifTrue: [ x := 2 ])
- ' return: #(1 2).
- self should: 'foo
- | x |
- x := Array.
- ^ x with: x with: (true ifTrue: [ x := 2 ])
- ' return: {Array. 2}.
- !
- testSuperSend
- self
- should: 'foo ^ super isBoolean'
- receiver: true
- return: false
- !
- testSuperSend2
- self
- should: 'foo ^ super isNil'
- receiver: nil
- return: false
- !
- testSuperSend3
- self
- should: 'doo ^ super isNil'
- class: Object
- receiver: nil
- return: false
- !
- testSuperSend4
- self
- should: 'foo ^ super asJavaScriptObject'
- receiver: 'me'
- return: #('m' 'e')
- !
- testSuperSend5
- self
- should: 'foo [super addLast: 4] on: Error do: [ self add: 5 ]. ^ self'
- class: SequenceableCollection
- receiver: #(1 2 3)
- return: #(1 2 3 5)
- !
- testSuperSend6
- self
- should: 'foo ^ super ifTrue: [ true ] ifFalse: [ false ]'
- receiver: true
- raise: Error
- !
- testTempVariables
- self should: 'foo | a | ^ a' return: nil.
- self should: 'foo | AVariable | ^ AVariable' return: nil.
- self should: 'foo | a b c | ^ c' return: nil.
- self should: 'foo | a | [ | d | ^ d ] value' return: nil.
-
- self should: 'foo | a | a:= 1. ^ a' return: 1.
- self should: 'foo | AVariable | AVariable := 1. ^ AVariable' return: 1.
- !
- testThisContext
- self should: 'foo ^ [ thisContext ] value outerContext == thisContext' return: true
- !
- testUnknownPragma
- self should: 'foo < fooBar: ''return 2+3'' > | x | ^ x := 6' return: 6.
- self should: 'foo | x | < fooBar: ''return 2+3'' > ^ x := 6' return: 6
- !
- testifFalse
- self should: 'foo true ifFalse: [ ^ 1 ]' return: receiver.
- self should: 'foo false ifFalse: [ ^ 2 ]' return: 2.
-
- self should: 'foo ^ true ifFalse: [ 1 ]' return: nil.
- self should: 'foo ^ false ifFalse: [ 2 ]' return: 2.
- !
- testifFalseIfTrue
- self should: 'foo true ifFalse: [ ^ 1 ] ifTrue: [ ^ 2 ]' return: 2.
- self should: 'foo false ifFalse: [ ^ 2 ] ifTrue: [ ^1 ]' return: 2.
-
- self should: 'foo ^ true ifFalse: [ 1 ] ifTrue: [ 2 ]' return: 2.
- self should: 'foo ^ false ifFalse: [ 2 ] ifTrue: [ 1 ]' return: 2.
- !
- testifNil
- self should: 'foo ^ 1 ifNil: [ 2 ]' return: 1.
- self should: 'foo ^ nil ifNil: [ 2 ]' return: 2.
- self should: 'foo 1 ifNil: [ ^ 2 ]' return: receiver.
- self should: 'foo nil ifNil: [ ^ 2 ]' return: 2.
- !
- testifNilIfNotNil
- self should: 'foo ^ 1 ifNil: [ 2 ] ifNotNil: [ 3 ]' return: 3.
- self should: 'foo ^ nil ifNil: [ 2 ] ifNotNil: [ 3 ]' return: 2.
- self should: 'foo 1 ifNil: [ ^ 2 ] ifNotNil: [ ^3 ]' return: 3.
- self should: 'foo nil ifNil: [ ^ 2 ] ifNotNil: [ ^3 ]' return: 2.
- !
- testifNotNil
- self should: 'foo ^ 1 ifNotNil: [ 2 ]' return: 2.
- self should: 'foo ^ nil ifNotNil: [ 2 ]' return: nil.
- self should: 'foo 1 ifNotNil: [ ^ 2 ]' return: 2.
- self should: 'foo nil ifNotNil: [ ^ 2 ]' return: receiver.
- !
- testifNotNilWithArgument
- self should: 'foo ^ 1 ifNotNil: [ :val | val + 2 ]' return: 3.
- self should: 'foo ^ nil ifNotNil: [ :val | val + 2 ]' return: nil.
-
- self should: 'foo ^ 1 ifNil: [ 5 ] ifNotNil: [ :val | val + 2 ]' return: 3.
- self should: 'foo ^ nil ifNil: [ 5 ] ifNotNil: [ :val | val + 2 ]' return: 5.
-
- self should: 'foo ^ 1 ifNotNil: [ :val | val + 2 ] ifNil: [ 5 ]' return: 3.
- self should: 'foo ^ nil ifNotNil: [ :val | val + 2 ] ifNil: [ 5 ]' return: 5
- !
- testifTrue
- self should: 'foo false ifTrue: [ ^ 1 ]' return: receiver.
- self should: 'foo true ifTrue: [ ^ 2 ]' return: 2.
-
- self should: 'foo ^ false ifTrue: [ 1 ]' return: nil.
- self should: 'foo ^ true ifTrue: [ 2 ]' return: 2.
- !
- testifTrueIfFalse
- self should: 'foo false ifTrue: [ ^ 1 ] ifFalse: [ ^2 ]' return: 2.
- self should: 'foo true ifTrue: [ ^ 1 ] ifFalse: [ ^ 2 ]' return: 1.
-
- self should: 'foo ^ false ifTrue: [ 2 ] ifFalse: [ 1 ]' return: 1.
- self should: 'foo ^ true ifTrue: [ 2 ] ifFalse: [ 1 ]' return: 2.
- ! !
- !AbstractCompilerTest class methodsFor: 'testing'!
- isAbstract
- ^ self name = AbstractCompilerTest name
- ! !
- AbstractCompilerTest subclass: #ASTDebuggerTest
- slots: {}
- package: 'Compiler-Tests'!
- AbstractCompilerTest subclass: #ASTInterpreterTest
- slots: {}
- package: 'Compiler-Tests'!
- AbstractCompilerTest subclass: #CodeGeneratorTest
- slots: {}
- package: 'Compiler-Tests'!
- AbstractCompilerTest subclass: #InliningCodeGeneratorTest
- slots: {}
- package: 'Compiler-Tests'!
- TestCase subclass: #ASTPCNodeVisitorTest
- slots: {}
- package: 'Compiler-Tests'!
- !ASTPCNodeVisitorTest methodsFor: 'factory'!
- astPCNodeVisitor
- ^ ASTPCNodeVisitor new
- index: 0;
- yourself
- !
- astPCNodeVisitorForSelector: aString
- ^ ASTPCNodeVisitor new
- selector: aString;
- index: 0;
- yourself
- !
- newTeachableVisitor
- | result |
- result := Teachable new
- whenSend: #visit: evaluate: [ :one | one acceptDagVisitor: result ];
- acceptSend: #visitDagNode:.
- ^ result
- ! !
- !ASTPCNodeVisitorTest methodsFor: 'tests'!
- testJSStatementNode
- | ast result |
-
- ast := self parse: 'foo <inlineJS: ''consolee.log(1)''>' forClass: Object.
- result := self astPCNodeVisitor visit: ast; currentNode.
- self
- assert: ((self newTeachableVisitor whenSend: #visitJSStatementNode: return: 'JS'; yourself) visit: result)
- equals: 'JS'
- !
- testMessageSend
- | ast |
-
- ast := self parse: 'foo self asString yourself. ^ self asBoolean' forClass: Object.
- self assert: ((self astPCNodeVisitorForSelector: 'yourself')
- visit: ast;
- currentNode) selector equals: 'yourself'
- !
- testMessageSendWithBlocks
- | ast |
-
- ast := self parse: 'foo true ifTrue: [ [ self asString yourself ] value. ]. ^ self asBoolean' forClass: Object.
- self assert: ((self astPCNodeVisitorForSelector: 'yourself')
- visit: ast;
- currentNode) selector equals: 'yourself'
- !
- testMessageSendWithInlining
- | ast |
-
- ast := self parse: 'foo true ifTrue: [ self asString yourself ]. ^ self asBoolean' forClass: Object.
- self assert: ((self astPCNodeVisitorForSelector: 'yourself')
- visit: ast;
- currentNode) selector equals: 'yourself'.
-
- ast := self parse: 'foo true ifTrue: [ self asString yourself ]. ^ self asBoolean' forClass: Object.
- self assert: ((self astPCNodeVisitorForSelector: 'asBoolean')
- visit: ast;
- currentNode) selector equals: 'asBoolean'
- !
- testNoMessageSend
- | ast |
-
- ast := self parse: 'foo ^ self' forClass: Object.
- self assert: (self astPCNodeVisitor
- visit: ast;
- currentNode) isNil
- ! !
- TestCase subclass: #ASTPositionTest
- slots: {}
- package: 'Compiler-Tests'!
- !ASTPositionTest methodsFor: 'tests'!
- testNodeAtPosition
- | node |
-
- node := self parse: 'yourself
- ^ self' forClass: Object.
-
- self assert: (node navigationNodeAt: 2@4 ifAbsent: [ nil ]) source equals: 'self'.
-
- node := self parse: 'foo
- true ifTrue: [ 1 ]' forClass: Object.
-
- self assert: (node navigationNodeAt: 2@7 ifAbsent: [ nil ]) selector equals: 'ifTrue:'.
-
- node := self parse: 'foo
- self foo; bar; baz' forClass: Object.
-
- self assert: (node navigationNodeAt: 2@8 ifAbsent: [ nil ]) selector equals: 'foo'
- ! !
- TestCase subclass: #AbstractCodeGeneratorInstallTest
- slots: {#receiver}
- package: 'Compiler-Tests'!
- !AbstractCodeGeneratorInstallTest methodsFor: 'accessing'!
- receiver
- ^ receiver
- ! !
- !AbstractCodeGeneratorInstallTest methodsFor: 'testing'!
- shouldntInstall: aString
- | method |
- [ self
- should: [ method := self install: aString forClass: receiver class ]
- raise: ParseError ]
- ensure: [ method ifNotNil: [ receiver class removeCompiledMethod: method ] ]
- ! !
- !AbstractCodeGeneratorInstallTest methodsFor: 'tests'!
- testMistypedPragmaJSStatement
- self shouldntInstall: 'foo < inlineJS: ''return ''foo'''' >'
- !
- testNiladicJSOverride
- receiver := ObjectMock new.
- receiver foo: 4.
- self while: 'baz <jsOverride: #baz> ^ (foo := foo + 3)' should: [
- self assert: receiver baz equals: 7.
- self assert: (receiver basicPerform: #baz) equals: 10.
- self assert: receiver baz equals: 13.
- self assert: receiver foo equals: 13 ]
- !
- testNiladicJSOverrideDifferentNames
- receiver := ObjectMock new.
- receiver foo: 4.
- self while: 'quux <jsOverride: #mux> ^ (foo := foo + 3)' should: [
- self should: [ receiver mux ] raise: MessageNotUnderstood.
- self assert: (receiver basicPerform: #mux) equals: 7.
- self assert: receiver quux equals: 10.
- self should: [ receiver basicPerform: #quux ] raise: Error.
- self assert: receiver foo equals: 10 ]
- !
- testPragmaInBlock
- self shouldntInstall: 'foo ^ [ < fooBar > 4 ] value'
- ! !
- !AbstractCodeGeneratorInstallTest class methodsFor: 'testing'!
- isAbstract
- ^ self name = AbstractCodeGeneratorInstallTest name
- ! !
- AbstractCodeGeneratorInstallTest subclass: #CodeGeneratorInstallTest
- slots: {}
- package: 'Compiler-Tests'!
- AbstractCodeGeneratorInstallTest subclass: #InliningCodeGeneratorInstallTest
- slots: {}
- package: 'Compiler-Tests'!
- TestCase subclass: #ScopeVarTest
- slots: {}
- package: 'Compiler-Tests'!
- !ScopeVarTest methodsFor: 'tests'!
- testClassRefVar
- | node |
- node := VariableNode new
- value: 'Object';
- yourself.
- SemanticAnalyzer new
- pushScope: MethodLexicalScope new;
- visit: node.
- self assert: node binding isClassRefVar
- !
- testInstanceVar
- | node scope |
- node := VariableNode new
- value: 'bzzz';
- yourself.
- scope := MethodLexicalScope new.
- scope addIVar: 'bzzz'.
- self assert: (scope bindingFor: node) isInstanceVar
- !
- testPseudoVar
- | node pseudoVars |
- pseudoVars := #('self' 'super' 'true' 'false' 'nil').
- pseudoVars do: [:each |
- node := VariableNode new
- value: each;
- yourself.
- self assert: (MethodLexicalScope new bindingFor: node) isPseudoVar]
- !
- testTempVar
- | node scope |
- node := VariableNode new
- value: 'bzzz';
- yourself.
- scope := MethodLexicalScope new.
- scope addTemp: 'bzzz'.
- self assert: (scope bindingFor: node) isTempVar
- !
- testUnknownVar
- | node |
- node := VariableNode new
- value: 'bzzz';
- yourself.
- self assert: (MethodLexicalScope new bindingFor: node) isNil
- ! !
- TestCase subclass: #SemanticAnalyzerTest
- slots: {#analyzer}
- package: 'Compiler-Tests'!
- !SemanticAnalyzerTest methodsFor: 'running'!
- setUp
- analyzer := SemanticAnalyzer on: Object
- ! !
- !SemanticAnalyzerTest methodsFor: 'tests'!
- testAssignment
- | src ast |
- src := 'foo self := 1'.
- ast := Smalltalk parse: src.
- self should: [analyzer visit: ast] raise: InvalidAssignmentError
- !
- testNonLocalReturn
- | src ast |
- src := 'foo | a | a + 1. ^ a'.
- ast := Smalltalk parse: src.
- analyzer visit: ast.
- self deny: ast scope hasNonLocalReturn
- !
- testNonLocalReturn2
- | src ast |
- src := 'foo | a | a + 1. [ [ ^ a] ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast.
- self assert: ast scope hasNonLocalReturn
- !
- testScope
- | src ast |
- src := 'foo | a | a + 1. [ | b | b := a ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast.
- self deny: ast dagChildren first dagChildren last scope == ast scope.
- !
- testScope2
- | src ast |
- src := 'foo | a | a + 1. [ [ | b | b := a ] ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast.
- self deny: ast dagChildren first dagChildren last dagChildren first dagChildren first scope == ast scope.
- !
- testScopeLevel
- | src ast |
- src := 'foo | a | a + 1. [ [ | b | b := a ] ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast.
- self assert: ast scope scopeLevel equals: 1.
- self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first scope scopeLevel equals: 3
- !
- testUnknownVariables
- | src ast |
- src := 'foo | a | b + a'.
- ast := Smalltalk parse: src.
- self should: [ analyzer visit: ast ] raise: UnknownVariableError
- !
- testUnknownVariablesWithScope
- | src ast |
- src := 'foo | a b | [ c + 1. [ a + 1. d + 1 ]]'.
- ast := Smalltalk parse: src.
-
- self should: [ analyzer visit: ast ] raise: UnknownVariableError
- !
- testVariableShadowing
- | src ast |
- src := 'foo | a | a + 1'.
- ast := Smalltalk parse: src.
- analyzer visit: ast
- !
- testVariableShadowing2
- | src ast |
- src := 'foo | a | a + 1. [ | a | a := 2 ]'.
- ast := Smalltalk parse: src.
- self should: [analyzer visit: ast] raise: ShadowingVariableError
- !
- testVariableShadowing3
- | src ast |
- src := 'foo | a | a + 1. [ | b | b := 2 ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast
- !
- testVariableShadowing4
- | src ast |
- src := 'foo | a | a + 1. [ [ [ | b | b := 2 ] ] ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast
- !
- testVariableShadowing5
- | src ast |
- src := 'foo | a | a + 1. [ [ [ | a | a := 2 ] ] ]'.
- ast := Smalltalk parse: src.
- self should: [analyzer visit: ast] raise: ShadowingVariableError
- !
- testVariablesLookup
- | src ast |
- src := 'foo | a | a + 1. [ | b | b := a ]'.
- ast := Smalltalk parse: src.
- analyzer visit: ast.
- "Binding for `a` in the message send"
- self assert: ast dagChildren first dagChildren first receiver binding isTempVar.
- self assert: ast dagChildren first dagChildren first receiver binding scope == ast scope.
- "Binding for `b`"
- self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first left binding isTempVar.
- self assert: ast dagChildren first dagChildren last dagChildren first dagChildren first left binding scope == ast dagChildren first dagChildren last scope.
- ! !
- SemanticAnalyzerTest subclass: #AISemanticAnalyzerTest
- slots: {}
- package: 'Compiler-Tests'!
- !AISemanticAnalyzerTest methodsFor: 'running'!
- setUp
- analyzer := (AISemanticAnalyzer on: Object)
- context: (AIContext new
- defineLocal: 'local';
- localAt: 'local' put: 3;
- yourself);
- yourself
- ! !
- !AISemanticAnalyzerTest methodsFor: 'tests'!
- testContextVariables
- | src ast |
-
- src := 'foo | a | local + a'.
- ast := Smalltalk parse: src.
- self shouldnt: [ analyzer visit: ast ] raise: UnknownVariableError
- ! !
- Trait named: #TASTCompilingTest
- package: 'Compiler-Tests'!
- !TASTCompilingTest methodsFor: 'accessing'!
- codeGeneratorClass
- self subclassResponsibility
- ! !
- !TASTCompilingTest methodsFor: 'compiling'!
- install: aString forClass: aClass
- ^ self compiler
- install: aString
- forClass: aClass
- protocol: 'tests'
- ! !
- !TASTCompilingTest methodsFor: 'factory'!
- compiler
- ^ Compiler new
- codeGeneratorClass: self codeGeneratorClass;
- yourself
- ! !
- !TASTCompilingTest methodsFor: 'testing'!
- while: aString inClass: aClass should: aBlock
- | method |
- [
- method := self install: aString forClass: aClass.
- aBlock value: method ]
- ensure: [ method ifNotNil: [ aClass removeCompiledMethod: method ] ]
- !
- while: aString should: aBlock
- self while: aString inClass: self receiver class should: aBlock
- ! !
- Trait named: #TASTParsingTest
- package: 'Compiler-Tests'!
- !TASTParsingTest methodsFor: 'parsing'!
- parse: aString forClass: aClass
- ^ Compiler new
- ast: aString
- forClass: aClass
- protocol: 'test'
- ! !
- Trait named: #TCTDebugged
- package: 'Compiler-Tests'!
- !TCTDebugged methodsFor: 'private'!
- interpret: aString forClass: aClass receiver: anObject withArguments: aDictionary
- "The food is a methodNode. Interpret the sequenceNode only"
-
- | ctx |
-
- ctx := self prepareContextFor: aString class: aClass receiver: anObject withArguments: aDictionary.
-
- ^ (ASTDebugger context: ctx) proceed; result
- ! !
- Trait named: #TCTExecuted
- package: 'Compiler-Tests'!
- !TCTExecuted methodsFor: 'testing'!
- while: aString inClass: aClass should: aBlock
- super
- while: aString
- inClass: aClass
- should: [ :method | aBlock value: [
- self receiver perform: method selector ] ]
- ! !
- Trait named: #TCTInlined
- package: 'Compiler-Tests'!
- !TCTInlined methodsFor: 'accessing'!
- codeGeneratorClass
- ^ InliningCodeGenerator
- ! !
- Trait named: #TCTInterpreted
- package: 'Compiler-Tests'!
- !TCTInterpreted methodsFor: 'private'!
- interpret: aString forClass: aClass receiver: anObject withArguments: aDictionary
- "The food is a methodNode. Interpret the sequenceNode only"
-
- | ctx |
-
- ctx := self prepareContextFor: aString class: aClass receiver: anObject withArguments: aDictionary.
-
- ^ ctx interpreter proceed; result
- !
- prepareContextFor: aString class: aClass receiver: anObject withArguments: aDictionary
- "The food is a methodNode. Interpret the sequenceNode only"
-
- | ctx ast |
-
- ast := self parse: aString forClass: aClass.
-
- ctx := AIContext new
- receiver: anObject;
- selector: ast selector;
- interpreter: ASTInterpreter new;
- yourself.
-
- "Define locals for the context"
- ast sequenceNode ifNotNil: [ :sequence |
- sequence temps do: [ :each |
- ctx defineLocal: each ] ].
-
- aDictionary keysAndValuesDo: [ :key :value |
- ctx localAt: key put: value ].
-
- ctx interpreter
- context: ctx;
- node: ast;
- enterNode.
-
- ^ctx
- ! !
- !TCTInterpreted methodsFor: 'testing'!
- while: aString inClass: aClass should: aBlock
- super
- while: aString
- inClass: aClass
- should: [ aBlock value: [
- self
- interpret: aString
- forClass: aClass
- receiver: self receiver
- withArguments: #{} ] ]
- ! !
- Trait named: #TCTNonInlined
- package: 'Compiler-Tests'!
- !TCTNonInlined methodsFor: 'accessing'!
- codeGeneratorClass
- ^ CodeGenerator
- ! !
- TASTCompilingTest setTraitComposition: {TASTParsingTest} asTraitComposition!
- TCTDebugged setTraitComposition: {TCTInterpreted} asTraitComposition!
- ASTMethodRunningTest setTraitComposition: {TASTCompilingTest} asTraitComposition!
- ASTDebuggerTest setTraitComposition: {TCTNonInlined. TCTDebugged} asTraitComposition!
- ASTInterpreterTest setTraitComposition: {TCTNonInlined. TCTInterpreted} asTraitComposition!
- CodeGeneratorTest setTraitComposition: {TCTNonInlined. TCTExecuted} asTraitComposition!
- InliningCodeGeneratorTest setTraitComposition: {TCTInlined. TCTExecuted} asTraitComposition!
- ASTPCNodeVisitorTest setTraitComposition: {TASTParsingTest} asTraitComposition!
- ASTPositionTest setTraitComposition: {TASTParsingTest} asTraitComposition!
- AbstractCodeGeneratorInstallTest setTraitComposition: {TASTCompilingTest} asTraitComposition!
- CodeGeneratorInstallTest setTraitComposition: {TCTNonInlined} asTraitComposition!
- InliningCodeGeneratorInstallTest setTraitComposition: {TCTInlined} asTraitComposition!
- ! !
|