1- Extension { #name : ' OCCodeSnippetTest' }
1+ Class {
2+ #name : ' OCCompileCodeSnippetTest' ,
3+ #superclass : ' OCCodeSnippetTest' ,
4+ #category : ' AST-Core-Tests-Snippets' ,
5+ #package : ' AST-Core-Tests' ,
6+ #tag : ' Snippets'
7+ }
28
3- { #category : ' *OpalCompiler-Tests ' }
4- OCCodeSnippetTest >> compileSnippet: anOCCodeSnippet [
9+ { #category : ' helpers ' }
10+ OCCompileCodeSnippetTest >> compileSnippet: anOCCodeSnippet [
511
612 ^ [ OpalCompiler new
713 permitFaulty: true ;
@@ -15,8 +21,8 @@ OCCodeSnippetTest >> compileSnippet: anOCCodeSnippet [
1521 e pass ]
1622]
1723
18- { #category : ' *OpalCompiler-Tests ' }
19- OCCodeSnippetTest >> compileSnippet: aSnippet onError: errorBlock [
24+ { #category : ' helpers ' }
25+ OCCompileCodeSnippetTest >> compileSnippet: aSnippet onError: errorBlock [
2026
2127 ^ [
2228 OpalCompiler new
@@ -26,8 +32,8 @@ OCCodeSnippetTest >> compileSnippet: aSnippet onError: errorBlock [
2632 do: [ :e | errorBlock cull: e ]
2733]
2834
29- { #category : ' *OpalCompiler-Tests ' }
30- OCCodeSnippetTest >> testCompileFailBlock [
35+ { #category : ' tests ' }
36+ OCCompileCodeSnippetTest >> testCompileFailBlock [
3137
3238 | method error |
3339 error := nil .
@@ -50,8 +56,8 @@ OCCodeSnippetTest >> testCompileFailBlock [
5056 self testExecute: method ]
5157]
5258
53- { #category : ' *OpalCompiler-Tests ' }
54- OCCodeSnippetTest >> testCompileFaulty [
59+ { #category : ' tests ' }
60+ OCCompileCodeSnippetTest >> testCompileFaulty [
5561
5662 | method |
5763
@@ -74,8 +80,8 @@ OCCodeSnippetTest >> testCompileFaulty [
7480 self testExecute: method
7581]
7682
77- { #category : ' *OpalCompiler-Tests ' }
78- OCCodeSnippetTest >> testCompileOnError [
83+ { #category : ' tests ' }
84+ OCCompileCodeSnippetTest >> testCompileOnError [
7985
8086 | method error |
8187 error := nil .
@@ -92,8 +98,8 @@ OCCodeSnippetTest >> testCompileOnError [
9298 self testExecute: method ]
9399]
94100
95- { #category : ' *OpalCompiler-Tests ' }
96- OCCodeSnippetTest >> testCompileOnErrorResume [
101+ { #category : ' tests ' }
102+ OCCompileCodeSnippetTest >> testCompileOnErrorResume [
97103
98104 | method error |
99105 error := nil .
@@ -107,8 +113,8 @@ OCCodeSnippetTest >> testCompileOnErrorResume [
107113 self testExecute: method
108114]
109115
110- { #category : ' *OpalCompiler-Tests ' }
111- OCCodeSnippetTest >> testCompileUndeclaredFaultyFailBlock [
116+ { #category : ' tests ' }
117+ OCCompileCodeSnippetTest >> testCompileUndeclaredFaultyFailBlock [
112118
113119 | method error |
114120 error := nil .
@@ -132,8 +138,8 @@ OCCodeSnippetTest >> testCompileUndeclaredFaultyFailBlock [
132138 self testExecute: method ]
133139]
134140
135- { #category : ' *OpalCompiler-Tests ' }
136- OCCodeSnippetTest >> testCompileWithRequestor [
141+ { #category : ' tests ' }
142+ OCCompileCodeSnippetTest >> testCompileWithRequestor [
137143
138144 | requestor method |
139145 requestor := OCMockRequestor new .
@@ -162,8 +168,52 @@ OCCodeSnippetTest >> testCompileWithRequestor [
162168 self testExecute: method
163169]
164170
165- { #category : ' *OpalCompiler-Tests' }
166- OCCodeSnippetTest >> testDoSemanticAnalysis [
171+ { #category : ' tests' }
172+ OCCompileCodeSnippetTest >> testCritiques [
173+
174+ | ast critiques |
175+ ast := snippet parse.
176+ critiques := ast critiques.
177+
178+ snippet numberOfCritiques ifNotNil: [ :n |
179+ self assert: critiques size equals: n.
180+ ^ self ].
181+
182+ " Alone blocks will have ReDeadBlockRule. Currently no other critiques are fired."
183+ " When we get some critiques, we will add a instance vaviable in the snippet to validate them"
184+ ast isBlock
185+ ifTrue: [
186+ self assert: critiques size equals: 1 .
187+ self assert: critiques anyOne rule class equals: ReDeadBlockRule ]
188+ ifFalse: [ self assert: critiques isEmpty ]
189+ ]
190+
191+ { #category : ' tests' }
192+ OCCompileCodeSnippetTest >> testDecompile [
193+
194+ | method ast |
195+ method := self compileSnippet: snippet.
196+ method ifNil: [ ^ self skip ]. " Another test responsibility"
197+ ast := method decompile.
198+ self assert: ast isMethod.
199+ ast := method parseTree.
200+ self assert: ast isMethod.
201+ " Decompilation lose many information. Not sure how to test more"
202+ ]
203+
204+ { #category : ' tests' }
205+ OCCompileCodeSnippetTest >> testDecompileIR [
206+
207+ | method ir |
208+ method := self compileSnippet: snippet.
209+ method ifNil: [ ^ self skip ]. " Another test responsibility"
210+ ir := method decompileIR.
211+ self assert: ir class equals: OCIRMethod .
212+ " Decompilation lose information. Not sure how to test more"
213+ ]
214+
215+ { #category : ' tests' }
216+ OCCompileCodeSnippetTest >> testDoSemanticAnalysis [
167217 " We should test more than that"
168218
169219 | ast |
@@ -174,8 +224,8 @@ OCCodeSnippetTest >> testDoSemanticAnalysis [
174224 self assert: (snippet hasAllNotices: ast allNotices)
175225]
176226
177- { #category : ' *OpalCompiler-Tests ' }
178- OCCodeSnippetTest >> testDoSemanticAnalysisOnError [
227+ { #category : ' tests ' }
228+ OCCompileCodeSnippetTest >> testDoSemanticAnalysisOnError [
179229 " We should test more than that"
180230
181231 | ast error |
@@ -190,8 +240,8 @@ OCCodeSnippetTest >> testDoSemanticAnalysisOnError [
190240 self assert: error isNil ]
191241]
192242
193- { #category : ' *OpalCompiler-Tests ' }
194- OCCodeSnippetTest >> testDump [
243+ { #category : ' tests ' }
244+ OCCompileCodeSnippetTest >> testDump [
195245
196246 | ast dump ast2 dump2 |
197247 ast := snippet parse.
@@ -202,8 +252,8 @@ OCCodeSnippetTest >> testDump [
202252 self assert: dump2 equals: dump
203253]
204254
205- { #category : ' *OpalCompiler-Tests ' }
206- OCCodeSnippetTest >> testExecute: method [
255+ { #category : ' helpers ' }
256+ OCCompileCodeSnippetTest >> testExecute: method [
207257
208258 | runBlock phonyArgs |
209259 self skipIf: #exec .
@@ -215,8 +265,8 @@ OCCodeSnippetTest >> testExecute: method [
215265 self testExecuteBlock: runBlock
216266]
217267
218- { #category : ' *OpalCompiler-Tests ' }
219- OCCodeSnippetTest >> testExecuteBlock: aRunBlock [
268+ { #category : ' helpers ' }
269+ OCCompileCodeSnippetTest >> testExecuteBlock: aRunBlock [
220270
221271 | runBlock |
222272 " a block that apply value on aRunBlock until it's no more a block"
0 commit comments