Skip to content

Commit e07ce91

Browse files
committed
Fix the XRay Primitive
1 parent 8905149 commit e07ce91

File tree

2 files changed

+8
-8
lines changed

2 files changed

+8
-8
lines changed

smalltalksrc/VMMaker/CogX64Compiler.class.st

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -433,6 +433,13 @@ CogX64Compiler >> canZeroExtend [
433433
^true
434434
]
435435

436+
{ #category : 'testing' }
437+
CogX64Compiler >> checkIs32bit: offset [
438+
439+
(offset between: -2147483648 and: 2147483647) ifFalse: [
440+
self error: 'Cannot jump to distances larger than 32 bits' ]
441+
]
442+
436443
{ #category : 'accessing' }
437444
CogX64Compiler >> cmpC32RTempByteSize [
438445
^5
@@ -4276,13 +4283,6 @@ CogX64Compiler >> is32BitSignedImmediate: a64BitUnsignedOperand [
42764283
inSmalltalk: [((a64BitUnsignedOperand >> 32) signedIntFromLong + 1 bitXor: 1) = (a64BitUnsignedOperand >> 31 bitAnd: 1)]
42774284
]
42784285

4279-
{ #category : 'testing' }
4280-
CogX64Compiler >> checkIs32bit: offset [
4281-
4282-
(offset between: -2147483648 and: 2147483647) ifFalse: [
4283-
self error: 'Cannot jump to distances larger than 32 bits' ]
4284-
]
4285-
42864286
{ #category : 'testing' }
42874287
CogX64Compiler >> isAddressRelativeToVarBase: varAddress [
42884288
"Support for addressing variables off the dedicated VarBaseReg. Allow for 1Mb of variables.

smalltalksrc/VMMaker/StackToRegisterMappingCogit.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3738,7 +3738,7 @@ StackToRegisterMappingCogit >> populate: tuple withPICInfoFor: cPIC firstCacheTa
37383738
picCaseMachineCodePC := self addressOfEndOfCase: i inCPIC: cPIC.
37393739
cacheTag := i = 1
37403740
ifTrue: [firstCacheTag]
3741-
ifFalse: [backEnd literalBeforeFollowingAddress: picCaseMachineCodePC - backEnd jumpLongConditionalByteSize].
3741+
ifFalse: [backEnd literal32BeforeFollowingAddress: picCaseMachineCodePC - backEnd jumpLongConditionalByteSize].
37423742

37433743
classOop := objectRepresentation classForInlineCacheTag: cacheTag.
37443744
objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.

0 commit comments

Comments
 (0)