@@ -5501,7 +5501,7 @@ StackInterpreter >> extJumpIfFalse [
55015501	byte := self fetchByte.
55025502	offset := byte + (extB << 8).
55035503	numExtB := extB := extA := 0.
5504- 	self jumplfFalseBy : offset
5504+ 	self jumpIfFalseBy : offset
55055505]
55065506
55075507{ #category : 'jump bytecodes' }
@@ -5511,7 +5511,7 @@ StackInterpreter >> extJumpIfTrue [
55115511	byte := self fetchByte.
55125512	offset := byte + (extB << 8).
55135513	numExtB := extB := extA := 0.
5514- 	self jumplfTrueBy : offset
5514+ 	self jumpIfTrueBy : offset
55155515]
55165516
55175517{ #category : 'miscellaneous bytecodes' }
@@ -8444,6 +8444,34 @@ StackInterpreter >> jumpBinaryInlinePrimitive: primIndex [
84448444	self pop: 2
84458445]
84468446
8447+ { #category : 'jump bytecodes' }
8448+ StackInterpreter >> jumpIfFalseBy: offset [
8449+ 
8450+ 	| boolean |
8451+ 	boolean := self stackTop.
8452+ 	boolean = objectMemory falseObject
8453+ 		ifTrue: [ self jump: offset ]
8454+ 		ifFalse: [ 
8455+ 			boolean = objectMemory trueObject ifFalse: [ 
8456+ 				^ self internalMustBeBoolean ].
8457+ 			self fetchNextBytecode ].
8458+ 	self pop: 1
8459+ ]
8460+ 
8461+ { #category : 'jump bytecodes' }
8462+ StackInterpreter >> jumpIfTrueBy: offset [
8463+ 
8464+ 	| boolean |
8465+ 	boolean := self stackTop.
8466+ 	boolean = objectMemory trueObject
8467+ 		ifTrue: [ self jump: offset ]
8468+ 		ifFalse: [ 
8469+ 			boolean = objectMemory falseObject ifFalse: [ 
8470+ 				^ self internalMustBeBoolean ].
8471+ 			self fetchNextBytecode ].
8472+ 	self pop: 1
8473+ ]
8474+ 
84478475{ #category : 'sista bytecodes' }
84488476StackInterpreter >> jumpTrinaryInlinePrimitive: primIndex [
84498477
@@ -8515,34 +8543,6 @@ StackInterpreter >> jumpUnaryInlinePrimitive: primIndex [
85158543	^ self unknownInlinePrimitive
85168544]
85178545
8518- { #category : 'jump bytecodes' }
8519- StackInterpreter >> jumplfFalseBy: offset [
8520- 
8521- 	| boolean |
8522- 	boolean := self stackTop.
8523- 	boolean = objectMemory falseObject
8524- 		ifTrue: [ self jump: offset ]
8525- 		ifFalse: [ 
8526- 			boolean = objectMemory trueObject ifFalse: [ 
8527- 				^ self internalMustBeBoolean ].
8528- 			self fetchNextBytecode ].
8529- 	self pop: 1
8530- ]
8531- 
8532- { #category : 'jump bytecodes' }
8533- StackInterpreter >> jumplfTrueBy: offset [
8534- 
8535- 	| boolean |
8536- 	boolean := self stackTop.
8537- 	boolean = objectMemory trueObject
8538- 		ifTrue: [ self jump: offset ]
8539- 		ifFalse: [ 
8540- 			boolean = objectMemory falseObject ifFalse: [ 
8541- 				^ self internalMustBeBoolean ].
8542- 			self fetchNextBytecode ].
8543- 	self pop: 1
8544- ]
8545- 
85468546{ #category : 'message sending' }
85478547StackInterpreter >> justActivateNewMethod: mustBeInterpreterFrame [
85488548
@@ -8714,13 +8714,13 @@ StackInterpreter >> long: aJumpBuf jmp: returnValue [
87148714{ #category : 'jump bytecodes' }
87158715StackInterpreter >> longJumpIfFalse [
87168716
8717- 	self jumplfFalseBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
8717+ 	self jumpIfFalseBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
87188718]
87198719
87208720{ #category : 'jump bytecodes' }
87218721StackInterpreter >> longJumpIfTrue [
87228722
8723- 	self jumplfTrueBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
8723+ 	self jumpIfTrueBy : ((currentBytecode bitAnd: 3) * 256) + self fetchByte.
87248724]
87258725
87268726{ #category : 'debug printing' }
@@ -13865,13 +13865,13 @@ StackInterpreter >> shadowCallStackSize [
1386513865{ #category : 'jump bytecodes' }
1386613866StackInterpreter >> shortConditionalJumpFalse [
1386713867
13868- 	self jumplfFalseBy : (currentBytecode bitAnd: 7) + 1
13868+ 	self jumpIfFalseBy : (currentBytecode bitAnd: 7) + 1
1386913869]
1387013870
1387113871{ #category : 'jump bytecodes' }
1387213872StackInterpreter >> shortConditionalJumpTrue [
1387313873
13874- 	self jumplfTrueBy : (currentBytecode bitAnd: 7) + 1
13874+ 	self jumpIfTrueBy : (currentBytecode bitAnd: 7) + 1
1387513875]
1387613876
1387713877{ #category : 'simulation' }
0 commit comments