Skip to content

Commit

Permalink
VMMaker.oscog-eem.1972 Redo fixing extB sign extension in NewsqueakV4…
Browse files Browse the repository at this point in the history
… & SistaV1 extPushIntegerBytecode & extUnconditionalJump in interpreter and Cogit using bitShift: 8 instead of << 8. Slang seems to generate the correct code with bitAShift:, but not with <<.
  • Loading branch information
eliotmiranda committed Oct 31, 2016
1 parent e6245b4 commit ca0eca2
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 5 deletions.
6 changes: 3 additions & 3 deletions smalltalksrc/VMMaker/SimpleStackBasedCogit.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1833,7 +1833,7 @@ SimpleStackBasedCogit >> genExtPushIntegerBytecode [
"NewsqueakV4: 229 11100101 iiiiiiii Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
SistaV1: 232 11101000 iiiiiiii Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
| value |
value := byte1 + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) << 8).
value := byte1 + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) bitShift: 8).
extB := 0.
^self genPushLiteral: (objectMemory integerObjectOf: value)
]
Expand Down Expand Up @@ -2092,7 +2092,7 @@ SimpleStackBasedCogit >> genExtTrapIfNotInstanceOfBehaviorsBytecode [
SimpleStackBasedCogit >> genExtUnconditionalJump [
"242 11110010 i i i i i i i i Jump i i i i i i i i (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
| distance target |
distance := byte1 + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) << 8).
distance := byte1 + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) bitShift: 8).
self assert: distance = (self v4: (self generatorAt: byte0)
Long: bytecodePC
Branch: (extA ~= 0 ifTrue: [1] ifFalse: [0]) + (extB ~= 0 ifTrue: [1] ifFalse: [0])
Expand Down Expand Up @@ -3956,7 +3956,7 @@ SimpleStackBasedCogit >> v4: descriptor Long: pc Branch: nExts Distance: aMethod
self assert: nExts >= 0.
self parseV4Exts: nExts priorTo: pc in: aMethodObj into: [:ea :eb| extBValue := eb].
^(objectMemory fetchByte: pc + 1 ofObject: aMethodObj)
+ (extBValue << 8)
+ (extBValue bitShift: 8)
]
{ #category : #'span functions' }
Expand Down
4 changes: 2 additions & 2 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -5504,7 +5504,7 @@ StackInterpreter >> extPushFullClosureBytecode [
StackInterpreter >> extPushIntegerBytecode [
"229 11100101 i i i i i i i i Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
| value |
value := self fetchByte + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) << 8).
value := self fetchByte + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) bitShift: 8).
self fetchNextBytecode.
extB := 0.
self internalPush: (objectMemory integerObjectOf: value)
Expand Down Expand Up @@ -5814,7 +5814,7 @@ StackInterpreter >> extUnconditionalJump [
"242 11110010 i i i i i i i i Jump i i i i i i i i (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
| byte offset |
byte := self fetchByte.
offset := byte + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) << 8).
offset := byte + ((extB > 127 ifTrue: [extB - 256] ifFalse: [extB]) bitShift: 8).
extB := 0.
localIP := localIP + offset.
self ifBackwardsCheckForEvents: offset.
Expand Down

0 comments on commit ca0eca2

Please sign in to comment.