@@ -5394,7 +5394,7 @@ StackInterpreter >> extJumpIfFalse [
53945394	byte := self fetchByte.
53955395	offset := byte + (extB << 8).
53965396	numExtB := extB := extA := 0.
5397- 	self jumplfFalseBy : offset
5397+ 	self jumpIfFalseBy : offset
53985398]
53995399
54005400{ #category : 'jump bytecodes' }
@@ -5404,7 +5404,7 @@ StackInterpreter >> extJumpIfTrue [
54045404	byte := self fetchByte.
54055405	offset := byte + (extB << 8).
54065406	numExtB := extB := extA := 0.
5407- 	self jumplfTrueBy : offset
5407+ 	self jumpIfTrueBy : offset
54085408]
54095409
54105410{ #category : 'miscellaneous bytecodes' }
@@ -8399,6 +8399,34 @@ StackInterpreter >> jumpBinaryInlinePrimitive: primIndex [
83998399	self pop: 2
84008400]
84018401
8402+ { #category : 'jump bytecodes' }
8403+ StackInterpreter >> jumpIfFalseBy: offset [
8404+ 
8405+ 	| boolean |
8406+ 	boolean := self stackTop.
8407+ 	boolean = objectMemory falseObject
8408+ 		ifTrue: [ self jump: offset ]
8409+ 		ifFalse: [ 
8410+ 			boolean = objectMemory trueObject ifFalse: [ 
8411+ 				^ self internalMustBeBoolean ].
8412+ 			self fetchNextBytecode ].
8413+ 	self pop: 1
8414+ ]
8415+ 
8416+ { #category : 'jump bytecodes' }
8417+ StackInterpreter >> jumpIfTrueBy: offset [
8418+ 
8419+ 	| boolean |
8420+ 	boolean := self stackTop.
8421+ 	boolean = objectMemory trueObject
8422+ 		ifTrue: [ self jump: offset ]
8423+ 		ifFalse: [ 
8424+ 			boolean = objectMemory falseObject ifFalse: [ 
8425+ 				^ self internalMustBeBoolean ].
8426+ 			self fetchNextBytecode ].
8427+ 	self pop: 1
8428+ ]
8429+ 
84028430{ #category : 'sista bytecodes' }
84038431StackInterpreter >> jumpTrinaryInlinePrimitive: primIndex [
84048432
@@ -8470,34 +8498,6 @@ StackInterpreter >> jumpUnaryInlinePrimitive: primIndex [
84708498	^ self unknownInlinePrimitive
84718499]
84728500
8473- { #category : 'jump bytecodes' }
8474- StackInterpreter >> jumplfFalseBy: offset [
8475- 
8476- 	| boolean |
8477- 	boolean := self stackTop.
8478- 	boolean = objectMemory falseObject
8479- 		ifTrue: [ self jump: offset ]
8480- 		ifFalse: [ 
8481- 			boolean = objectMemory trueObject ifFalse: [ 
8482- 				^ self internalMustBeBoolean ].
8483- 			self fetchNextBytecode ].
8484- 	self pop: 1
8485- ]
8486- 
8487- { #category : 'jump bytecodes' }
8488- StackInterpreter >> jumplfTrueBy: offset [
8489- 
8490- 	| boolean |
8491- 	boolean := self stackTop.
8492- 	boolean = objectMemory trueObject
8493- 		ifTrue: [ self jump: offset ]
8494- 		ifFalse: [ 
8495- 			boolean = objectMemory falseObject ifFalse: [ 
8496- 				^ self internalMustBeBoolean ].
8497- 			self fetchNextBytecode ].
8498- 	self pop: 1
8499- ]
8500- 
85018501{ #category : 'debug printing' }
85028502StackInterpreter >> lengthOfNameOfClass: classOop [
85038503	<inline: false>
@@ -8612,13 +8612,13 @@ StackInterpreter >> long: aJumpBuf jmp: returnValue [
86128612{ #category : 'jump bytecodes' }
86138613StackInterpreter >> longJumpIfFalse [
86148614
8615- 	self jumplfFalseBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
8615+ 	self jumpIfFalseBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
86168616]
86178617
86188618{ #category : 'jump bytecodes' }
86198619StackInterpreter >> longJumpIfTrue [
86208620
8621- 	self jumplfTrueBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
8621+ 	self jumpIfTrueBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
86228622]
86238623
86248624{ #category : 'debug printing' }
@@ -13876,13 +13876,13 @@ StackInterpreter >> setupFrameForNewMethodInterpreted [
1387613876{ #category : 'jump bytecodes' }
1387713877StackInterpreter >> shortConditionalJumpFalse [
1387813878
13879- 	self jumplfFalseBy : (currentBytecode bitAnd: 7) + 1
13879+ 	self jumpIfFalseBy : (currentBytecode bitAnd: 7) + 1
1388013880]
1388113881
1388213882{ #category : 'jump bytecodes' }
1388313883StackInterpreter >> shortConditionalJumpTrue [
1388413884
13885- 	self jumplfTrueBy : (currentBytecode bitAnd: 7) + 1
13885+ 	self jumpIfTrueBy : (currentBytecode bitAnd: 7) + 1
1388613886]
1388713887
1388813888{ #category : 'simulation' }
0 commit comments