-
Notifications
You must be signed in to change notification settings - Fork 71
/
VMSimpleStackBasedCogitPolymorphicPICTest.class.st
279 lines (219 loc) · 8.33 KB
/
VMSimpleStackBasedCogitPolymorphicPICTest.class.st
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
Class {
#name : #VMSimpleStackBasedCogitPolymorphicPICTest,
#superclass : #VMSimpleStackBasedCogitAbstractTest,
#instVars : [
'selector',
'numArgs',
'receiver',
'receiverTag',
'picTypeTags',
'cogMethods',
'compiledMethods',
'configuredPicCases'
],
#pools : [
'CogMethodConstants'
],
#category : #'VMMakerTests-JitTests'
}
{ #category : #'building suites' }
VMSimpleStackBasedCogitPolymorphicPICTest class >> testParameters [
^ super testParameters *
(ParametrizedTestMatrix new
forSelector: #configuredPicCases addOptions: (2 to: 6);
yourself)
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> assertHitAtCase: aCase [
| pic |
"Only run this test if the test is configured for so much cases"
aCase < self configuredPicCases ifFalse: [ ^ self skip ].
picTypeTags at: aCase put: receiverTag.
pic := self makePolymorphicPIC.
self assertPIC: pic hits: (cogMethods at: aCase)
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> assertPIC: pic hits: hitMethod [
"Receiver is nil, class tag of the first entry is the receiver's class tag.
- the receiver matches class tag for case 0
- the receiver does not match with the class tag for case 1
- so it should call method for case 0"
machineSimulator receiverRegisterValue: receiver.
machineSimulator classRegisterValue: (picTypeTags at: 0).
"Should call method 1 just after the type check (to avoid it).
The check was already done in the PIC"
self runFrom: pic address + cogit entryOffset until: hitMethod address + cogit noCheckEntryOffset.
"When a PIC Hits
- The instruction pointer is at no check entry offset of the hitted method
- The class register value case 0 tag regardless of the hit
- the receiver register value contains the receiver"
self assert: machineSimulator instructionPointerRegisterValue equals: hitMethod address + cogit noCheckEntryOffset.
self assert: machineSimulator classRegisterValue equals: (picTypeTags at: 0).
self assert: machineSimulator receiverRegisterValue equals: receiver
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> assertPICMiss: pic [
"Receiver is nil, class tag of the first entry is 1 (a small integer).
- the receiver does not match with the class tag for case 0
- the receiver does not match with the class tag for case 1
- so it should call the closed pic miss trampoline"
machineSimulator receiverRegisterValue: receiver.
machineSimulator classRegisterValue: (picTypeTags at: 0).
self runFrom: pic address + cogit entryOffset until: cogit ceCPICMissTrampoline.
"Failing all two PIC cases calls the pic trampoline.
- The instruction pointer is at the trampoline
- The class register value contains the pic
- the receiver register value contains the receiver"
self assert: machineSimulator instructionPointerRegisterValue equals: cogit ceCPICMissTrampoline.
self assert: machineSimulator classRegisterValue equals: pic address.
self assert: machineSimulator receiverRegisterValue equals: receiver
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> configuredPicCases [
^ configuredPicCases
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> configuredPicCases: aNumber [
configuredPicCases := aNumber
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> extendPIC: aPic [
cogit
cogExtendPIC: aPic
CaseNMethod: (compiledMethods at: aPic cPICNumCases)
tag: (picTypeTags at: aPic cPICNumCases)
isMNUCase: false.
]
{ #category : #helpers }
VMSimpleStackBasedCogitPolymorphicPICTest >> makePolymorphicPIC [
| pic |
pic := cogit cogPICSelector: selector
numArgs: numArgs
Case0Method: (cogMethods at: 0)
Case1Method: (compiledMethods at: 1)
tag: (picTypeTags at: 1)
isMNUCase: false.
3 to: self configuredPicCases do: [ :extraCase |
self extendPIC: pic ].
^ pic
]
{ #category : #running }
VMSimpleStackBasedCogitPolymorphicPICTest >> setUp [
super setUp.
self setUpCogMethodEntry.
cogit generateClosedPICPrototype.
cogit methodZone
manageFrom: cogit methodZoneBase
to: cogit methodZone effectiveLimit.
"Prepare the methods to put in PICs"
receiver := memory nilObject.
selector := self newOldSpaceObjectWithSlots: 0.
numArgs := 0.
receiverTag := memory classIndexOf: receiver.
picTypeTags := Dictionary new.
compiledMethods := Dictionary new.
cogMethods := Dictionary new.
"Configure by default some type tags.
None of them should match by costruction the tag of the receiver.
Specific tests should override this to force a PIC HIT"
1 to: 6 do: [ :index |
| cogMethod compiledMethod |
picTypeTags at: index - 1 put: receiverTag + index.
compiledMethod := methodBuilder newMethod
literals: { selector };
buildMethod.
cogMethod := self
generateCogMethod: [ cogit RetN: 0 ]
selector: selector.
cogit coInterpreter
rawHeaderOf: compiledMethod
put: cogMethod asInteger.
compiledMethods at: index - 1 put: compiledMethod.
cogMethods at: index - 1 put: cogMethod ] "Maximum polymorphic cases"
]
{ #category : #'tests - metadata' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHasConfiguredCases [
| pic |
pic := self makePolymorphicPIC.
self assert: pic cPICNumCases equals: self configuredPicCases
]
{ #category : #'tests - metadata' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHasJumpToAbortTrampoline [
| pic |
pic := self makePolymorphicPIC.
self assert: (cogit backend callTargetFromReturnAddress: pic asInteger + cogit missOffset) equals: (cogit picAbortTrampolineFor: numArgs)
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHitCase0 [
self assertHitAtCase: 0
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHitCase1 [
self assertHitAtCase: 1
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHitCase2 [
self assertHitAtCase: 2
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHitCase3 [
self assertHitAtCase: 3
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHitCase4 [
self assertHitAtCase: 4
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testHitCase5 [
"This is the last case. Cog PICs have 6 cases (0-based)"
self assertHitAtCase: 5
]
{ #category : #'tests - metadata' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testIsClosedPic [
| pic |
pic := self makePolymorphicPIC.
self assert: pic cmType equals: CMPolymorphicIC.
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testMiss [
| pic |
pic := self makePolymorphicPIC.
self assertPICMiss: pic
]
{ #category : #'tests - metadata' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testNumberOfArgumentsInHeader [
| pic |
pic := self makePolymorphicPIC.
self assert: pic cmNumArgs equals: numArgs
]
{ #category : #'tests - hit/miss' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testPolymorphicPICHitDoesNotCallEntryOffset [
| pic methodCheckEntryPoint methodNoCheckEntryPoint passedByCheckEntryPoint |
picTypeTags at: 0 put: receiverTag.
pic := self makePolymorphicPIC.
"Receiver is nil, class tag of the first entry is the receiver's class tag.
- the receiver matches class tag for case 0
- the receiver does not match with the class tag for case 1
- so it should call method for case 0"
machineSimulator receiverRegisterValue: receiver.
machineSimulator classRegisterValue: (picTypeTags at: 0).
"Should call method of case 0 just after the type check (to avoid it).
The check was already done in the PIC.
We execute from the PIC expecting to arrive to the no entry offset of the cog method, checking we never pass through the check entry"
methodCheckEntryPoint := (cogMethods at: 0) address + cogit entryOffset.
methodNoCheckEntryPoint := (cogMethods at: 0) address + cogit noCheckEntryOffset.
passedByCheckEntryPoint := false.
machineSimulator
registerHook: [ passedByCheckEntryPoint := true ]
atAddress: methodCheckEntryPoint.
self
runFrom: pic address + cogit entryOffset
until: methodNoCheckEntryPoint.
self deny: passedByCheckEntryPoint
]
{ #category : #'tests - metadata' }
VMSimpleStackBasedCogitPolymorphicPICTest >> testSelectorInHeader [
| pic |
pic := self makePolymorphicPIC.
self assert: pic selector equals: selector
]