Skip to content

Commit 26beb75

Browse files
authored
Merge pull request #873 from tesonep/fix-large-classIndex-should-be-positive
When patching JITed code after become of a class, the class index can look like a negative number
2 parents cab16b3 + f572ef1 commit 26beb75

9 files changed

+99
-10
lines changed

smalltalksrc/VMMaker/CogAbstractInstruction.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1057,7 +1057,7 @@ CogAbstractInstruction >> getOperandsWithFormat: format [
10571057
ifTrue: [ (operand > 16 and: [ opcode ~= Label ])
10581058
ifTrue: [
10591059
(operand allMask: 16r80000000)
1060-
ifTrue: [ strOperands add: operand, '/', operand signedIntFromLong ].
1060+
ifTrue: [ strOperands add: operand printString, '/', operand signedIntFromLong printString ].
10611061
strOperands add: operand asString, '/', (operand hex)]
10621062
ifFalse: [
10631063
strOperands add: operand.

smalltalksrc/VMMaker/CogIA32Compiler.class.st

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3646,7 +3646,11 @@ CogIA32Compiler >> hasThreeAddressArithmetic [
36463646
{ #category : 'inline cacheing' }
36473647
CogIA32Compiler >> inlineCacheTagAt: callSiteReturnAddress [
36483648
"Answer the inline cache tag for the return address of a send."
3649-
^self literalBeforeFollowingAddress: callSiteReturnAddress - 5
3649+
3650+
<returnTypeC: #usqInt>
3651+
3652+
^ (self literalBeforeFollowingAddress: callSiteReturnAddress - 5)
3653+
bitAnd: 1 << objectMemory classIndexFieldWidth - 1
36503654
]
36513655

36523656
{ #category : 'disassembly' }

smalltalksrc/VMMaker/CogInLineLiteralsARMCompiler.class.st

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -50,8 +50,15 @@ CogInLineLiteralsARMCompiler >> getDefaultCogCodeSize [
5050
{ #category : 'inline cacheing' }
5151
CogInLineLiteralsARMCompiler >> inlineCacheTagAt: callSiteReturnAddress [
5252
"Answer the inline cache tag for the return address of a send."
53-
self assert: (self instructionIsBL: (self instructionBeforeAddress: callSiteReturnAddress)).
54-
^self extract32BitOperandFrom4InstructionsPreceding: callSiteReturnAddress - 4
53+
54+
<returnTypeC: #usqInt>
55+
56+
self assert: (self instructionIsBL:
57+
(self instructionBeforeAddress: callSiteReturnAddress)).
58+
59+
^ (self extract32BitOperandFrom4InstructionsPreceding:
60+
callSiteReturnAddress - 4) bitAnd:
61+
1 << objectMemory classIndexFieldWidth - 1
5562
]
5663

5764
{ #category : 'testing' }

smalltalksrc/VMMaker/CogInLineLiteralsX64Compiler.class.st

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -164,7 +164,11 @@ CogInLineLiteralsX64Compiler >> getDefaultCogCodeSize [
164164
{ #category : 'inline cacheing' }
165165
CogInLineLiteralsX64Compiler >> inlineCacheTagAt: callSiteReturnAddress [
166166
"Answer the inline cache tag for the return address of a send."
167-
^self literal32BeforeFollowingAddress: callSiteReturnAddress - 5
167+
168+
<returnTypeC: #usqInt>
169+
170+
^ (self literal32BeforeFollowingAddress: callSiteReturnAddress - 5)
171+
bitAnd: 1 << objectMemory classIndexFieldWidth - 1
168172
]
169173

170174
{ #category : 'testing' }

smalltalksrc/VMMaker/CogMIPSELCompiler.class.st

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1908,6 +1908,8 @@ CogMIPSELCompiler >> inlineCacheTagAt: callSiteReturnAddress [
19081908
... <-- callSiteReturnAddress"
19091909

19101910
<var: #callSiteReturnAddress type: #usqInt>
1911+
<returnTypeC: #usqInt>
1912+
19111913
self assert: (self opcodeAtAddress: callSiteReturnAddress - 24) = LUI.
19121914
self assert: (self opcodeAtAddress: callSiteReturnAddress - 20) = ORI.
19131915
self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
@@ -1916,7 +1918,8 @@ CogMIPSELCompiler >> inlineCacheTagAt: callSiteReturnAddress [
19161918
self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JALR.
19171919
self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
19181920

1919-
^self literalAtAddress: callSiteReturnAddress - 20
1921+
^(self literalAtAddress: callSiteReturnAddress - 20) bitAnd:
1922+
1 << objectMemory classIndexFieldWidth - 1
19201923
]
19211924

19221925
{ #category : 'disassembly' }

smalltalksrc/VMMaker/CogOutOfLineLiteralsARMCompiler.class.st

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,11 @@ CogOutOfLineLiteralsARMCompiler >> getDefaultCogCodeSize [
5151

5252
{ #category : 'inline cacheing' }
5353
CogOutOfLineLiteralsARMCompiler >> inlineCacheTagAt: callSiteReturnAddress [
54-
<inline: true>
55-
^objectMemory uint32AtPointer: (self pcRelativeAddressAt: (callSiteReturnAddress - 8) asUnsignedInteger)
54+
55+
<returnTypeC: #usqInt>
56+
57+
^(objectMemory uint32AtPointer: (self pcRelativeAddressAt: (callSiteReturnAddress - 8) asUnsignedInteger)) bitAnd:
58+
1 << objectMemory classIndexFieldWidth - 1
5659
]
5760

5861
{ #category : 'testing' }

smalltalksrc/VMMaker/CogOutOfLineLiteralsARMv8Compiler.class.st

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -207,8 +207,12 @@ CogOutOfLineLiteralsARMv8Compiler >> getDefaultCogCodeSize [
207207

208208
{ #category : 'inline cacheing' }
209209
CogOutOfLineLiteralsARMv8Compiler >> inlineCacheTagAt: callSiteReturnAddress [
210-
<inline: true>
211-
^objectMemory unsignedLongAt: (self pcRelativeAddressAt: (callSiteReturnAddress - 8) asUnsignedInteger)
210+
211+
<returnTypeC: #usqInt>
212+
213+
^ (objectMemory unsignedLongAt: (self pcRelativeAddressAt:
214+
(callSiteReturnAddress - 8) asUnsignedInteger)) bitAnd:
215+
1 << objectMemory classIndexFieldWidth - 1
212216
]
213217

214218
{ #category : 'testing' }

smalltalksrc/VMMaker/SpurMemoryManager.class.st

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3697,6 +3697,7 @@ SpurMemoryManager >> classFormatFromInstFormat: instFormat [
36973697

36983698
{ #category : 'header format' }
36993699
SpurMemoryManager >> classIndexFieldWidth [
3700+
<api>
37003701
"22-bit class mask => ~ 4M classes"
37013702
^22
37023703
]
@@ -8166,6 +8167,7 @@ SpurMemoryManager >> isValidClassIndex: classIndex [
81668167
SpurMemoryManager >> isValidClassTag: classIndex [
81678168
<api>
81688169
| classOrNil |
8170+
81698171
self assert: (classIndex between: 0 and: 1 << self classIndexFieldWidth - 1).
81708172
classOrNil := self classOrNilAtIndex: classIndex.
81718173
^classOrNil ~= nilObj
Lines changed: 62 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,62 @@
1+
Class {
2+
#name : 'VMClassTagInlineReadTest',
3+
#superclass : 'VMPrimitiveCallAbstractTest',
4+
#pools : [
5+
'CogRTLOpcodes'
6+
],
7+
#category : 'VMMakerTests-JitTests',
8+
#package : 'VMMakerTests',
9+
#tag : 'JitTests'
10+
}
11+
12+
{ #category : 'tests' }
13+
VMClassTagInlineReadTest >> testLinkingWithEntryOffset [
14+
15+
| sendingMethod targetMethod callSiteReturn |
16+
sendingMethod := self
17+
jitMethod: (self findMethod: #methodWithSend)
18+
selector: memory nilObject.
19+
20+
targetMethod := self
21+
jitMethod: (self findMethod: #yourself)
22+
selector: memory trueObject.
23+
24+
callSiteReturn := sendingMethod address + 16r98.
25+
26+
cogit
27+
linkSendAt: callSiteReturn
28+
in: sendingMethod
29+
to: targetMethod
30+
offset: cogit entryOffset
31+
receiver: memory falseObject.
32+
33+
self assert: (cogit backend inlineCacheTagAt: callSiteReturn) equals:(memory classIndexOf: memory falseObject)
34+
]
35+
36+
{ #category : 'tests' }
37+
VMClassTagInlineReadTest >> testLinkingWithEntryOffsetLargeClassIndex [
38+
39+
| sendingMethod targetMethod callSiteReturn |
40+
sendingMethod := self
41+
jitMethod: (self findMethod: #methodWithSend)
42+
selector: memory nilObject.
43+
44+
targetMethod := self
45+
jitMethod: (self findMethod: #yourself)
46+
selector: memory trueObject.
47+
48+
callSiteReturn := sendingMethod address + 16r98.
49+
50+
obj := self newZeroSizedObject.
51+
memory setClassIndexOf: obj to: (1 << memory classIndexFieldWidth - 5).
52+
53+
cogit
54+
linkSendAt: callSiteReturn
55+
in: sendingMethod
56+
to: targetMethod
57+
offset: cogit entryOffset
58+
receiver: obj.
59+
60+
61+
self assert: (cogit backend inlineCacheTagAt: callSiteReturn) equals: (1 << memory classIndexFieldWidth - 5)
62+
]

0 commit comments

Comments
 (0)