[Pkg] The Trunk: Kernel-eem.852.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 19 18:50:41 UTC 2014


Eliot Miranda uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-eem.852.mcz

==================== Summary ====================

Name: Kernel-eem.852
Author: eem
Time: 19 May 2014, 11:49:49.951 am
UUID: 6d0add2f-b4ae-4e90-9b0d-7c938c4f4c1c
Ancestors: Kernel-eem.851

Change scanning methods in InstructionStream and
CompiledMethod to double-dispatch through
CompiledMethod>>#encoderClass to provide pluggable
multiple bytecode set support.  The sign of a method's
header chooses which of two bytecode sets are in effect,
choosing between PrimaryBytecodeSetEncoderClass
(header >= 0), and SecondaryBytecodeSetEncoderClass
(header <= 0).

=============== Diff against Kernel-eem.851 ===============

Item was changed:
  ----- Method: CompiledMethod class>>newBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive: (in category 'instance creation') -----
  newBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex
  	"Answer an instance of me. The header is specified by the message 
+ 	 arguments. The remaining parts are not as yet determined."
- 	arguments. The remaining parts are not as yet determined."
  	| largeBit primBits |
  	nTemps > 63 ifTrue:
  		[^ self error: 'Cannot compile -- too many temporary variables'].	
  	nLits > 255 ifTrue:
+ 		[^ self error: 'Cannot compile -- too many literals'].	
- 		[^ self error: 'Cannot compile -- too many literals variables'].	
  	largeBit := (nTemps + stackSize) > SmallFrame ifTrue: [1] ifFalse: [0].
  	primBits := primitiveIndex <= 16r1FF
  		ifTrue: [primitiveIndex]
  		ifFalse: ["For now the high bit of primitive no. is in the 29th bit of header"
  				primitiveIndex > 16r3FF ifTrue: [self error: 'prim num too large'].
  				(primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19)].
  
  	^trailer
  		createMethod: numberOfBytes
  		class: self
  		header: (nArgs bitShift: 24) +
  				(nTemps bitShift: 18) +
  				(largeBit bitShift: 17) +
  				(nLits bitShift: 9) +
  				primBits!

Item was changed:
  ----- Method: CompiledMethod class>>newBytes:trailerBytes:nArgs:nTemps:nStack:nLits:primitive:flag: (in category 'instance creation') -----
  newBytes: numberOfBytes trailerBytes: trailer nArgs: nArgs nTemps: nTemps nStack: stackSize nLits: nLits primitive: primitiveIndex flag: flag
  	"Answer an instance of me. The header is specified by the message 
+ 	 arguments. The remaining parts are not as yet determined."
- 	arguments. The remaining parts are not as yet determined."
  	| largeBit primBits flagBit |
  	nTemps > 63 ifTrue:
  		[^ self error: 'Cannot compile -- too many temporary variables'].	
  	nLits > 255 ifTrue:
+ 		[^ self error: 'Cannot compile -- too many literals'].	
- 		[^ self error: 'Cannot compile -- too many literals variables'].	
  	largeBit := (nTemps + stackSize) > SmallFrame ifTrue: [1] ifFalse: [0].
  
  	"For now the high bit of the primitive no. is in a high bit of the header"
  	primBits := (primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19).
  
  	flagBit := flag ifTrue: [ 1 ] ifFalse: [ 0 ].
  
- 	"Copy the source code trailer to the end"
  	^trailer
  		createMethod: numberOfBytes
  		class: self
  		header: (nArgs bitShift: 24) +
  				(nTemps bitShift: 18) +
  				(largeBit bitShift: 17) +
  				(nLits bitShift: 9) +
  				primBits +
  				(flagBit bitShift: 29)!

Item was changed:
  ----- Method: CompiledMethod>>containsBlockClosures (in category 'closures') -----
  containsBlockClosures
+ 	^self scanner scanFor: self encoderClass createClosureScanBlock!
- 	^ self scanner scanFor: [ :bc | bc = 143 "push closure bytecode" ]!

Item was changed:
  ----- Method: CompiledMethod>>header (in category 'literals') -----
  header
  	"Answer the word containing the information about the form of the 
+ 	 receiver and the form of the context needed to run the receiver.
+ 	 There are two different formats, selected by the sign bit.  These are
- 	receiver and the form of the context needed to run the receiver."
  
+ 	 Original Squeak V3:
+ 		30:sign:0 29:flag 28:prim (high bit) 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16-9:numLits 8-0:prim (low 9 bits)
+ 
+ 	 Alternate Bytecode Set
+ 		30:sign:1 29-28:accessModifier 27-24:numArgs 23-18:numTemps 17:largeFrameFlag 16:hasPrimitive 15-0:numLits
+ 
+ 	 i.e. the Alternate Bytecode Set expands the number of literals to 65535 by assuming a CallPrimitive bytecode."
+ 
  	^self objectAt: 1!

Item was changed:
  ----- Method: CompiledMethod>>isBlueBookCompiled (in category 'testing') -----
  isBlueBookCompiled
+ 	"Answer whether the receiver was compiled using the old Smalltalk-80 blocks
+ 	 compiler.  This is used to help DebuggerMethodMap choose which mechanisms
+ 	 to use to inspect (debug) activations of the receiver."
- 	"Answer whether the receiver was compiled using the closure compiler.
- 	 This is used to help DebuggerMethodMap choose which mechanisms to
- 	 use to inspect activations of the receiver.
- 	 This method answers false negatives in that it only identifies methods
- 	 that create old BlockClosures or use the new BlockClosure bytecodes.
- 	 It cannot tell if a method which uses neither the old nor the new block
- 	 bytecodes is compiled with the blue-book compiler or the new compiler.
- 	 But since methods that don't create blocks have essentially the same
- 	 code when compiled with either compiler this makes little difference."
  
