Skip to content

Commit

Permalink
Simplify generation of druid conditional jumps
Browse files Browse the repository at this point in the history
  • Loading branch information
guillep committed Jul 6, 2023
1 parent dd7c99c commit 9791660
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 16 deletions.
4 changes: 3 additions & 1 deletion smalltalksrc/VMMaker/Integer.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,9 @@ Integer >> asUnsignedInteger [
"Since the simulator deals with positive integers most of the time we assert that the receiver is greater than zero.
But one major exception is stack pointers in the StackInterpreterSimulator, which are negative. So don't fail
if the sender is a StackInterpreter and the receiver could be a stack pointer."
^ thisContext sender receiver objectMemory wordSize = 8

^ (thisContext findMethodContextSuchThat: [ :e |
e receiver respondsTo: #wordSize ]) receiver wordSize = 8
ifTrue: [ self signedIntToLong64 ]
ifFalse: [ self signedIntToLong ]
]
Expand Down
38 changes: 23 additions & 15 deletions smalltalksrc/VMMaker/StackInterpreter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -7576,6 +7576,18 @@ StackInterpreter >> internalMustBeBoolean [
self normalSend
]

{ #category : #'return bytecodes' }
StackInterpreter >> internalMustBeBoolean: aBoolean [
<inline: true>

"Push the boolean to send it the mustBeBoolean message"
self push: aBoolean.

messageSelector := objectMemory splObj: SelectorMustBeBoolean.
argumentCount := 0.
self normalSend
]

{ #category : #'interpreter shell' }
StackInterpreter >> interpret [
"This is the main interpreter loop. It normally loops forever, fetching and executing bytecodes. When running in the context of a browser plugin VM, however, it must return control to the browser periodically. This should done only when the state of the currently running Squeak thread is safely stored in the object heap. Since this is the case at the moment that a check for interrupts is performed, that is when we return to the browser if it is time to do so. Interrupt checks happen quite frequently."
Expand Down Expand Up @@ -8234,30 +8246,26 @@ StackInterpreter >> jumplfFalseBy: offset [

| boolean |
boolean := self stackTop.
self pop: 1.
boolean = objectMemory falseObject
ifTrue: [
self pop: 1.
self jump: offset ]
ifFalse: [
boolean = objectMemory trueObject ifFalse: [
^ self internalMustBeBoolean ].
self pop: 1.
self fetchNextBytecode ].
ifTrue: [ self jump: offset ]
ifFalse: [
boolean = objectMemory trueObject ifFalse: [
^ self internalMustBeBoolean: boolean ].
self fetchNextBytecode ]
]

{ #category : #'jump bytecodes' }
StackInterpreter >> jumplfTrueBy: offset [

| boolean |
boolean := self stackTop.
self pop: 1.
boolean = objectMemory trueObject
ifTrue: [
self pop: 1.
self jump: offset ]
ifFalse: [
boolean = objectMemory falseObject ifFalse: [
^ self internalMustBeBoolean ].
self pop: 1.
ifTrue: [ self jump: offset ]
ifFalse: [
boolean = objectMemory falseObject ifFalse: [
^ self internalMustBeBoolean: boolean ].
self fetchNextBytecode ]
]

Expand Down

0 comments on commit 9791660

Please sign in to comment.