Skip to content

Commit afdaa93

Browse files
authored
Merge pull request #987 from RenaudFondeur/betterInliningStable
refactor inlining code and add tests for it
2 parents 2121d9e + bdda5f9 commit afdaa93

16 files changed

+1919
-94
lines changed

smalltalksrc/Slang-Tests/SLDeadCodeEliminationTest.class.st

Lines changed: 13 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ SLDeadCodeEliminationTest >> testConditionalWithOnlyCommentNoSendInReceiver [
2929
tMethod := ccg methodNamed:
3030
#conditionalWithOnlyCommentNoSendInReceiver.
3131

32+
ccg prepareMethods.
3233
ccg doBasicInlining: true.
3334

3435
sLDeadCodeElimination currentMethod: tMethod.
@@ -55,11 +56,11 @@ SLDeadCodeEliminationTest >> testConditionalWithOnlyCommentSendInReceiver [
5556
"currently the only way to get comments in a methods is through inlining, having only comments is equivalent to being empty so it shouldn't change the behavior of the dead code elimination process"
5657

5758
| translation tMethod |
58-
tMethod := ccg methodNamed:
59-
#conditionalWithOnlyCommentSendInReceiver.
59+
tMethod := ccg methodNamed: #conditionalWithOnlyCommentSendInReceiver.
6060

61+
ccg prepareMethods.
6162
ccg doBasicInlining: true.
62-
63+
6364
sLDeadCodeElimination currentMethod: tMethod.
6465
sLDeadCodeElimination removeDeadCodeInCurrentMethod.
6566

@@ -1795,7 +1796,8 @@ SLDeadCodeEliminationTest >> testMethodWithNeverUsedLocalsFromBlockasArguments [
17951796
| translation tMethod |
17961797
tMethod := ccg methodNamed:
17971798
#methodWithNeverUsedLocalsFromBlockasArguments.
1798-
tMethod prepareMethodIn: ccg.
1799+
1800+
ccg prepareMethods.
17991801
ccg doBasicInlining: true.
18001802

18011803
sLDeadCodeElimination currentMethod: tMethod.
@@ -1920,7 +1922,9 @@ SLDeadCodeEliminationTest >> testMethodWithOnlyComment [
19201922
| translation tMethod |
19211923
tMethod := ccg methodNamed: #methodWithOnlyComment.
19221924

1925+
ccg prepareMethods.
19231926
ccg doBasicInlining: true.
1927+
19241928
sLDeadCodeElimination currentMethod: tMethod.
19251929
sLDeadCodeElimination removeDeadCodeInCurrentMethod.
19261930

@@ -5192,7 +5196,8 @@ SLDeadCodeEliminationTest >> testSwitchWithOnlyCommentNoSendInReceiver [
51925196

51935197
| translation tMethod |
51945198
tMethod := ccg methodNamed: #switchWithOnlyCommentNoSendInReceiver:.
5195-
tMethod prepareMethodIn: ccg.
5199+
5200+
ccg prepareMethods.
51965201
ccg doBasicInlining: true.
51975202

51985203
sLDeadCodeElimination currentMethod: tMethod.
@@ -5207,7 +5212,7 @@ SLDeadCodeEliminationTest >> testSwitchWithOnlyCommentNoSendInReceiver [
52075212
equals:
52085213
'/* SLDeadCodeEliminationTestClass>>#switchWithOnlyCommentNoSendInReceiver: */
52095214
static void
5210-
switchWithOnlyCommentNoSendInReceiver(SLDeadCodeEliminationTestClass * self_in_switchWithOnlyCommentNoSendInReceiver, sqInt anInt)
5215+
switchWithOnlyCommentNoSendInReceiver(SLDeadCodeEliminationTestClass * self_in_switchWithOnlyCommentNoSendInReceiver, sqInt _anInt)
52115216
{
52125217
{
52135218
return;
@@ -5221,7 +5226,8 @@ SLDeadCodeEliminationTest >> testSwitchWithOnlyCommentSendInReceiver [
52215226

52225227
| translation tMethod |
52235228
tMethod := ccg methodNamed: #switchWithOnlyCommentSendInReceiver.
5224-
tMethod prepareMethodIn: ccg.
5229+
5230+
ccg prepareMethods.
52255231
ccg doBasicInlining: true.
52265232

52275233
sLDeadCodeElimination currentMethod: tMethod.
Lines changed: 296 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,296 @@
1+
Class {
2+
#name : 'SLMockInliningTestClass',
3+
#superclass : 'SlangClass',
4+
#category : 'Slang-Tests',
5+
#package : 'Slang-Tests'
6+
}
7+
8+
{ #category : 'helpers' }
9+
SLMockInliningTestClass >> emptyMethod: arg [
10+
11+
12+
]
13+
14+
{ #category : 'inlining-arguments' }
15+
SLMockInliningTestClass >> emptyMethodAWithSimpleArgumentsInlined [
16+
17+
self emptyMethod: self methodBAlwaysInlined
18+
]
19+
20+
{ #category : 'inlining-simple' }
21+
SLMockInliningTestClass >> methodA [
22+
23+
1 + 1.
24+
self methodB
25+
]
26+
27+
{ #category : 'inlining-assignment-helpers' }
28+
SLMockInliningTestClass >> methodAAssignOnReturn [
29+
30+
1 + 1.
31+
^ self methodBAssignOnReturn
32+
]
33+
34+
{ #category : 'inlining-assignment' }
35+
SLMockInliningTestClass >> methodAInlineIfFalseReturningIfTrueInAssignement [
36+
37+
| a |
38+
a := self methodBIfFalseReturningIfTrue
39+
]
40+
41+
{ #category : 'inlining-returning-conditional' }
42+
SLMockInliningTestClass >> methodAInlineIfFalseReturningIfTrueInReturn [
43+
44+
^ self methodBIfFalseReturningIfTrue
45+
]
46+
47+
{ #category : 'inlining-assignment' }
48+
SLMockInliningTestClass >> methodAInlineMultipleIfFalseReturningIfTrueInAssignment [
49+
50+
| a |
51+
a := self methodB
52+
ifFalse: [ self methodBIfFalseReturningIfTrue ]
53+
ifTrue: [
54+
5.
55+
self methodBIfFalseReturningIfTrue ]
56+
]
57+
58+
{ #category : 'inlining-assignment' }
59+
SLMockInliningTestClass >> methodAInlineReturningIfTrueIfFalseInAssignment [
60+
61+
| a |
62+
a := self methodBReturningIfTrueIfFalse
63+
]
64+
65+
{ #category : 'inlining-returning-conditional' }
66+
SLMockInliningTestClass >> methodAInlineReturningIfTrueIfFalseInReturn [
67+
68+
^ self methodBReturningIfTrueIfFalse
69+
]
70+
71+
{ #category : 'inlining-assignment' }
72+
SLMockInliningTestClass >> methodAInlineReturningIfTrueInAssignment [
73+
74+
| a |
75+
a := self methodBReturningIfTrue
76+
]
77+
78+
{ #category : 'inlining-returning-conditional' }
79+
SLMockInliningTestClass >> methodAInlineReturningIfTrueInReturn [
80+
81+
^ self methodBReturningIfTrue
82+
]
83+
84+
{ #category : 'inlining-assignment' }
85+
SLMockInliningTestClass >> methodAInlineReturningInlinedIfTrueInAssignment [
86+
87+
| a |
88+
a := self methodBReturningInlinedIfTrue
89+
]
90+
91+
{ #category : 'inlining-jump' }
92+
SLMockInliningTestClass >> methodAMultipleReturn [
93+
94+
self methodBMultipleReturn.
95+
^ 1 + 1
96+
]
97+
98+
{ #category : 'inlining-jump' }
99+
SLMockInliningTestClass >> methodAMultipleReturnAsAssignmentExpression [
100+
101+
| x |
102+
x := self methodBMultipleReturn
103+
]
104+
105+
{ #category : 'inlining-jump' }
106+
SLMockInliningTestClass >> methodAMultipleReturnAsReturnExpression [
107+
108+
^ self methodBMultipleReturn
109+
]
110+
111+
{ #category : 'inlining-jump' }
112+
SLMockInliningTestClass >> methodAMultipleReturnExpression [
113+
114+
self methodBMultipleReturn.
115+
^ 1 + 1
116+
]
117+
118+
{ #category : 'inlining-assignment' }
119+
SLMockInliningTestClass >> methodAReturnAssignment [
120+
121+
| a |
122+
^ a := self methodB
123+
]
124+
125+
{ #category : 'inlining-assignment-helpers' }
126+
SLMockInliningTestClass >> methodAReturnOnAssignment [
127+
128+
| var |
129+
1 + 1.
130+
^ self methodBReturnOnAssignment: [ :x |
131+
var := x.
132+
]
133+
]
134+
135+
{ #category : 'inlining-jump' }
136+
SLMockInliningTestClass >> methodASimpleReturn [
137+
138+
self methodBSimpleReturn.
139+
^ 1 + 1
140+
]
141+
142+
{ #category : 'inlining-arguments' }
143+
SLMockInliningTestClass >> methodAWithArgumentsInlined [
144+
145+
^ self methodB: self methodCAlwaysInlined
146+
]
147+
148+
{ #category : 'inlining-arguments' }
149+
SLMockInliningTestClass >> methodAWithReturningSendArgumentsInlined [
150+
151+
^ self methodB: self methodCAlwaysInlined
152+
]
153+
154+
{ #category : 'inlining-arguments' }
155+
SLMockInliningTestClass >> methodAWithSimpleArgumentsInlined [
156+
157+
self methodB: self methodBAlwaysInlined
158+
]
159+
160+
{ #category : 'inlining-simple-helpers' }
161+
SLMockInliningTestClass >> methodB [
162+
163+
2 + 2
164+
]
165+
166+
{ #category : 'inlining-arguments-helpers' }
167+
SLMockInliningTestClass >> methodB: anArg [
168+
169+
<inline: #never>
170+
^ anArg
171+
]
172+
173+
{ #category : 'inlining-arguments-helpers' }
174+
SLMockInliningTestClass >> methodBAlwaysInlined [
175+
176+
<inline: #always>
177+
2 + 2
178+
]
179+
180+
{ #category : 'inlining-assignment-helpers' }
181+
SLMockInliningTestClass >> methodBAssignOnReturn [
182+
183+
^ 2 + 2
184+
]
185+
186+
{ #category : 'inlining-returning-conditional-helpers' }
187+
SLMockInliningTestClass >> methodBIfFalseReturningIfTrue [
188+
189+
self methodB
190+
ifFalse: [ true ]
191+
ifTrue: [ ^ false ].
192+
^ true
193+
]
194+
195+
{ #category : 'inlining-jump-helpers' }
196+
SLMockInliningTestClass >> methodBMultipleReturn [
197+
198+
self methodB ifTrue: [ ^ 0 ].
199+
self methodCMultipleReturn.
200+
^ 2 + 2
201+
]
202+
203+
{ #category : 'inlining-assignment-helpers' }
204+
SLMockInliningTestClass >> methodBReturnOnAssignment [
205+
206+
| var |
207+
var := 2 + 2
208+
]
209+
210+
{ #category : 'inlining-assignment-helpers' }
211+
SLMockInliningTestClass >> methodBReturnOnAssignment: aBlock [
212+
213+
| var |
214+
var := 2 + 2.
215+
^ aBlock value: var
216+
]
217+
218+
{ #category : 'inlining-returning-conditional-helpers' }
219+
SLMockInliningTestClass >> methodBReturningIfTrue [
220+
221+
^ self methodB ifTrue: [ true ]
222+
]
223+
224+
{ #category : 'inlining-returning-conditional-helpers' }
225+
SLMockInliningTestClass >> methodBReturningIfTrueIfFalse [
226+
227+
^ self methodB ifTrue: [ 1 ] ifFalse: [ 2 ]
228+
]
229+
230+
{ #category : 'inlining-returning-conditional-helpers' }
231+
SLMockInliningTestClass >> methodBReturningInlinedIfTrue [
232+
233+
^ self methodB ifTrue: [ self methodB ]
234+
]
235+
236+
{ #category : 'inlining-jump-helpers' }
237+
SLMockInliningTestClass >> methodBSimpleReturn [
238+
239+
self methodCSimpleReturn.
240+
^ 2 + 2
241+
]
242+
243+
{ #category : 'inlining-simple-helpers' }
244+
SLMockInliningTestClass >> methodC [
245+
246+
3 + 3.
247+
self methodA
248+
]
249+
250+
{ #category : 'inlining-arguments-helpers' }
251+
SLMockInliningTestClass >> methodCAlwaysInlined [
252+
253+
<inline: #always>
254+
3 + 3.
255+
self methodA
256+
]
257+
258+
{ #category : 'inlining-assignment' }
259+
SLMockInliningTestClass >> methodCAssignOnReturn [
260+
261+
| a |
262+
3 + 3.
263+
a := self methodAAssignOnReturn
264+
]
265+
266+
{ #category : 'inlining-jump-helpers' }
267+
SLMockInliningTestClass >> methodCMultipleReturn [
268+
269+
self methodC ifTrue: [ ^ 1 ].
270+
^ 3 + 3
271+
]
272+
273+
{ #category : 'inlining-assignment' }
274+
SLMockInliningTestClass >> methodCReturnOnAssignment [
275+
276+
3 + 3.
277+
^ self methodAReturnOnAssignment
278+
]
279+
280+
{ #category : 'inlining-jump-helpers' }
281+
SLMockInliningTestClass >> methodCSimpleReturn [
282+
283+
^ 3 + 3
284+
]
285+
286+
{ #category : 'collect-statements-for-inlining' }
287+
SLMockInliningTestClass >> methodWithAvoidedSelectors [
288+
289+
self cCode: [ ] inSmalltalk: [ ].
290+
self cCall: 'method'.
291+
self cCall: 'method' withArguments: { 1. 2. 3 }.
292+
self cppIf: ['cppCond'. true] ifTrue: [ 'in cppIfTrue'. false ] ifFalse: [ 'in cppIfFalse'. true ].
293+
[ 'and receiver'. true ] and: [ 'and argument'. false ].
294+
[ 'or receiver' . false ] or: [ 'or argument'. true ].
295+
[ 'ifTrue receiver'. false ] ifTrue: ['ifTrue argument' . true ]
296+
]

0 commit comments

Comments
 (0)