+ 	^self encoderClass supportsClosures not!
- 	^((InstructionStream on: self) scanFor:
- 		[:instr |
- 		(instr >= 138 and: [instr <= 143]) ifTrue: [^false].
- 		instr = 200])
- 	   or: [(self hasLiteral: #blockCopy:)
- 		   and: [self messages includes: #blockCopy:]]!

Item was changed:
  ----- Method: CompiledMethod>>isClosureCompiled (in category 'testing') -----
  isClosureCompiled
  	"Answer whether the receiver was compiled using the closure compiler.
  	 This is used to help DebuggerMethodMap choose which mechanisms to
+ 	 use to inspect (debug) activations of the receiver."
- 	 use to inspect activations of the receiver.
- 	 This method answers false negatives in that it only identifies methods
- 	 that create new BlockClosures or use the new BlockClosure bytecodes.
- 	 But since methods that don't create blocks have essentially the same
- 	 code when compiled with either compiler this makes little difference."
  
+ 	^self encoderClass supportsClosures!
- 	^((InstructionStream on: self) scanFor: [:instr | instr >= 138 and: [instr <= 143]])
- 	   or: [(self hasLiteral: #closureCopy:copiedValues:)
- 		   and: [self messages includes: #closureCopy:copiedValues:]]!

Item was changed:
  ----- Method: CompiledMethod>>methodNode (in category 'decompiling') -----
  methodNode
  	"Return the parse tree that represents self. If parsing fails, decompile the method."
  	| aClass source |
  	aClass := self methodClass.
  	source := self
  				getSourceFor: (self selector ifNil: [self defaultSelector])
  				in: aClass.
  	^[(aClass newParser
+ 		encoderClass: self encoderClass;
- 		encoderClass: (self isBlueBookCompiled
- 						ifTrue: [EncoderForV3]
- 						ifFalse: [EncoderForV3PlusClosures]);
  		parse: source class: aClass)
  			sourceText: source;
  			yourself]
  		on: SyntaxErrorNotification
+ 		do: [:ex | ex return: self decompileWithTemps]!
- 		do: [:ex | ex return: self decompileWithTemps].!

Item was changed:
  ----- Method: CompiledMethod>>numLiterals (in category 'accessing') -----
  numLiterals
  	"Answer the number of literals used by the receiver."
+ 	| header |
+ 	^(header := self header) < 0
+ 		ifTrue: [header bitAnd: 65535]
+ 		ifFalse: [(header bitShift: -9) bitAnd: 16rFF]!
- 	
- 	^ (self header bitShift: -9) bitAnd: 16rFF!

Item was changed:
  ----- Method: CompiledMethod>>primitive (in category 'accessing') -----
  primitive
  	"Answer the primitive index associated with the receiver.
+ 	 Zero indicates that this is not a primitive method.
+ 	 In the original header format we currently allow 10 bits of primitive index, but they are
+ 	 in two places for backward compatibility.  In the new format the primitive index is in the
+ 	 last two bytes of a three byte callPrimitive: bytecode. The time to unpack is negligible,
+ 	 since the derived primitive function pointer full index is stored in the method cache."
+ 	| header initialPC |
+ 	^(header := self header) < 0
+ 		ifTrue:
+ 			[(header anyMask: 65536) "Is the hasPrimitive? flag set?"
+ 				ifTrue: [(self at: (initialPC := self initialPC) + 1) + ((self at: initialPC + 2) bitShift: 8)]
+ 				ifFalse: [0]]
+ 		ifFalse:
+ 			[(header bitAnd: 16r1FF) + ((header bitShift: -19) bitAnd: 16r200)]!
- 	Zero indicates that this is not a primitive method.
- 	We currently allow 10 bits of primitive index, but they are in two places
- 	for  backward compatibility.  The time to unpack is negligible,
- 	since the reconstituted full index is stored in the method cache."
- 	| primBits |
- 	primBits := self header bitAnd: 16r100001FF.
- 	
- 	^ (primBits bitAnd: 16r1FF) + (primBits bitShift: -19)
- !

Item was changed:
  ----- Method: CompiledMethod>>readsField: (in category 'scanning') -----
  readsField: varIndex 
+ 	"Answer whether the receiver loads the instance variable indexed by the  argument."
- 	"Answer whether the receiver loads the instance variable indexed by the 
- 	 argument."
- 	"eem 5/24/2008 Rewritten to no longer assume the compiler uses the
- 	 most compact encoding available (for EncoderForLongFormV3 support)."
  	| varIndexCode scanner |
  	varIndexCode := varIndex - 1.
+ 	self isQuick ifTrue:
+ 		[^self isReturnField and: [self returnField = varIndexCode]].
+ 	scanner := InstructionStream on: self.
+ 	^scanner scanFor:(self encoderClass instVarReadScanBlockFor: varIndexCode using: scanner)!
- 	self isReturnField ifTrue: [^self returnField = varIndexCode].
- 	^(scanner := InstructionStream on: self) scanFor:
- 		[:b|
- 		b < 16
- 			ifTrue: [b = varIndexCode]
- 			ifFalse:
- 				[b = 128
- 					ifTrue: [scanner followingByte = varIndexCode and: [varIndexCode <= 63]]
- 					ifFalse:
- 						[b = 132
- 						 and: [(scanner followingByte between: 64 and: 95)
- 						 and: [scanner thirdByte = varIndexCode]]]]]!

Item was changed:
  ----- Method: CompiledMethod>>readsRef: (in category 'scanning') -----
+ readsRef: variableBinding 
+ 	"Answer whether the receiver reads the value of the argument."
- readsRef: literalAssociation 
- 	"Answer whether the receiver loads the argument."
  	"eem 5/24/2008 Rewritten to no longer assume the compler uses the
  	 most compact encoding available (for EncoderForLongFormV3 support)."
  	| litIndex scanner |
+ 	(litIndex := self indexOfLiteral: variableBinding) = 0 ifTrue:
- 	(litIndex := self indexOfLiteral: literalAssociation) = 0 ifTrue:
  		[^false].
+ 	scanner := InstructionStream on: self.
+ 	^scanner scanFor: (self encoderClass bindingReadScanBlockFor: litIndex - 1 using: scanner)!
- 	litIndex := litIndex - 1.
- 	^(scanner := InstructionStream on: self) scanFor:
- 		[:b|
- 		b >= 64
- 		and:
- 			[b <= 95
- 				ifTrue: [b - 64 = litIndex]
- 				ifFalse:
- 					[b = 128
- 						ifTrue: [scanner followingByte - 192 = litIndex]
- 						ifFalse:
- 							[b = 132
- 							 and: [(scanner followingByte between: 128 and: 159)
- 							 and: [scanner thirdByte = litIndex]]]]]]!

Item was removed:
- ----- Method: CompiledMethod>>scanLongLoad: (in category 'scanning') -----
- scanLongLoad: extension 
- 	"Answer whether the receiver contains a long load whose extension is the 
- 	argument."
- 
- 	| scanner |
- 	scanner := InstructionStream on: self.
- 	^scanner scanFor: [:instr | instr = 128 and: [scanner followingByte = extension]]!

Item was removed:
- ----- Method: CompiledMethod>>scanLongStore: (in category 'scanning') -----
- scanLongStore: extension 
- 	"Answer whether the receiver contains a long store whose extension is 
- 	the argument."
- 	| scanner |
- 	scanner := InstructionStream on: self.
- 	^scanner scanFor: 
- 		[:instr |  (instr = 129 or: [instr = 130]) and: [scanner followingByte = extension]]!

Item was removed:
- ----- Method: CompiledMethod>>scanVeryLongLoad:offset: (in category 'scanning') -----
- scanVeryLongLoad: extension offset: offset
- 	"Answer whether the receiver contains a long load whose extension is the 
- 	argument."
- 	| scanner |
- 	scanner := InstructionStream on: self.
- 	^ scanner scanFor: [:instr | (instr = 132 and: [scanner followingByte = extension])
- 											and: [scanner thirdByte = offset]]!

Item was removed:
- ----- Method: CompiledMethod>>scanVeryLongStore:offset: (in category 'scanning') -----
- scanVeryLongStore: extension offset: offset
- 	"Answer whether the receiver contains a long load with the given offset.
- 	Note that the constant +32 is the known difference between a
- 	store and a storePop for instVars, and it will always fail on literal variables,
- 	but these only use store (followed by pop) anyway."
- 	| scanner |
- 	scanner := InstructionStream on: self.
- 	^scanner scanFor:
- 		[:instr | | ext |
- 		(instr = 132 and: [(ext := scanner followingByte) = extension
- 											or: ["might be a store/pop into rcvr"
- 												ext = (extension+32)]])
- 		and: [scanner thirdByte = offset]]!

Item was changed:
  ----- Method: CompiledMethod>>sendsToSuper (in category 'scanning') -----
  sendsToSuper
  	"Answer whether the receiver sends any message to super."
  	| scanner |
  	scanner := InstructionStream on: self.
+ 	^scanner scanFor: (self encoderClass superSendScanBlockUsing: scanner)!
- 	^ scanner scanFor: 
- 		[:instr |  instr = 16r85 or: [instr = 16r84
- 						and: [scanner followingByte between: 16r20 and: 16r3F]]]!

Item was changed:
  ----- Method: CompiledMethod>>usesClosureBytecodes (in category 'testing') -----
  usesClosureBytecodes
  	"Answer whether the receiver was compiled using the closure compiler.
  	 This is used to help DebuggerMethodMap choose which mechanisms to
  	 use to inspect activations of the receiver.
  	 This method answers false negatives in that it only identifies methods
  	 that use the new BlockClosure bytecodes.
  	 But since methods that don't create blocks have essentially the same
  	 code when compiled with either compiler this makes little difference."
  
+ 	^self encoderClass supportsClosures!
- 	^(InstructionStream on: self) scanFor: [:instr | instr >= 138 and: [instr <= 143]]!

Item was changed:
  ----- Method: CompiledMethod>>writesField: (in category 'scanning') -----
  writesField: varIndex
  	"Answer whether the receiver stores into the instance variable indexed
  	 by the argument."
- 	"eem 5/24/2008 Rewritten to no longer assume the compler uses the
- 	 most compact encoding available (for EncoderForLongFormV3 support)."
  
+ 	| scanner |
- 	| varIndexCode scanner |
  	self isQuick ifTrue: [^false].
+ 	scanner := InstructionStream on: self.
+ 	^scanner scanFor: (self encoderClass instVarWriteScanBlockFor: varIndex - 1 using: scanner)!
- 	varIndexCode := varIndex - 1.
- 	^(scanner := InstructionStream on: self) scanFor:
- 		[:b|
- 		b >= 96
- 		and: [b <= 103
- 				ifTrue: [b - 96 = varIndexCode]
- 				ifFalse:
- 					[(b = 129 or: [b = 130])
- 						ifTrue: [scanner followingByte = varIndexCode and: [varIndexCode <= 63]]
- 						ifFalse:
- 							[b = 132
- 							 and: [(scanner followingByte between: 160 and: 223)
- 							 and: [scanner thirdByte = varIndexCode]]]]]]!

Item was changed:
  ----- Method: CompiledMethod>>writesRef: (in category 'scanning') -----
+ writesRef: variableBinding 
+ 	"Answer whether the receiver writes the value of the argument."
- writesRef: literalAssociation 
- 	"Answer whether the receiver stores into the argument."
  	"eem 5/24/2008 Rewritten to no longer assume the compler uses the
  	 most compact encoding available (for EncoderForLongFormV3 support)."
  	| litIndex scanner |
+ 	(litIndex := self indexOfLiteral: variableBinding) = 0 ifTrue:
- 	(litIndex := self indexOfLiteral: literalAssociation) = 0 ifTrue:
  		[^false].
+ 	scanner := InstructionStream on: self.
+ 	^scanner scanFor: (self encoderClass bindingWriteScanBlockFor: litIndex - 1 using: scanner)!
- 	litIndex := litIndex - 1.
- 	^(scanner := InstructionStream on: self) scanFor:
- 		[:b|
- 		(b = 129 or: [b = 130])
- 			ifTrue: [scanner followingByte - 192 = litIndex]
- 			ifFalse:
- 				[b = 132
- 				 and: [scanner followingByte >= 224
- 				 and: [scanner thirdByte = litIndex]]]]!

Item was changed:
  ----- Method: InstructionStream>>followingPc (in category 'scanning') -----
  followingPc
  	"Answer the pc of the following bytecode."
+ 	| method |
+ 	method := self method.
+ 	^pc + (method encoderClass bytecodeSize: (method at: pc))!
- 
- 	^self nextPc: (self method at: pc)!

Item was removed:
- ----- Method: InstructionStream>>interpret (in category 'decoding') -----
- interpret
- 
- 	[self atEnd] whileFalse: [self interpretNextInstructionFor: self]!

Item was changed:
  ----- Method: InstructionStream>>interpretJump (in category 'decoding') -----
  interpretJump
+ 	"If the instruction at pc is an unconditional jump, interpret it, advancing the pc,
+ 	 and answering the jump distance. Otherwise answer nil."
+ 	^self method encoderClass interpretJumpIn: self!
- 
- 	| byte |
- 	byte := self method at: pc.
- 	(byte between: 144 and: 151) ifTrue:
- 		[pc := pc + 1. ^byte - 143].
- 	(byte between: 160 and: 167) ifTrue:
- 		[pc := pc + 2. ^(byte - 164) * 256 + (self method at: pc - 1)].
- 	^nil!

Item was changed:
  ----- Method: InstructionStream>>interpretJumpIfCond (in category 'decoding') -----
  interpretJumpIfCond
+ 	"If the instruction at pc is a conditional jump, interpret it, advancing the pc,
+ 	 and answering the jump distance. Otherwise answer nil."
+ 	^self method encoderClass interpretJumpIfCondIn: self!
- 
- 	| byte |
- 	byte := self method at: pc.
- 	(byte between: 152 and: 159) ifTrue:
- 		[pc := pc + 1. ^byte - 151].
- 	(byte between: 168 and: 175) ifTrue:
- 		[pc := pc + 2. ^(byte bitAnd: 3) * 256 + (self method at: pc - 1)].
- 	^nil!

Item was changed:
  ----- Method: InstructionStream>>interpretNextInstructionFor: (in category 'decoding') -----
+ interpretNextInstructionFor: client
+ 	"Send to the argument, client, a message that specifies the type of the next instruction."
- interpretNextInstructionFor: client 
- 	"Send to the argument, client, a message that specifies the type of the 
- 	next instruction."
  
+ 	^self method encoderClass interpretNextInstructionFor: client in: self!
- 	| byte type offset method |
- 	method := self method.  
- 	byte := method at: pc.
- 	type := byte // 16.  
- 	offset := byte \\ 16.  
- 	pc := pc+1.
- 	"We do an inline binary search on each of the possible 16 values of type:
- 	The old, cleaner but slowe code is retained as a comment below"
- 	type < 8
- 	ifTrue: [type < 4
- 				ifTrue: [type < 2
- 						ifTrue: [type < 1
- 								ifTrue: ["type = 0"
- 									^ client pushReceiverVariable: offset]
- 								ifFalse: ["type = 1"
- 									^ client pushTemporaryVariable: offset]]
- 						ifFalse: [type < 3
- 								ifTrue: ["type = 2"
- 									^ client
- 										pushConstant: (method literalAt: offset + 1)]
- 								ifFalse: ["type = 3"
- 									^ client
- 										pushConstant: (method literalAt: offset + 17)]]]
- 				ifFalse: [type < 6
- 						ifTrue: [type < 5
- 								ifTrue: ["type = 4"
- 									^ client
- 										pushLiteralVariable: (method literalAt: offset + 1)]
- 								ifFalse: ["type = 5"
- 									^ client
- 										pushLiteralVariable: (method literalAt: offset + 17)]]
- 						ifFalse: [type < 7
- 								ifTrue: ["type = 6"
- 									offset < 8
- 										ifTrue: [^ client popIntoReceiverVariable: offset]
- 										ifFalse: [^ client popIntoTemporaryVariable: offset - 8]]
- 								ifFalse: ["type = 7"
- 									offset = 0
- 										ifTrue: [^ client pushReceiver].
- 									offset < 8
- 										ifTrue: [^ client
- 												pushConstant: (SpecialConstants at: offset)].
- 									offset = 8
- 										ifTrue: [^ client methodReturnReceiver].
- 									offset < 12
- 										ifTrue: [^ client
- 												methodReturnConstant: (SpecialConstants at: offset - 8)].
- 									offset = 12
- 										ifTrue: [^ client methodReturnTop].
- 									offset = 13
- 										ifTrue: [^ client blockReturnTop].
- 									offset > 13
- 										ifTrue: [^ self error: 'unusedBytecode']]]]]
- 		ifFalse: [type < 12
- 				ifTrue: [type < 10
- 						ifTrue: [type < 9
- 								ifTrue: ["type = 8"
- 									^ self
- 										interpretExtension: offset
- 										in: method
- 										for: client]
- 								ifFalse: ["type = 9 (short jumps)"
- 									offset < 8
- 										ifTrue: [^ client jump: offset + 1].
- 									^ client jump: offset - 8 + 1 if: false]]
- 						ifFalse: [type < 11
- 								ifTrue: ["type = 10 (long jumps)"
- 									byte := method at: pc.
- 									pc := pc + 1.
- 									offset < 8
- 										ifTrue: [^ client jump: offset - 4 * 256 + byte].
- 									^ client jump: (offset bitAnd: 3)
- 											* 256 + byte if: offset < 12]
- 								ifFalse: ["type = 11"
- 									^ client
- 										send: (Smalltalk specialSelectorAt: offset + 1)
- 										super: false
- 										numArgs: (Smalltalk specialNargsAt: offset + 1)]]]
- 				ifFalse: [type = 12
- 						ifTrue: [^ client
- 								send: (Smalltalk specialSelectorAt: offset + 17)
- 								super: false
- 								numArgs: (Smalltalk specialNargsAt: offset + 17)]
- 						ifFalse: ["type = 13, 14 or 15"
- 							^ client
- 								send: (method literalAt: offset + 1)
- 								super: false
- 								numArgs: type - 13]]].
- 
- 
- "    old code 
- 	type=0 ifTrue: [^client pushReceiverVariable: offset].
- 	type=1 ifTrue: [^client pushTemporaryVariable: offset].
- 	type=2 ifTrue: [^client pushConstant: (method literalAt: offset+1)].
- 	type=3 ifTrue: [^client pushConstant: (method literalAt: offset+17)].
- 	type=4 ifTrue: [^client pushLiteralVariable: (method literalAt: offset+1)].
- 	type=5 ifTrue: [^client pushLiteralVariable: (method literalAt: offset+17)].
- 	type=6 
- 		ifTrue: [offset<8
- 					ifTrue: [^client popIntoReceiverVariable: offset]
- 					ifFalse: [^client popIntoTemporaryVariable: offset-8]].
- 	type=7
- 		ifTrue: [offset=0 ifTrue: [^client pushReceiver].
- 				offset<8 ifTrue: [^client pushConstant: (SpecialConstants at: offset)].
- 				offset=8 ifTrue: [^client methodReturnReceiver].
- 				offset<12 ifTrue: [^client methodReturnConstant: 
- 												(SpecialConstants at: offset-8)].
- 				offset=12 ifTrue: [^client methodReturnTop].
- 				offset=13 ifTrue: [^client blockReturnTop].
- 				offset>13 ifTrue: [^self error: 'unusedBytecode']].
- 	type=8 ifTrue: [^self interpretExtension: offset in: method for: client].
- 	type=9
- 		ifTrue:  short jumps
- 			[offset<8 ifTrue: [^client jump: offset+1].
- 			^client jump: offset-8+1 if: false].
- 	type=10 
- 		ifTrue:  long jumps
- 			[byte:= method at: pc.  pc:= pc+1.
- 			offset<8 ifTrue: [^client jump: offset-4*256 + byte].
- 			^client jump: (offset bitAnd: 3)*256 + byte if: offset<12].
- 	type=11 
- 		ifTrue: 
- 			[^client 
- 				send: (Smalltalk specialSelectorAt: offset+1) 
- 				super: false
- 				numArgs: (Smalltalk specialNargsAt: offset+1)].
- 	type=12 
- 		ifTrue: 
- 			[^client 
- 				send: (Smalltalk specialSelectorAt: offset+17) 
- 				super: false
- 				numArgs: (Smalltalk specialNargsAt: offset+17)].
- 	type>12
- 		ifTrue: 
- 			[^client send: (method literalAt: offset+1) 
- 					super: false
- 					numArgs: type-13]"!

Item was added:
+ ----- Method: InstructionStream>>interpretNextV3ClosuresInstructionFor: (in category 'decoding - private - v3 plus closures') -----
+ interpretNextV3ClosuresInstructionFor: client 
+ 	"Send to the argument, client, a message that specifies the type of the 
+ 	 next instruction."
+ 
+ 	| byte type offset method |
+ 	method := self method.  
+ 	byte := method at: pc.
+ 	type := byte // 16.  
+ 	offset := byte \\ 16.  
+ 	pc := pc+1.
+ 	"We do an inline binary search on each of the possible 16 values of type."
+ 	type < 8 ifTrue:
+ 		[type < 4 ifTrue:
+ 			[type < 2 ifTrue:
+ 				[type = 0 ifTrue:
+ 					[^ client pushReceiverVariable: offset].
+ 				^ client pushTemporaryVariable: offset].				"type = 1"
+ 			type = 2 ifTrue: 
+ 				[^ client pushConstant: (method literalAt: offset + 1)].
+ 			^ client pushConstant: (method literalAt: offset + 17)].		"type = 3"
+ 		type < 6 ifTrue:
+ 			[type = 4 ifTrue:
+ 				[^ client pushLiteralVariable: (method literalAt: offset + 1)].
+ 			^ client pushLiteralVariable: (method literalAt: offset + 17)]."type = 5"
+ 		type = 6 ifTrue:
+ 			[offset < 8 ifTrue:
+ 				[^ client popIntoReceiverVariable: offset].
+ 			^ client popIntoTemporaryVariable: offset - 8].
+ 		"type = 7"
+ 		offset = 0 ifTrue: [^ client pushReceiver].
+ 		offset < 8 ifTrue: [^ client pushConstant: (SpecialConstants at: offset)].
+ 		offset = 8 ifTrue: [^ client methodReturnReceiver].
+ 		offset < 12 ifTrue: [^ client methodReturnConstant: (SpecialConstants at: offset - 8)].
+ 		offset = 12 ifTrue: [^ client methodReturnTop].
+ 		offset = 13 ifTrue: [^ client blockReturnTop].
+ 		offset > 13 ifTrue: [^ self error: 'unusedBytecode']].
+ 	type < 12 ifTrue:
+ 		[type < 10 ifTrue:
+ 			[type = 8 ifTrue:
+ 				[^ self
+ 					interpretV3ClosuresExtension: offset
+ 					in: method
+ 					for: client].
+ 			"type = 9 (short jumps)"
+ 			offset < 8 ifTrue: [^ client jump: offset + 1].
+ 			^ client jump: offset - 8 + 1 if: false].
+ 		type = 10 ifTrue: "(long jumps)"
+ 			[byte := method at: pc.
+ 			pc := pc + 1.
+ 			offset < 8 ifTrue: [^ client jump: offset - 4 * 256 + byte].
+ 			^ client jump: (offset bitAnd: 3) * 256 + byte if: offset < 12].
+ 		"type = 11; arithmetic special selector sends"
+ 		^ client
+ 			send: (Smalltalk specialSelectorAt: offset + 1)
+ 			super: false
+ 			numArgs: (Smalltalk specialNargsAt: offset + 1)].
+ 		type = 12 ifTrue: "non-arithmetic special selector sends"
+ 			[^ client
+ 				send: (Smalltalk specialSelectorAt: offset + 17)
+ 				super: false
+ 				numArgs: (Smalltalk specialNargsAt: offset + 17)].
+ 	"type = 13, 14 or 15"
+ 	^ client
+ 		send: (method literalAt: offset + 1)
+ 		super: false
+ 		numArgs: type - 13 "0, 1 & 2"!

Item was added:
+ ----- Method: InstructionStream>>interpretNextV3InstructionFor: (in category 'decoding - private - v3 plus closures') -----
+ interpretNextV3InstructionFor: client 
+ 	"Send to the argument, client, a message that specifies the type of the 
+ 	 next instruction."
+ 
+ 	| byte type offset method |
+ 	method := self method.  
+ 	byte := method at: pc.
+ 	type := byte // 16.  
+ 	offset := byte \\ 16.  
+ 	pc := pc+1.
+ 	"We do an inline binary search on each of the possible 16 values of type."
+ 	type < 8 ifTrue:
+ 		[type < 4 ifTrue:
+ 			[type < 2 ifTrue:
+ 				[type = 0 ifTrue:
+ 					[^ client pushReceiverVariable: offset].
+ 				^ client pushTemporaryVariable: offset].				"type = 1"
+ 			type = 2 ifTrue: 
+ 				[^ client pushConstant: (method literalAt: offset + 1)].
+ 			^ client pushConstant: (method literalAt: offset + 17)].		"type = 3"
+ 		type < 6 ifTrue:
+ 			[type = 4 ifTrue:
+ 				[^ client pushLiteralVariable: (method literalAt: offset + 1)].
+ 			^ client pushLiteralVariable: (method literalAt: offset + 17)]."type = 5"
+ 		type = 6 ifTrue:
+ 			[offset < 8 ifTrue:
+ 				[^ client popIntoReceiverVariable: offset].
+ 			^ client popIntoTemporaryVariable: offset - 8].
+ 		"type = 7"
+ 		offset = 0 ifTrue: [^ client pushReceiver].
+ 		offset < 8 ifTrue: [^ client pushConstant: (SpecialConstants at: offset)].
+ 		offset = 8 ifTrue: [^ client methodReturnReceiver].
+ 		offset < 12 ifTrue: [^ client methodReturnConstant: (SpecialConstants at: offset - 8)].
+ 		offset = 12 ifTrue: [^ client methodReturnTop].
+ 		offset = 13 ifTrue: [^ client blockReturnTop].
+ 		^ self error: 'unusedBytecode']. "offset = 14 & offset = 15, 126 & 127"
+ 	type < 12 ifTrue:
+ 		[type < 10 ifTrue:
+ 			[type = 8 ifTrue:
+ 				[^ self
+ 					interpretV3Extension: offset
+ 					in: method
+ 					for: client].
+ 			"type = 9 (short jumps)"
+ 			offset < 8 ifTrue: [^ client jump: offset + 1].
+ 			^ client jump: offset - 8 + 1 if: false].
+ 		type = 10 ifTrue: "(long jumps)"
+ 			[byte := method at: pc.
+ 			pc := pc + 1.
+ 			offset < 8 ifTrue: [^ client jump: offset - 4 * 256 + byte].
+ 			^ client jump: (offset bitAnd: 3) * 256 + byte if: offset < 12].
+ 		"type = 11; arithmetic special selector sends"
+ 		^ client
+ 			send: (Smalltalk specialSelectorAt: offset + 1)
+ 			super: false
+ 			numArgs: (Smalltalk specialNargsAt: offset + 1)].
+ 		type = 12 ifTrue: "non-arithmetic special selector sends"
+ 			[^ client
+ 				send: (Smalltalk specialSelectorAt: offset + 17)
+ 				super: false
+ 				numArgs: (Smalltalk specialNargsAt: offset + 17)].
+ 	"type = 13, 14 or 15"
+ 	^ client
+ 		send: (method literalAt: offset + 1)
+ 		super: false
+ 		numArgs: type - 13 "0, 1 & 2"!

Item was added:
+ ----- Method: InstructionStream>>interpretV3ClosuresExtension:in:for: (in category 'decoding - private - v3 plus closures') -----
+ interpretV3ClosuresExtension: offset in: method for: client
+ 	| type offset2 byte2 byte3 byte4 |
+ 	offset <= 6 ifTrue: 
+ 		["Extended op codes 128-134"
+ 		byte2 := method at: pc. pc := pc + 1.
+ 		offset <= 2 ifTrue:
+ 			["128-130:  extended pushes and pops"
+ 			type := byte2 // 64.
+ 			offset2 := byte2 \\ 64.
+ 			offset = 0 ifTrue: 
+ 				[type = 0 ifTrue: [^client pushReceiverVariable: offset2].
+ 				type = 1 ifTrue: [^client pushTemporaryVariable: offset2].
+ 				type = 2  ifTrue: [^client pushConstant: (method literalAt: offset2 + 1)].
+ 				type = 3 ifTrue: [^client pushLiteralVariable: (method literalAt: offset2 + 1)]].
+ 			offset = 1 ifTrue: 
+ 				[type = 0 ifTrue: [^client storeIntoReceiverVariable: offset2].
+ 				type = 1 ifTrue: [^client storeIntoTemporaryVariable: offset2].
+ 				type = 2 ifTrue: [self error: 'illegalStore'].
+ 				type = 3 ifTrue: [^client storeIntoLiteralVariable: (method literalAt: offset2 + 1)]].
+ 			offset = 2 ifTrue: 
+ 				[type = 0 ifTrue: [^client popIntoReceiverVariable: offset2].
+ 				type = 1 ifTrue: [^client popIntoTemporaryVariable: offset2].
+ 				type = 2 ifTrue: [self error: 'illegalStore'].
+ 				type = 3  ifTrue: [^client popIntoLiteralVariable: (method literalAt: offset2 + 1)]]].
+ 		"131-134: extended sends"
+ 		offset = 3 ifTrue:  "Single extended send"
+ 			[^client send: (method literalAt: byte2 \\ 32 + 1)
+ 					super: false numArgs: byte2 // 32].
+ 		offset = 4 ifTrue:    "Double extended do-anything"
+ 			[byte3 := method at: pc. pc := pc + 1.
+ 			type := byte2 // 32.
+ 			type = 0 ifTrue: [^client send: (method literalAt: byte3 + 1)
+ 									super: false numArgs: byte2 \\ 32].
+ 			type = 1 ifTrue: [^client send: (method literalAt: byte3 + 1)
+ 									super: true numArgs: byte2 \\ 32].
+ 			type = 2 ifTrue: [^client pushReceiverVariable: byte3].
+ 			type = 3 ifTrue: [^client pushConstant: (method literalAt: byte3 + 1)].
+ 			type = 4 ifTrue: [^client pushLiteralVariable: (method literalAt: byte3 + 1)].
+ 			type = 5 ifTrue: [^client storeIntoReceiverVariable: byte3].
+ 			type = 6 ifTrue: [^client popIntoReceiverVariable: byte3].
+ 			type = 7 ifTrue: [^client storeIntoLiteralVariable: (method literalAt: byte3 + 1)]].
+ 		offset = 5 ifTrue:  "Single extended send to super"
+ 			[^client send: (method literalAt: byte2 \\ 32 + 1)
+ 					super: true
+ 					numArgs: byte2 // 32].
+ 		offset = 6 ifTrue:   "Second extended send"
+ 			[^client send: (method literalAt: byte2 \\ 64 + 1)
+ 					super: false
+ 					numArgs: byte2 // 64]].
+ 	offset = 7 ifTrue: [^client doPop].
+ 	offset = 8 ifTrue: [^client doDup].
+ 	offset = 9 ifTrue: [^client pushActiveContext].
+ 	byte2 := method at: pc. pc := pc + 1.
+ 	offset = 10 ifTrue:
+ 		[^byte2 < 128
+ 			ifTrue: [client pushNewArrayOfSize: byte2]
+ 			ifFalse: [client pushConsArrayWithElements: byte2 - 128]].
+ 	offset = 11 ifTrue: [^self error: 'unusedBytecode'].
+ 	byte3 := method at: pc.  pc := pc + 1.
+ 	offset = 12 ifTrue: [^client pushRemoteTemp: byte2 inVectorAt: byte3].
+ 	offset = 13 ifTrue: [^client storeIntoRemoteTemp: byte2 inVectorAt: byte3].
+ 	offset = 14 ifTrue: [^client popIntoRemoteTemp: byte2 inVectorAt: byte3].
+ 	"offset = 15"
+ 	byte4 := method at: pc.  pc := pc + 1.
+ 	^client
+ 		pushClosureCopyNumCopiedValues: (byte2 bitShift: -4)
+ 		numArgs: (byte2 bitAnd: 16rF)
+ 		blockSize: (byte3 * 256) + byte4!

Item was added:
+ ----- Method: InstructionStream>>interpretV3Extension:in:for: (in category 'decoding - private - v3 plus closures') -----
+ interpretV3Extension: offset in: method for: client
+ 	| type offset2 byte2 byte3 |
+ 	offset <= 6 ifTrue: 
+ 		["Extended op codes 128-134"
+ 		byte2 := method at: pc. pc := pc + 1.
+ 		offset <= 2 ifTrue:
+ 			["128-130:  extended pushes and pops"
+ 			type := byte2 // 64.
+ 			offset2 := byte2 \\ 64.
+ 			offset = 0 ifTrue: 
+ 				[type = 0 ifTrue: [^client pushReceiverVariable: offset2].
+ 				type = 1 ifTrue: [^client pushTemporaryVariable: offset2].
+ 				type = 2  ifTrue: [^client pushConstant: (method literalAt: offset2 + 1)].
+ 				type = 3 ifTrue: [^client pushLiteralVariable: (method literalAt: offset2 + 1)]].
+ 			offset = 1 ifTrue: 
+ 				[type = 0 ifTrue: [^client storeIntoReceiverVariable: offset2].
+ 				type = 1 ifTrue: [^client storeIntoTemporaryVariable: offset2].
+ 				type = 2 ifTrue: [self error: 'illegalStore'].
+ 				type = 3 ifTrue: [^client storeIntoLiteralVariable: (method literalAt: offset2 + 1)]].
+ 			offset = 2 ifTrue: 
+ 				[type = 0 ifTrue: [^client popIntoReceiverVariable: offset2].
+ 				type = 1 ifTrue: [^client popIntoTemporaryVariable: offset2].
+ 				type = 2 ifTrue: [self error: 'illegalStore'].
+ 				type = 3  ifTrue: [^client popIntoLiteralVariable: (method literalAt: offset2 + 1)]]].
+ 		"131-134: extended sends"
+ 		offset = 3 ifTrue:  "Single extended send"
+ 			[^client send: (method literalAt: byte2 \\ 32 + 1)
+ 					super: false numArgs: byte2 // 32].
+ 		offset = 4 ifTrue:    "Double extended do-anything"
+ 			[byte3 := method at: pc. pc := pc + 1.
+ 			type := byte2 // 32.
+ 			type = 0 ifTrue: [^client send: (method literalAt: byte3 + 1)
+ 									super: false numArgs: byte2 \\ 32].
+ 			type = 1 ifTrue: [^client send: (method literalAt: byte3 + 1)
+ 									super: true numArgs: byte2 \\ 32].
+ 			type = 2 ifTrue: [^client pushReceiverVariable: byte3].
+ 			type = 3 ifTrue: [^client pushConstant: (method literalAt: byte3 + 1)].
+ 			type = 4 ifTrue: [^client pushLiteralVariable: (method literalAt: byte3 + 1)].
+ 			type = 5 ifTrue: [^client storeIntoReceiverVariable: byte3].
+ 			type = 6 ifTrue: [^client popIntoReceiverVariable: byte3].
+ 			type = 7 ifTrue: [^client storeIntoLiteralVariable: (method literalAt: byte3 + 1)]].
+ 		offset = 5 ifTrue:  "Single extended send to super"
+ 			[^client send: (method literalAt: byte2 \\ 32 + 1)
+ 					super: true
+ 					numArgs: byte2 // 32].
+ 		offset = 6 ifTrue:   "Second extended send"
+ 			[^client send: (method literalAt: byte2 \\ 64 + 1)
+ 					super: false
+ 					numArgs: byte2 // 64]].
+ 	offset = 7 ifTrue: [^client doPop].
+ 	offset = 8 ifTrue: [^client doDup].
+ 	offset = 9 ifTrue: [^client pushActiveContext].
+ 	^self error: 'unusedBytecode'!

Item was added:
+ ----- Method: InstructionStream>>interpretV3Jump (in category 'decoding - private - v3 plus closures') -----
+ interpretV3Jump
+ 	"If the instruction at pc is an unconditional jump, interpret it, advancing the pc,
+ 	 and answering the target pc. Otherwise answer nil."
+ 
+ 	"144-151 	10010iii 		Jump iii + 1 (i.e., 1 through 8)
+ 	 160-167 	10100iii jjjjjjjj 	Jump(iii - 4) *256+jjjjjjjj"
+ 	| byte |
+ 	byte := self method at: pc.
+ 	(byte between: 144 and: 151) ifTrue:
+ 		[pc := pc + 1.
+ 		 ^byte - 143].
+ 	(byte between: 160 and: 167) ifTrue:
+ 		[pc := pc + 2.
+ 		 ^(byte - 164) * 256 + (self method at: pc - 1)].
+ 	^nil!

Item was added:
+ ----- Method: InstructionStream>>interpretV3JumpIfCond (in category 'decoding - private - v3 plus closures') -----
+ interpretV3JumpIfCond
+ 	"If the instruction at pc is a conditional jump, interpret it, advancing the pc,
+ 	 and answering the jump distance. Otherwise answer nil."
+ 
+ 	"152-159 	10011iii 		Pop and Jump 0n False iii +1 (i.e., 1 through 8)
+ 	 168-171 	101010ii jjjjjjjj 	Pop and Jump On True ii *256+jjjjjjjj
+ 	 172-175 	101011ii jjjjjjjj 	Pop and Jump On False ii *256+jjjjjjjj"
+ 	| byte |
+ 	byte := self method at: pc.
+ 	(byte between: 152 and: 159) ifTrue:
+ 		[pc := pc + 1.
+ 		 ^byte - 151].
+ 	(byte between: 168 and: 175) ifTrue:
+ 		[pc := pc + 2.
+ 		 ^(byte bitAnd: 3) * 256 + (self method at: pc - 1)].
+ 	^nil!

Item was changed:
  ----- Method: InstructionStream>>nextPc: (in category 'private') -----
  nextPc: currentByte
  	"Answer the pc of the next bytecode following the current one, given the current bytecode.."
  
+ 	^pc + (self method encoderClass bytecodeSize: currentByte)!
- 	| type |
- 	type := currentByte // 16.
- 	^type = 8 "extensions"
- 				ifTrue: [pc + (#(2 2 2 2 3 2 2 1 1 1 2 1 3 3 3 4) at: currentByte \\ 16 + 1)]
- 				ifFalse: [type = 10 "long jumps"
- 							ifTrue: [pc + 2]
- 							ifFalse: [pc + 1]]!

Item was changed:
  ----- Method: InstructionStream>>scanFor: (in category 'scanning') -----
  scanFor: scanBlock
  	"Check all bytecode instructions with scanBlock, answer true if scanBlock answers true.
  	This can be used to, e.g., check whether a method contains 'push closure' bytecodes like this:
  	aMethod scanFor: [ :b | b = 143 ]"
  
+ 	| method encoderClass end byte |
- 	| method end byte |
  	method := self method.
  	end := method endPC.
+ 	encoderClass := method encoderClass.
  	[pc <= end] whileTrue: 
  		[(scanBlock value: (byte := method at: pc)) ifTrue:
  			[^true].
+ 		 pc := pc + (encoderClass bytecodeSize: byte)].
- 		 pc := self nextPc: byte].
  	^false!

Item was changed:
  ----- Method: InstructionStream>>willBlockReturn (in category 'testing') -----
  willBlockReturn
+ 	"Answer whether the next bytecode is a return."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isBlockReturnAt: pc in: method!
- 
- 	^ (self method at: pc) = Encoder blockReturnCode!

Item was changed:
  ----- Method: InstructionStream>>willJump (in category 'testing') -----
  willJump
+ 	"Answer whether the next bytecode is an uncoinditional jump."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isJumpAt: pc in: method!
- 	"unconditionally"
- 
- 	| byte |
- 	byte := self method at: pc.
- 	^ (byte between: 144 and: 151) or: [byte between: 160 and: 167]!

Item was changed:
  ----- Method: InstructionStream>>willJumpIfFalse (in category 'testing') -----
  willJumpIfFalse
  	"Answer whether the next bytecode is a jump-if-false."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isBranchIfFalseAt: pc in: method!
- 
- 	| byte |
- 	byte := self method at: pc.
- 	^(byte between: 152 and: 159) or: [byte between: 172 and: 175]!

Item was changed:
  ----- Method: InstructionStream>>willJumpIfTrue (in category 'testing') -----
+ willJumpIfTrue
- willJumpIfTrue 
  	"Answer whether the next bytecode is a jump-if-true."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isBranchIfTrueAt: pc in: method!
-  
- 	| byte |
- 	byte := self method at: pc.
- 	^ byte between: 168 and: 171!

Item was changed:
  ----- Method: InstructionStream>>willJustPop (in category 'testing') -----
  willJustPop
+ 	"Answer whether the bytecode at pc is a pop."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isJustPopAt: pc in: method!
- 
- 	^ (self method at: pc) = Encoder popCode!

Item was changed:
  ----- Method: InstructionStream>>willReallySend (in category 'testing') -----
  willReallySend
+ 	"Answer whether the next bytecode is a real message-send, not blockCopy:."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isRealSendAt: pc in: method!
- 	"Answer whether the next bytecode is a real message-send,
- 	not blockCopy:."
- 
- 	| byte |
- 	byte := self method at: pc.
- 	^byte >= 131
- 	  and: [byte ~= 200
- 	  and: [byte >= 176   "special send or short send"
- 		or: [byte <= 134 "long sends"	
- 			and: [| litIndex |
- 				"long form support demands we check the selector"
- 				litIndex := byte = 132
- 							ifTrue: [(self method at: pc + 1) // 32 > 1 ifTrue: [^false].
- 									self method at: pc + 2]
- 							ifFalse: [byte = 134
- 										ifTrue: [(self method at: pc + 1) bitAnd: 2r111111]
- 										ifFalse: [(self method at: pc + 1) bitAnd: 2r11111]].
- 				(self method literalAt: litIndex + 1) ~~ #blockCopy:]]]]!

Item was changed:
  ----- Method: InstructionStream>>willReturn (in category 'testing') -----
  willReturn
  	"Answer whether the next bytecode is a return."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isReturnAt: pc in: method!
- 
- 	^(self method at: pc) between: 120 and: 125!

Item was changed:
  ----- Method: InstructionStream>>willSend (in category 'testing') -----
  willSend
  	"Answer whether the next bytecode is a message-send."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isSendAt: pc in: method!
- 
- 	| byte |
- 	byte := self method at: pc.
- 	^byte >= 131
- 	  and: [byte >= 176 "special send or short send"
- 		or: [byte <= 134]]	"long sends"!

Item was changed:
  ----- Method: InstructionStream>>willStore (in category 'testing') -----
  willStore
+ 	"Answer whether the bytecode at pc is a store or store-pop."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isStoreAt: pc in: method!
- 	"Answer whether the next bytecode is a store or store-pop"
- 
- 	| byte |
- 	byte := self method at: pc.
- 	^(byte between: 96 and: 142)
- 		and: [byte <= 111			"96 103		storeAndPopReceiverVariableBytecode"
- 									"104 111	storeAndPopTemporaryVariableBytecode"
- 			or: [byte >= 129		"129		extendedStoreBytecode"
- 				and: [byte <= 130	"130		extendedStoreAndPopBytecode"
- 					or: [(byte = 132	"132		doubleExtendedDoAnythingBytecode"
- 						and: [(self method at: pc+1) >= 160])
- 					or: [byte = 141	"141		storeRemoteTempLongBytecode"
- 					or: [byte = 142	"142		storeAndPopRemoteTempLongBytecode"]]]]]]!

Item was changed:
  ----- Method: InstructionStream>>willStorePop (in category 'testing') -----
  willStorePop
+ 	"Answer whether the bytecode at pc is a store-pop."
+ 	| method |
+ 	method := self method.
+ 	^method encoderClass isStorePopAt: pc in: method!
- 	"Answer whether the next bytecode is a store-pop."
- 
- 	| byte |
- 	byte := self method at: pc.
- 	^byte = 130					"130		extendedStoreAndPopBytecode"
- 	  or: [byte = 142				"142		storeAndPopRemoteTempLongBytecode"
- 	  or: [byte between: 96 and: 111	"96 103		storeAndPopReceiverVariableBytecode"
- 									"104 111	storeAndPopTemporaryVariableBytecode"]]!



More information about the Packages mailing list