[Vm-dev] VM Maker: BytecodeSets.spur-eem.76.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jan 11 17:43:50 UTC 2018


Eliot Miranda uploaded a new version of BytecodeSets to project VM Maker:
http://source.squeak.org/VMMaker/BytecodeSets.spur-eem.76.mcz

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

Name: BytecodeSets.spur-eem.76
Author: eem
Time: 11 January 2018, 9:43:48.966063 am
UUID: 8082f573-5d35-4767-a69f-eb3bd8f5283b
Ancestors: BytecodeSets.spur-eem.75

Save BytecodeeSets now that both Pharo and Squeak have the SistaV1 bytecode set in the base.

=============== Diff against BytecodeSets.spur-eem.75 ===============

Item was changed:
  SystemOrganization addCategory: #'BytecodeSets-NewsqueakV4'!
- SystemOrganization addCategory: #'BytecodeSets-ParseNodes'!
  SystemOrganization addCategory: #'BytecodeSets-SistaV1'!

Item was removed:
- ----- Method: BlockLocalTempCounter>>blockReturnConstant: (in category '*BytecodeSets-instruction decoding') -----
- blockReturnConstant: value
- 	"Return Constant From Block bytecode."
- 	scanner pc < blockEnd ifTrue:
- 		[self doJoin]!

Item was removed:
- ----- Method: BlockLocalTempCounter>>directedSuperSend:numArgs: (in category '*BytecodeSets-instruction decoding') -----
- directedSuperSend: selector numArgs: numArgs
- 	"Send Message Above Specific Class With Selector, selector, bytecode.
- 	 Start the lookup above the class that is the value of the association on
- 	 top of stack. The arguments  of the message are found in the top numArgs
- 	 stack locations beneath the association, and the receiver just below them."
- 
- 	stackPointer := stackPointer - (numArgs + 1)!

Item was removed:
- ----- Method: BytecodeEncoder class>>stackDeltaForPrimitive:in: (in category '*BytecodeSets-bytecode decoding') -----
- stackDeltaForPrimitive: primitiveIndex in: method
- 	"This is the default implementation.  Subclasses with inline primitives will need to override."
- 	^0!

Item was removed:
- ----- Method: BytecodeEncoder>>sizePushFullClosure:numCopied: (in category '*BytecodeSets-opcode sizing') -----
- sizePushFullClosure: compiledBlockLiteralIndex numCopied: numCopied
- 	^self sizeOpcodeSelector: #genPushFullClosure:numCopied: withArguments: {compiledBlockLiteralIndex.numCopied}!

Item was removed:
- ----- Method: BytecodeEncoder>>sizePushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category '*BytecodeSets-opcode sizing') -----
- sizePushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: rcvrOnStack ignoreOuterContext: ignoreOuterContext
- 	^self
- 		sizeOpcodeSelector: #genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext:
- 		withArguments: {compiledBlockLiteralIndex.numCopied. rcvrOnStack. ignoreOuterContext}!

Item was removed:
- ----- Method: BytecodeEncoder>>sizeSendDirectedSuper:numArgs: (in category '*BytecodeSets-opcode sizing') -----
- sizeSendDirectedSuper: selectorLiteralIndex numArgs: numArgs
- 	^self sizeOpcodeSelector: #genSendDirectedSuper:numArgs: withArguments: {selectorLiteralIndex. numArgs}!

Item was removed:
- ----- Method: BytecodeEncoder>>sizeTrapIfNotInstanceOf: (in category '*BytecodeSets-opcode sizing') -----
- sizeTrapIfNotInstanceOf: litIndex
- 	^self sizeOpcodeSelector: #genTrapIfNotInstanceOf: withArguments: {litIndex}!

Item was removed:
- ----- Method: ClosureExtractor>>blockReturnConstant: (in category '*BytecodeSets-instruction decoding') -----
- blockReturnConstant: value
- 	currentContext := currentContext sender!

Item was removed:
- ----- Method: Decompiler>>blockReturnConstant: (in category '*BytecodeSets-instruction decoding') -----
- blockReturnConstant: value
- 
- 	self pushConstant: value; blockReturnTop!

Item was removed:
- BytecodeEncoder subclass: #EncoderForSistaV1
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'BytecodeSets-SistaV1'!
- 
- !EncoderForSistaV1 commentStamp: 'cb 3/22/2017 10:11' prior: 0!
- EncoderForSistaV1 encodes a bytecode set for Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.  This bytecode set therefore differs from a normal Smalltalk set in providing a set of inlined primitives that do not validate their arguments that the compiler generates only when it can prove that the primitives' arguments are valid.
- 
- The basic scheme is that the Cogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
- 
- The Sista Cogit (e.g. SistaStackToRegisterMappingCogit) adds counters to conditional branches.  Each branch has an executed and a taken count.  On execution the executed count is decremented and if the count goes below zero the VM sends a message at a special index in the specialObjectsArray (as of writing, conditionalCounterTrippedOn:).  Then if the branch is taken the taken count is decremented.  The two counter values allow the Sista optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
- 
- The VM provides a primitive that fills an Array with the state of the counters, and the state of each linked send in a method.  Tthe optimizer obtains the branch and send data for a method via this primitive.
- 
- This bytecde set encodes a bytecode set for Smalltalk that lifts limits on the number of literals and branch distances, and extended push integer and push character bytecodes.  Bytecodes are ordered by length to make decoding easier.  Bytecodes marked with an * are extensible via a prefix bytecode.
- 
- N.B.  Extension bytecodes can only come before extensible bytecodes, and only if valid (one cannot extend a bytecode extensible by Ext A with an Ext B).  An extensible bytecode consumes (and zeros) its extension(s).  Hence the hidden implicit variables holding extensions are always zero except after a valid sequence of extension bytecodes.
- 
- Instance Variables (inherited)
- 
- 1 Byte Bytecodes
- 	code	(note)	binary			name
- 	0-15		0000 iiii 			Push Receiver Variable #iiii
- 	16-31		0001 iiii			Push Literal Variable #iiii
- 	32-63		001 iiiii				Push Literal #iiiii
- 	64-71		01000 iii			Push Temp #iii
- 	72-75		010010 ii			Push Temp #ii + 8
- 	76			01001100			Push Receiver
- 	77			01001101			Push true
- 	78			01001110			Push false
- 	79			01001111			Push nil
- 	80			01010000			Push 0
- 	81			01010001			Push 1
- *	82			01010010			Push thisContext, (then Extend B = 1 => push thisProcess)
- 	83			01010011			Duplicate Stack Top
- 	84-87		010101 ii			UNASSIGNED
- 	88-91		010110 ii			Return Receiver/true/false/nil
- 	92			01011100			Return top
- 	93			01011101			BlockReturn nil
- *	94			01011110			BlockReturn Top [* return from enclosing block N, N = Extend A, then jump by Ext B ]
- *	95			01011111			Nop
- 	96-111		0110 iiii			Send Arithmetic Message #iiii #(#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr:)
- 	112-119	01110 iii			Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #== class)
- 	120		01111000			UNASSIGNED (was: blockCopy::, reserved for #~~)
- 	121		01111001			Send Special Message #value
- 	122-123	0111101 i			Send Special Message #i #(#value: #do:)
- 	124-127	011111 ii			Send Special Message #ii #(#new #new: #x #y))
- 	128-143	1000 iiii			Send Literal Selector #iiii With 0 Argument
- 	144-159	1001 iiii			Send Literal Selector #iiii With 1 Arguments
- 	160-175	1010 iiii			Send Literal Selector #iiii With 2 Arguments
- 	176-183	10110 iii			Jump iii + 1 (i.e., 1 through 8)
- 	184-191	10111 iii			Pop and Jump 0n True iii +1 (i.e., 1 through 8)
- 	192-199	11000 iii			Pop and Jump 0n False iii +1 (i.e., 1 through 8)
- 	200-207	11001 iii			Pop and Store Receiver Variable #iii
- 	208-215	11010 iii			Pop and Store Temporary Variable #iii
- 	216		11011000			Pop Stack Top
- 	217		11011001			Unconditional trap
- 	218-219	1101101 i			UNASSIGNED
- 	220-223	110111 ii			UNASSIGNED
- 
- 2 Byte Bytecodes
- *	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A) A is an unsigned extension.
- *	225		11100001	bbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B) B is a signed extension.
- *	226		11100010	iiiiiiii		Push Receiver Variable #iiiiiiii (+ Extend A * 256)
- *	227		11100011	iiiiiiii		Push Literal Variable #iiiiiiii (+ Extend A * 256)
- *	228		11100100	iiiiiiii		Push Literal #iiiiiiii (+ Extend A * 256)
- 	229		11100101	iiiiiiii		Push Temporary Variable #iiiiiiii
- 	230		11100110	iiiiiiii		UNASSIGNED (was pushNClosureTemps)
- 	231		11100111	jkkkkkkk	Push (Array new: kkkkkkk) (j = 0)
- 									&	Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)
- *	232		11101000	iiiiiiii		Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
- *	233		11101001	iiiiiiii		Push Character #iiiiiiii (+ Extend B * 256)
- **	234		11101010	iiiiijjj		Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
- **	235	(1)	11101011	iiiiijjj	ExtendB < 64
- 										ifTrue: [Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments]
- 										ifFalse: [Send To Superclass of Stacked Class Literal Selector #iiiii (+ Extend A * 32) with jjj (+ (Extend B bitAnd: 63) * 8) Arguments]
- *	236		11101100	iiiiiiii		UNASSIGNED
- *	237		11101101	iiiiiiii		Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
- **	238		11101110	iiiiiiii		Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0) (4)
- **	239		11101111	iiiiiiii		Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0) (4)
- **	240	(3)	11110000	iiiiiiii		Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256) 
- **	241	(3)	11110001	iiiiiiii		Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256) 
- 	242		11110010	iiiiiiii		Pop and Store Temporary Variable #iiiiiiii
- **	243	(3)	11110011	iiiiiiii		Store Receiver Variable #iiiiiii (+ Extend A * 256) 
- **	244	(3)	11110100	iiiiiiii		Store Literal Variable #iiiiiiii (+ Extend A * 256) 
- 	245		11110110	iiiiiiii		Store Temporary Variable #iiiiiiii
- 	246-247	1111011 i	xxxxxxxx	UNASSIGNED
- 
- 3 Byte Bytecodes
- **	248	(2)	11111000 	iiiiiiii		mssjjjjj		Call Primitive #iiiiiiii + (jjjjj * 256) 
- 								m=1 means inlined primitive, no hard return after execution. 
- 								ss defines the unsafe operation set used to encode the operations. 
- 								(ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)
- 								Lowcode inlined primitives may have extensions.
- 	249		11111001 	xxxxxxxx	siyyyyyy	push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1
- **	250		11111010 	eeiiikkk		jjjjjjjj		Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions
- 	251		11111011 	kkkkkkkk	sjjjjjjj		Push Temp At kkkkkkkk In Temp Vector At: jjjjjjj, s = 1 implies remote inst var access instead of remote temp vector access 
- *	252	(3)	11111100 	kkkkkkkk	sjjjjjjj		Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access 
- *	253	(3)	11111101 	kkkkkkkk	sjjjjjjj		Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access
- **	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior literal kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0 and <= 127)
- **	254		11111110	kkkkkkkk	jjjjjjjj		branch If Instance Of Behavior/Array Of Behavior literal kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ (Extend B bitAnd: 127) * 256, where Extend B >= 128 and <= 255)
- *	255		11111111	xxxxxxxx	jjjjjjjj		UNASSIGNED
- 
- (1) Bytecode 235 is a super send bytecode that starts the lookup in the superclass of some class.  It has two forms, "normal" and "directed". In the normal form, the class is the value of the method's methodClassAssociation which must be the last literal.  In the directed form the class is the class on top of stack.
- 
- (2) The Call Primitive Bytecode specifies either a primitive in the primitive table (m=0) or an inlined primitive (m=1). Non-inlined primitives from the primitive table have index (jjjjjjj * 256) + iiiiiiii and return from the method if they succeed.  This bytecode is only valid as the first bytecode of a method.  Inline primitives have index (jjjjjjj * 256) + iiiiiiii, cannot fail, and do not return when they succeed, yielding a result (typically on top of stack after popping their arguments, but possibly in a byte data stack, for example for unboxed floating-point primitives).
- 
- (3) ExtB lowest bit implies no store check is needed, ExtB second bit implies the object may be a context, ExtB third bit implies no immutability/read-only check is needed, other bits in the extension are unused.
- 
- (4) ExtA = 1 implies no mustBeBoolean trampoline is needed, other bits in the extension are unused
- 
- Here is the specification of the sista unsafe instructions (unsafe operations, set 00). The lowcode set uses external specifications.
- We sort the inline primitive operations by arity.  Nullary primitives occupy the 0-999 range. Unary primitives occupy the 1-1999 range, up until 8 args. 8191 instructions can be encoded in each unsafe operation set, instructions from 0 to 7 arguments can have 1000 different instructions each, while 8 args instructions can have 192 different instructions.
- 
- We define the following inlined primitives:
- 1000	class
- 1001	pointer numSlots
- 1002	pointer basicSize
- 1003	byte8Type format numBytes (includes CompiledMethod)
- 1004	short16Type format numShorts
- 1005	word32Type format numWords
- 1006	doubleWord64Type format numDoubleWords
- 	
- 1010	ensure number of bytes available.
- 1011	fixed-sized new. (objects with 0 to n inst vars)
- 	
- 1020 	identityHash (non-immediate, non-Behavior)
- 1021	identityHash (SmallInteger)
- 1022	identityHash (Character)
- 1023	identityHash (SmallFloat64)
- 1024	identityHash (Behavior, has hash?)
- 
- 1030 	immediateAsInteger (Character)
- 1031 	immediateAsInteger (SmallFloat64)
- 1035 	immediateAsFloat 	(Smallinteger)
- 	
- 2000	SmallInteger #+.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2001	SmallInteger #-.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2002	SmallInteger #*.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2003	SmallInteger #/.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2004	SmallInteger #//.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2005	SmallInteger #\\.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2006	SmallInteger #quo:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 
- 2011	Variable-sized pointers new (new:). Array, etc.
- 2012	Variable-sized byte new (new:). ByteArray, ByteString, etc.
- 2013	Variable-sized 16-bit new (new:). DoubleByteArray, etc.
- 2014	Variable-sized 32-bit new (new:). Bitmap, FloatArray, etc.
- 2015	Variable-sized 64-bit new (new:). DoubleWordArray, etc.
- 
- 2016	SmallInteger #bitAnd:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2017	SmallInteger #bitOr:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2018	SmallInteger #bitXor:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2019	SmallInteger #bitShiftLeft:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 2020	SmallInteger #bitShiftRight:.  Both arguments are SmallIntegers and the result fits in a SmallInteger (* depends on word size)
- 
- 2032	SmallInteger #>.  Both arguments are SmallIntegers
- 2033	SmallInteger #<.  Both arguments are SmallIntegers
- 2034	SmallInteger #>=.  Both arguments are SmallIntegers
- 2035	SmallInteger #<=.  Both arguments are SmallIntegers
- 2036	SmallInteger #=.  Both arguments are SmallIntegers
- 2037	SmallInteger #~=.  Both arguments are SmallIntegers
- 
- 2064	Pointer Object>>at:.		The receiver is guaranteed to be a pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger
- 2065	Byte Object>>at:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger.
- 2066	16-bit Word Object>>at:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger.
- 2067	Word Object>>at:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger.
- 2068	DoubleWord Object>>at:.	The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger or a LargePositiveInteger.
- 2069	QuadWord Object>>at:.		The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The result is a SmallInteger or a LargePositiveInteger.
- 
- The following instructions can have the ExtB check flag (See (3)).
- 3000	Pointer Object>>at:put:.			The receiver is guaranteed to be a pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger
- 3001	Byte Object>>at:put:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 8 bits.
- 3002	Word Object>>at:put:.			The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 16 bits.
- 3003	DoubleWord Object>>at:put:.	The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 32 bits.
- 3004	QuadWord Object>>at:put:.		The receiver is guaranteed to be a non-pointer object.  The 0-relative (1-relative?) index is an in-range SmallInteger.  The argument is a SmallInteger.  The primitive stores the least significant 64 bits.
- 			
- 3021	Byte Object >> equals:length:	The receiver and the arguments are both byte objects and have both the same size (length). The length argument is a smallinteger. Answers true if all fields are equal, false if not. Comparison is bulked to word comparison.
- 
- 4000	Pointer Object>> fillFrom:to:with: The receiver is a Pointer object. the middle two arguments are smallintegers. Last argument is any object. Fills the object in between the two indexes with last argument. Receiver is guaranteed to be mutable. The pointer accesses are raw (no inst var check). If ExtB is set to 1, no store check is present. Else a single store check is done for the bulk operation. Answers the receiver.
- 	
- 5000	Pointer Object>> replaceFrom:to:with:startingAt: Src and dest are pointer objects. ScrPos, scrLast and destLast are smallintegers. Receiver is guaranteed to be mutable.  Both ranges are in-bounds. The pointer accesses are raw (no inst var check). As for the normal primitive, the copy is linear. Answers the receiver.
- 	!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>backJumpBytecodeSize (in category 'bytecode decoding') -----
- backJumpBytecodeSize
- 	^ 4!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>bindingReadScanBlockFor:using: (in category 'compiled method support') -----
- bindingReadScanBlockFor: litVarIndex using: scanner
- 	"Answer a block argument for InstructionStream>>scanFor: that answers true
- 	 for reads of the value of the binding with zero-relative index litVarIndex.
- 	 N.B. Don't assume the compiler uses the most compact encoding available."
- 
- 	"	16-31		0001 i i i i				Push Literal Variable #iiii
- 	 *	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	227		11100011	i i i i i i i i	Push Literal Variable #iiiiiiii (+ Extend A * 256)"
- 	| extension |
- 	extension := 0.
- 	^[:b| | prevext |
- 	   prevext := extension.
- 	   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
- 	   (b < 32 and: [b >= 16 and: [b - 16 = litVarIndex]])
- 	    or: [b = 227
- 			and: [scanner followingByte + prevext = litVarIndex]]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>bindingWriteScanBlockFor:using: (in category 'compiled method support') -----
- bindingWriteScanBlockFor: litVarIndex using: scanner
- 	"Answer a block argument for InstructionStream>>scanFor: that answers true
- 	 for writes of the value of the binding with zero-relative index litVarIndex.
- 	 N.B. Don't assume the compiler uses the most compact encoding available."
- 
- 	"*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	241		11110001	iiiiiiii		Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
- 	 *	244		11110100	iiiiiiii		Store Literal Variable #iiiiiiii (+ Extend A * 256)"
- 	| extension |
- 	extension := 0.
- 	^[:b| | prevext |
- 	   prevext := extension.
- 	   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
- 	   (b = 241 or: [b = 244])
- 	   and: [scanner followingByte + prevext = litVarIndex]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>bytecodeSize: (in category 'instruction stream support') -----
- bytecodeSize: bytecode
- 	"Answer the number of bytes in the bytecode."
- 	bytecode < 224 ifTrue: [^1].
- 	bytecode < 248 ifTrue: [^2].
- 	^3!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>callPrimitiveCode (in category 'bytecode decoding') -----
- callPrimitiveCode
- 	"Answer the call primitive bytecode, if it exists in the encoder's bytecode set, or nil if not.
- 	 248	11111000 	iiiiiiii	mjjjjjjj	Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution."
- 	^248!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>createClosureScanBlock (in category 'compiled method support') -----
- createClosureScanBlock
- 	"Answer a block argument for InstructionStream>>scanFor: that answers true
- 	 for block closure creation bytecodes.  ote that with this interface we can't answer
- 	 true for the extension in front of a push closure bytecode and so the interface may
- 	 have to change at some point."
- 
- 	"*	224	11100000	aaaaaaaa			Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	225		11100001	bbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	 **	250		11111010 	eeiiikkk		jjjjjjjj		Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
- 	^[:b| b = 250]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>extensionsAt:in:into: (in category 'compiled method support') -----
- extensionsAt: bcpc in: method into: aTrinaryBlock
- 	"If the bytecode at pc is an extension then evaluate aBinaryBlock with the values of extA and extB and number of extension *bytes*.
- 	 If the bytecode at pc is not extended then evaluate aBinaryBlock with 0 and 0.
- 	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	225		11100001	bbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)"
-  
- 	| scanpc byte extByte extA extB |
- 	scanpc := bcpc.
- 	"There may be an extension (it could be a false positive).  We must scan as fast as possible..."
- 	extA := extB := 0.
- 	[byte := method at: scanpc.
- 	 byte >= 224 and: [byte <= 225]] whileTrue: 
- 		[extByte := method at: scanpc + 1.
- 		 scanpc := scanpc + 2.
- 		 byte = 224
- 			ifTrue:
- 				[extA := (extA bitShift: 8) + extByte]
- 			ifFalse:
- 				[extB := (extB = 0 and: [extByte > 127])
- 					ifTrue: [extByte - 256]
- 					ifFalse: [(extB bitShift: 8) + extByte]]].
- 	^aTrinaryBlock value: extA value: extB value: scanpc - bcpc
- 
- 
- "Why use
- 	byte >= 224 and: [byte <= 225]
-  and not
- 	(byte bitAnd: 16rFE) = 16rE0
-  ?
-  | n |
-  n := 100000000.
-  #(0 224) collect:
- 	[:byte|
- 	{ Time millisecondsToRun: [1 to: n do: [:i| (byte >= 224 and: [byte <= 225]) ifTrue: []]].
- 	   Time millisecondsToRun: [1 to: n do: [:i| (byte bitAnd: 16rFE) = 16rE0 ifTrue: []]] }] #(#(297 599) #(702 671))"!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>instVarReadScanBlockFor:using: (in category 'compiled method support') -----
- instVarReadScanBlockFor: varIndexCode using: scanner
- 	"Answer a block argument for InstructionStream>>scanFor: that answers true
- 	 for reads of the inst var with zero-relative index varIndexCode.
- 	 N.B. Don't assume the compiler uses the most compact encoding available."
- 
- 	"	0-15		0000 i i i i 				Push Receiver Variable #iiii
- 	*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	*	226		11100010	i i i i i i i i	Push Receiver Variable #iiiiiiii (+ Extend A * 256)"
- 	| extension |
- 	extension := 0.
- 	^[:b| | prevext |
- 	   prevext := extension.
- 	   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
- 	   (b < 16 and: [b = varIndexCode])
- 	    or: [b = 226
- 			and: [scanner followingByte + prevext = varIndexCode]]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>instVarWriteScanBlockFor:using: (in category 'compiled method support') -----
- instVarWriteScanBlockFor: varIndexCode using: scanner
- 	"Answer a block argument for InstructionStream>>scanFor: that answers true
- 	 for writes of the inst var with zero-relative index varIndexCode.
- 	 N.B. Don't assume the compiler uses the most compact encoding available."
- 
- 	"	200-207	11001 iii			Pop and Store Receiver Variable #iii
- 	*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	*	240		11110000	iiiiiiii		Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
- 	*	243		11110011	iiiiiiii		Store Receiver Variable #iiiiiii (+ Extend A * 256)"
- 	| extension |
- 	extension := 0.
- 	^[:b| | prevext |
- 	   prevext := extension.
- 	   extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
- 	   (b >= 200
- 	    and: [b < 208
- 	    and: [b - 200 = varIndexCode]])
- 	   or: [(b = 240 or: [b = 243])
- 		  and: [scanner followingByte + prevext = varIndexCode]]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>interpretJumpIfCondIn: (in category 'compiled method support') -----
- interpretJumpIfCondIn: anInstructionStream
- 	"Double-dispatch through the encoder to select the correct conditional jump decoder for the instruction set."
- 	^anInstructionStream interpretSistaV1JumpIfCond!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>interpretJumpIn: (in category 'compiled method support') -----
- interpretJumpIn: anInstructionStream
- 	"Double-dispatch through the encoder to select the correct unconditional jump decoder for the instruction set."
- 	^anInstructionStream interpretSistaV1Jump!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>interpretNextInstructionFor:in: (in category 'instruction stream support') -----
- interpretNextInstructionFor: aClient in: anInstructionStream
- 	"Double-dispatch through the encoder to select the correct instruction set decoder."
- 	^anInstructionStream interpretNextSistaV1InstructionFor: aClient!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isBlockReturnAt:in: (in category 'instruction stream support') -----
- isBlockReturnAt: pc in: method
- 	"Answer whether the bytecode at pc is a return from block."
- 	"	93			01011101			BlockReturn nil
- 	 *	94			01011110			BlockReturn Top [* return from enclosing block N, N = Extend A, then jump by Ext B ]"
- 	^(self nonExtensionBytecodeAt: pc in: method) between: 93 and: 94!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isBranchIfFalseAt:in: (in category 'instruction stream support') -----
- isBranchIfFalseAt: pc in: method
- 	"Answer whether the bytecode at pc is a conditional branch-if-false."
- 
- 	"	192-199	11000 iii				Pop and Jump 0n False iii +1 (i.e., 1 through 8)
- 	 *	239		11101111	iiiiiiii		Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0)"
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^byte >= 192 and: [byte <= 199 or: [byte = 239]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isBranchIfTrueAt:in: (in category 'instruction stream support') -----
- isBranchIfTrueAt: pc in: method
- 	"Answer whether the bytecode at pc is a conditional branch-if-true."
- 
- 	"	184-191	10111 iii				Pop and Jump 0n True iii +1 (i.e., 1 through 8)
- 	 *	238		11101110	iiiiiiii		Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0))"
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^byte >= 184 and: [byte <= 191 or: [byte = 238]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isCreateBlockAt:in: (in category 'instruction stream support') -----
- isCreateBlockAt: pc in: method
- 	"Answer whether the bytecode at pc is a block creation bytecode."
- 	
- 	"250		11111010 	eeiiikkk		jjjjjjjj		Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
- 
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^ byte = 250!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isExtension: (in category 'instruction stream support') -----
- isExtension: bytecode
- 	"Answer if the bytecode is an extension bytecode, i.e. one that extends
- 	 the range of the following bytecode."
- 	^bytecode >= 16rE0 and: [bytecode <= 16rE1]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isJumpAt:in: (in category 'instruction stream support') -----
- isJumpAt: pc in: method
- 	"Answer whether the bytecode at pc is an (unconditional) jump."
- 
- 	"	176-183	10110 iii				Jump iii + 1 (i.e., 1 through 8)
- 	 *	225		11100001	bbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	 *	237		11101101	iiiiiiii		Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^byte >= 176 and: [byte <= 183 or: [byte = 237]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isJustPopAt:in: (in category 'instruction stream support') -----
- isJustPopAt: pc in: method
- 	"Answer whether the bytecode at pc is a pop."
- 
- 	^(method at: pc) = 216 "216		11011000			Pop Stack Top"!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isRealSendAt:in: (in category 'instruction stream support') -----
- isRealSendAt: pc in: method
- 	"Answer whether the bytecode at pc is a real message-send, not blockCopy:."
- 
- 	^self isSendAt: pc in: method!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isReturnAt:in: (in category 'instruction stream support') -----
- isReturnAt: pc in: method
- 	"Answer whether the bytecode at pc is a return from block."
- 	"	88-91		010110 ii			Return Receiver/true/false/nil
- 		92			01011100			Return top
- 		93			01011101			BlockReturn nil
- 	 *	94			01011110			BlockReturn Top [* return from enclosing block N, N = Extend A, then jump by Ext B ]"
- 	^(self nonExtensionBytecodeAt: pc in: method) between: 88 and: 94!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isReturnTopFromMethodAt:in: (in category 'instruction stream support') -----
- isReturnTopFromMethodAt: pc in: method
- 	"Answer whether the bytecode at pc is a return stack top from method."
- 
- 	^(method at: pc) = 92!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isSendAt:in: (in category 'instruction stream support') -----
- isSendAt: pc in: method
- 	"Answer whether the bytecode at pc is a message-send."
- 
- 	"	96-111		0110 iiii			Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
- 		112-119	01110 iii			Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #'==' class)
- 		120		01111000			UNASSIGNED (was: blockCopy:)
- 		121		01111001			Send Special Message #value
- 		122-123	0111101 i			Send Special Message #i #(#value: #do:)
- 		124-127	011111 ii			Send Special Message #ii #(#new #new: #x #y))
- 		128-143	1000 iiii			Send Literal Selector #iiii With 0 Argument
- 		144-159	1001 iiii			Send Literal Selector #iiii With 1 Arguments
- 		160-175	1010 iiii			Send Literal Selector #iiii With 2 Arguments
- 	 **	234		11101010	iiiiijjj	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
- 	 **	235		11101011	iiiiijjj	Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^byte >= 96
- 	  and: [byte <= 175
- 		 or: [byte >= 234 and: [byte <= 235]]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isStoreAt:in: (in category 'instruction stream support') -----
- isStoreAt: pc in: method
- 	"Answer whether the bytecode at pc is a store or store-pop."
- 
- 	"	200-207	11001 iii						Pop and Store Receiver Variable #iii
- 		208-215	11010 iii						Pop and Store Temporary Variable #iii
- 	 *	224		11100000	aaaaaaaa			Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	240		11110000	iiiiiiii				Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
- 	 *	241		11110001	iiiiiiii				Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
- 		242		11110010	iiiiiiii				Pop and Store Temporary Variable #iiiiiiii
- 	 *	243		11110011	iiiiiiii				Store Receiver Variable #iiiiiii (+ Extend A * 256)
- 	 *	244		11110100	iiiiiiii				Store Literal Variable #iiiiiiii (+ Extend A * 256)
- 		245		11110110	iiiiiiii				Store Temporary Variable #iiiiiiii
- 
- 		252		11111100 	kkkkkkkk	jjjjjjjj	Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj
- 		253		11111101 	kkkkkkkk	jjjjjjjj	Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
- 
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^byte >= 200
- 	  and: [byte <= 215
- 		 or: [(byte between: 240 and: 245)
- 		 or: [(byte between: 252 and: 253)]]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>isStorePopAt:in: (in category 'instruction stream support') -----
- isStorePopAt: pc in: method
- 	"Answer whether the bytecode at pc is a store or store-pop."
- 
- 	"	200-207	11001 iii						Pop and Store Receiver Variable #iii
- 		208-215	11010 iii						Pop and Store Temporary Variable #iii
- 	 *	224		11100000	aaaaaaaa			Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	240		11110000	iiiiiiii				Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
- 	 *	241		11110001	iiiiiiii				Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
- 		242		11110010	iiiiiiii				Pop and Store Temporary Variable #iiiiiiii
- 
- 		253		11111101 	kkkkkkkk	jjjjjjjj	Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
- 
- 	| byte |
- 	byte := self nonExtensionBytecodeAt: pc in: method.
- 	^byte >= 200
- 	  and: [byte <= 215
- 		 or: [(byte between: 240 and: 242)
- 		 or: [byte = 253]]]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>method:refersInBytecodeToLiteral:specialSelectorIndex: (in category 'scanning') -----
- method: method refersInBytecodeToLiteral: aLiteral specialSelectorIndex: specialOrNil
- 	"Answer if method refers to the literal aLiteral in the bytecode, as opposed to in its literal frame."
- 
- 	"	77			01001101				Push true
- 		78			01001110				Push false
- 		79			01001111				Push nil
- 		80			01010000				Push 0
- 		81			01010001				Push 1
- 		88-91		010110 ii				Return Receiver/true/false/nil
- 		93			01011101				BlockReturn nil
- 		96-111		0110 iiii				Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
- 		112-119	01110 iii				Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #'==' class)
- 		120		01111000				UNASSIGNED (was: blockCopy:)
- 		121		01111001				Send Special Message #value
- 		122-123	0111101 i				Send Special Message #i #(#value: #do:)
- 		124-127	011111 ii				Send Special Message #ii #(#new #new: #x #y))
- 	*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	*	225		11100001	sbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	*	232		11101000	iiiiiiii		Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
- 	*	233		11101001	iiiiiiii		Push Character #iiiiiiii (+ Extend B * 256)
- 		249		11111001 	xxxxxxxx	syyyyyyy	Reserved for Push Float"
- 	| byte extended scanner |
- 	specialOrNil ifNotNil:
- 		[byte := specialOrNil + 95.
- 		^(InstructionStream on: method) scanFor: [:b| b = byte]].
- 	extended := false.
- 	aLiteral isInteger ifTrue:
- 		[(aLiteral >= -32768 and: [aLiteral <= 32767]) ifFalse: [^false].
- 		 scanner := InstructionStream on: method.
- 		 (aLiteral >= 0 and: [aLiteral <= 255]) ifTrue:
- 			[aLiteral <= 1 ifTrue:
- 				[byte := aLiteral + 80.
- 				 ^scanner scanFor: [:b| b = byte]].
- 			 ^scanner scanFor:
- 				[:b|
- 				(b = 232
- 				 and: [extended not
- 				 and: [scanner followingByte = aLiteral]])
- 				or: [extended := b = 225.
- 					false]]].
- 		 byte := (aLiteral bitShift: -8) bitAnd: 255.
- 		^scanner scanFor:
- 			[:b|
- 			(b = 232
- 			 and: [extended
- 			 and: [scanner followingByte = (aLiteral bitAnd: 255)]])
- 			or: [extended := b = 225 and: [scanner followingByte = byte].
- 				false]]].
- 	aLiteral isCharacter ifTrue:
- 		[aLiteral asciiValue <= 65535 ifFalse: [^false].
- 		 scanner := InstructionStream on: method.
- 		 aLiteral asciiValue <= 255 ifTrue:
- 			[^scanner scanFor:
- 				[:b|
- 				(b = 233
- 				 and: [extended not
- 				 and: [scanner followingByte = aLiteral]])
- 				or: [extended := b = 225.
- 					false]]].
- 		 byte := (aLiteral bitShift: -8) bitAnd: 255.
- 		^scanner scanFor:
- 			[:b|
- 			(b = 233
- 			 and: [extended
- 			 and: [scanner followingByte = (aLiteral bitAnd: 255)]])
- 			or: [extended := b = 225 and: [scanner followingByte = byte].
- 				false]]].
- 	aLiteral == nil ifTrue:
- 		[^(InstructionStream on: method) scanFor: [:b| b = 79 or: [b = 91 or: b = 93]]].
- 	aLiteral == true ifTrue:
- 		[^(InstructionStream on: method) scanFor: [:b| b = 77 or: [b = 89]]].
- 	aLiteral == false ifTrue:
- 		[^(InstructionStream on: method) scanFor: [:b| b = 78 or: [b = 90]]].
- 	
- 	^false!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>nonExtensionBytecodeAt:in: (in category 'instruction stream support') -----
- nonExtensionBytecodeAt: pc in: method
- 	"Answer the actual bytecode at pc in method, skipping past any preceeding extensions."
- 	| scanpc byte |
- 	scanpc := pc.
- 	[ byte := method at: scanpc.
- 	 byte >= 224 and: [byte <= 225]] whileTrue: [ scanpc := scanpc + 2 ].
- 	^ byte!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>nopCode (in category 'bytecode decoding') -----
- nopCode
- 	"Answer the call primitive bytecode, if it exists in the encoder's bytecode set, or nil if not.
- 	 95			01011111			Nop"
- 	^95!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>numLocalTempsForBlockAt:in: (in category 'block closure support') -----
- numLocalTempsForBlockAt: startpc in: method
- 	"230		11100110	iiiiiiii		PushNClosureTemps iiiiiiii"
- 	^(method at: startpc) = 230
- 		ifTrue: [method at: startpc + 1]
- 		ifFalse: [0]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>pcOfBlockCreationBytecodeForBlockStartingAt:in: (in category 'bytecode decoding') -----
- pcOfBlockCreationBytecodeForBlockStartingAt: startpc in: method
- 	"Answer the pc of the push closure bytecode whose block starts at startpc in method.
- 	 May need to back up to include extension bytecodes."
- 
- 	"*	224		11100000	aaaaaaaa			Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	225		11100001	bbbbbbbb			Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	 **	250		11111010 	eeiiikkk		jjjjjjjj	Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
- 	| numExtensions |
- 	self assert: (method at: startpc - 3) = 250.
- 	numExtensions := (method at: startpc - 2) >> 6.
- 	^startpc - 3 - (numExtensions * 2)!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>pushClosureBytecodeSize (in category 'bytecode decoding') -----
- pushClosureBytecodeSize
- 	"Answer the size of the push closure bytecode.
- 	 **	250		11111010 	eeiiikkk		jjjjjjjj	Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
- 	^3!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>selectorToSendOrItselfFor:in:at: (in category 'instruction stream support') -----
- selectorToSendOrItselfFor: anInstructionStream in: method at: pc
- 	"If anInstructionStream is at a send bytecode then answer the send's selector,
- 	 otherwise answer anInstructionStream itself.  The rationale for answering
- 	 anInstructionStream instead of, say, nil, is that potentially any existing object
- 	 can be used as a selector, but since anInstructionStream postdates the method,
- 	 it can't be one of them.
- 
- 	 The compilcation is that for convenience we assume the pc could be
- 	 pointing to the raw send bytecode after its extensions, or at the extension
- 	 preceeding the raw send bytecode.
- 		96-111		0110 iiii			Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
- 		112-119	01110 iii			Send Special Message #iii #(#at: #at:put: #size #next #nextPut: #atEnd #'==' class)
- 		120		01111000			UNASSIGNED (was: blockCopy:)
- 		121		01111001			Send Special Message #value
- 		122-123	0111101 i			Send Special Message #i #(#value: #do:)
- 		124-127	011111 ii			Send Special Message #ii #(#new #new: #x #y))
- 		128-143	1000 iiii			Send Literal Selector #iiii With 0 Argument
- 		144-159	1001 iiii			Send Literal Selector #iiii With 1 Arguments
- 		160-175	1010 iiii			Send Literal Selector #iiii With 2 Arguments
- 	*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	*	225		11100001	bbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	**	234		11101010	iiiiijjj		Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
- 	**	235		11101011	iiiiijjj		Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 
- 	| byte |
- 	byte := method at: pc.
- 	byte < 96 ifTrue:
- 		[^anInstructionStream].
- 	byte <= 175 ifTrue: 
- 		["special byte or short send"
- 		 ^byte >= 128
- 			ifTrue: [method literalAt: (byte bitAnd: 15) + 1]
- 			ifFalse: [Smalltalk specialSelectorAt: byte - 95]].
- 	byte < 234 ifTrue: "need to check for either extension cuz order of extensions is not restricted. so extB could preceed extA"
- 		[(byte >= 224 and: [byte <= 225]) ifTrue:
- 			[^self extensionsAt: pc in: method into:
- 				[:extA :extB :nExtBytes| | byteAfter index |
- 				byteAfter := method at: pc + nExtBytes.
- 				(byteAfter >= 234 and: [byteAfter <= 235])
- 					ifTrue:
- 						[index := ((method at: pc + nExtBytes + 1) bitShift: -3) + (extA bitShift: 5).
- 						 method literalAt: index + 1]
- 					ifFalse: [anInstructionStream]]].
- 		^anInstructionStream].
- 	byte > 235 ifTrue:
- 		[^anInstructionStream].
- 	"they could be extended..."
- 	^self extensionsAt: pc in: method into:
- 		[:extA :extB :nExtBytes| | index |
- 		 index := ((method at: pc + 1) bitShift: -3) + (extA bitShift: 5).
- 		 method literalAt: index + 1]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>specialLiterals (in category 'bytecode decoding') -----
- specialLiterals
- 	^ #(true false nil 0 1) !

Item was removed:
- ----- Method: EncoderForSistaV1 class>>stackDeltaForPrimitive:in: (in category 'bytecode decoding') -----
- stackDeltaForPrimitive: primitiveIndex in: method
- 	"Answer the stack delta for the callPrimitive: bytecode (see my class comment).
- 	 There is no delta for non-inlined primitives (its implicitly 0 - method numArgs).
- 	 Inlined primitives are grouped by the thousand by argument count, 32 args max ;-)."
- 	^primitiveIndex < 32678
- 		ifTrue: [0]
- 		ifFalse: [primitiveIndex - 32768 // 1000]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>superSendScanBlockUsing: (in category 'instruction stream support') -----
- superSendScanBlockUsing: scanner
- 	"Answer a block argument for InstructionStream>>scanFor:
- 	 that answers true for super sends."
- 
- 	"*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	 *	225		11100001	sbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	 **	235		11101011	iiiiijjj		Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 					
- 	^[:instr | instr = 235]!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>supportsClosures (in category 'compiled method support') -----
- supportsClosures
- 	"Answer if the instruction set supports closures (contains
- 	 closure creation and indirect temp access bytecodes)."
- 
- 	^true!

Item was removed:
- ----- Method: EncoderForSistaV1 class>>unusedBytecode (in category 'bytecode decoding') -----
- unusedBytecode
- 	"Answer the opcode of a single-byte unused bytecode, if it exists in the encoder's bytecode set, or nil if not."
- 	^223!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchIfInstanceOf:distance: (in category 'extended bytecode generation') -----
- genBranchIfInstanceOf: literalIndex distance: distance
- 	self genBranchIfInstanceOf: literalIndex distance: distance orNot: false!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchIfInstanceOf:distance:orNot: (in category 'extended bytecode generation') -----
- genBranchIfInstanceOf: literalIndex distance: distance orNot: orNot
- 	"254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
- 							
- 	| extendedIndex extendedDistance |
- 	(literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65536].
- 	(distance < 1 or: [distance > 32767]) ifTrue: 
- 		[^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
- 	(extendedIndex := literalIndex) > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 256.
- 		 extendedIndex := extendedIndex \\ 256].
- 	(orNot not or: [(extendedDistance := distance) > 255]) ifTrue:
- 		[self genUnsignedSingleExtendB: (distance bitShift: -8) + (orNot not asBit  * 128).
- 		extendedDistance := distance bitAnd: 255].
- 	
- 	stream
- 		nextPut: 254;
- 		nextPut: extendedIndex;
- 		nextPut: extendedDistance!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchIfNotInstanceOf:distance: (in category 'extended bytecode generation') -----
- genBranchIfNotInstanceOf: literalIndex distance: distance
- 	self genBranchIfInstanceOf: literalIndex distance: distance orNot: true!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchPopFalse: (in category 'bytecode generation') -----
- genBranchPopFalse: distance
- 	(distance > 0 and: [distance < 9]) ifTrue:
- 		["192-199	11000 iii			Pop and Jump 0n False iii + 1 (i.e., 1 through 8)"
- 		 stream nextPut: 191 + distance.
- 		 ^self].
- 	^self genBranchPopFalseLong: distance!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchPopFalseLong: (in category 'bytecode generation') -----
- genBranchPopFalseLong: distance
- 	"239		11101111	iiiiiiii		Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0)	"
- 	| distanceMod256 |
- 	(distance < 0 or: [distance > 32767]) ifTrue:
- 		[^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
- 	distanceMod256 := (distance < 0 or: [distance > 255])
- 							ifTrue:
- 								[self genUnsignedSingleExtendB: (distance bitShift: -8).
- 								 distance bitAnd: 255]
- 							ifFalse: [distance].
- 	stream
- 		nextPut: 239;
- 		nextPut: distanceMod256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchPopFalseNoMustBeBoolean: (in category 'extended bytecode generation') -----
- genBranchPopFalseNoMustBeBoolean: distance
- 	self genNoMustBeBooleanFlag.
- 	self genBranchPopFalseLong: distance!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchPopTrue: (in category 'bytecode generation') -----
- genBranchPopTrue: distance
- 	(distance > 0 and: [distance < 9]) ifTrue:
- 		["184-191	10111 iii			Pop and Jump 0n True iii + 1 (i.e., 1 through 8)"
- 		 stream nextPut: 183 + distance.
- 		 ^self].
- 	^self genBranchPopTrueLong: distance!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchPopTrueLong: (in category 'bytecode generation') -----
- genBranchPopTrueLong: distance
- 	"238		11101110	iiiiiiii		Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0)"
- 	| distanceMod256 |
- 	(distance < 0 or: [distance > 32767]) ifTrue:
- 		[^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
- 	(distance > 0 and: [distance < 9]) ifTrue:
- 		["184-191	10111 iii			Pop and Jump 0n True iii + 1 (i.e., 1 through 8)"
- 		 stream nextPut: 183 + distance.
- 		 ^self].
- 	distanceMod256 := (distance < 0 or: [distance > 255])
- 							ifTrue:
- 								[self genUnsignedSingleExtendB: (distance bitShift: -8).
- 								 distance bitAnd: 255]
- 							ifFalse: [distance].
- 	stream
- 		nextPut: 238;
- 		nextPut: distanceMod256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genBranchPopTrueNoMustBeBoolean: (in category 'extended bytecode generation') -----
- genBranchPopTrueNoMustBeBoolean: distance
- 	self genNoMustBeBooleanFlag.
- 	self genBranchPopTrueLong: distance!

Item was removed:
- ----- Method: EncoderForSistaV1>>genCallInlinePrimitive: (in category 'extended bytecode generation') -----
- genCallInlinePrimitive: primitiveIndex
- 	"	248	(2)	11111000 	iiiiiiii		mssjjjjj		Call Primitive #iiiiiiii + (jjjjj * 256) 
- 								m=1 means inlined primitive, no hard return after execution. 
- 								ss defines the unsafe operation set used to encode the operations. 
- 								(ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
- 	"N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
- 	 complicate the VM's determination of the primitive number and the primitive error code
- 	 store since the extension, being optional, would make the sequence variable length."
- 	(primitiveIndex < 1 or: [primitiveIndex > 32767]) ifTrue:
- 		[self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 32767].
- 	stream
- 		nextPut: 248;
- 		nextPut: (primitiveIndex bitAnd: 255);
- 		nextPut: (primitiveIndex bitShift: -8) + 128!

Item was removed:
- ----- Method: EncoderForSistaV1>>genCallPrimitive: (in category 'bytecode generation') -----
- genCallPrimitive: primitiveIndex
- 	"248	(2)	11111000 	iiiiiiii		mssjjjjj		Call Primitive #iiiiiiii + (jjjjj * 256) 
- 								m=1 means inlined primitive, no hard return after execution. 
- 								ss defines the unsafe operation set used to encode the operations. 
- 								(ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)"
- 	"N.B. We could have made CallPrimitive a 2-byte code taking an extension, but that would
- 	 complicate the VM's determination of the primitive number and the primitive error code
- 	 store since the extension, being optional, would make the sequence variable length."
- 	(primitiveIndex < 1 or: [primitiveIndex > 65535]) ifTrue:
- 		[self outOfRangeError: 'primitive index' index: primitiveIndex range: 1 to: 65535].
- 	stream
- 		nextPut: 248;
- 		nextPut: (primitiveIndex bitAnd: 255);
- 		nextPut: (primitiveIndex bitShift: -8)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genDup (in category 'bytecode generation') -----
- genDup
- 	"83			01010011			Duplicate Stack Top"
- 	stream nextPut: 83!

Item was removed:
- ----- Method: EncoderForSistaV1>>genJump: (in category 'bytecode generation') -----
- genJump: distance
- 	(distance > 0 and: [distance < 9]) ifTrue:
- 		["176-183	10110 iii			Jump iii + 1 (i.e., 1 through 8)"
- 		 stream nextPut: 175 + distance.
- 		 ^self].
- 	"237		11101101	iiiiiiii		Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
- 	^self genJumpLong: distance!

Item was removed:
- ----- Method: EncoderForSistaV1>>genJumpLong: (in category 'bytecode generation') -----
- genJumpLong: distance
- 	"237		11101101	iiiiiiii		Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
- 	(distance between: -32768 and: 32767) ifFalse:
- 		[^self outOfRangeError: 'index' index: distance range: -32768 to: 32767].
- 	(distance < 0 or: [distance > 255]) ifTrue:
- 		[self genSignedSingleExtendB: (distance bitShift: -8)].
- 	stream
- 		nextPut: 237;
- 		nextPut: (distance bitAnd: 255)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genNoMustBeBooleanFlag (in category 'extended bytecode generation') -----
- genNoMustBeBooleanFlag
- 	self genUnsignedSingleExtendA: 1!

Item was removed:
- ----- Method: EncoderForSistaV1>>genNop (in category 'extended bytecode generation') -----
- genNop
- 	"95			01011111			Nop"
- 	stream nextPut: 95!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPop (in category 'bytecode generation') -----
- genPop
- 	"216		11011000			Pop Stack Top"
- 	stream nextPut: 216!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushCharacter: (in category 'bytecode generation') -----
- genPushCharacter: aCharacterOrCode
- 	"233		11101001	i i i i i i i i	Push Character #iiiiiiii (+ Extend B * 256)"
- 	"Why restrict the range to 16 bits when we could encode arbitrarily 32-bit Characters?
- 	 Well, 16 bits requires 4 bytes (extB + byte, 78 + byte) and so beyond this range we
- 	 lose space verses a single-byte pushLiteral and a 4 byte Character literal on 32-bits.
- 	 And generating the same bytecode on 64-bit and 32-bit is important if we want to be
- 	 able to load binary code from one to the other (e.g. via Fuel)."
- 	| code |
- 	code := aCharacterOrCode isInteger ifTrue: [aCharacterOrCode] ifFalse: [aCharacterOrCode asInteger].
- 	(code < 0 or: [code > 65535]) ifTrue:
- 		[^self outOfRangeError: 'character' index: code range: 0 to: 65535].
- 	(code > 255) ifTrue:
- 		[self genUnsignedSingleExtendB: (code bitShift: -8)].
- 	stream
- 		nextPut: 233;
- 		nextPut: (code bitAnd: 255)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushClosureCopyNumCopiedValues:numArgs:jumpSize: (in category 'bytecode generation') -----
- genPushClosureCopyNumCopiedValues: numCopied numArgs: numArgs jumpSize: jumpSize
- 	"250		11111010 eeiiikkk		jjjjjjjj		Push Closure Num Copied iii (+ Ext A // 16 * 8) Num Args kkk (+ Ext A \\ 16 * 8) BlockSize jjjjjjjj (+ Ext B * 256). ee = num extensions"
- 	"Including numExtensions makes decoding the bytecode quicker since it obviates having to scan from the beginning of a method."
- 	| numExtensions numCopiedMod8 numArgsMod8 extA |
- 	(jumpSize < 0 or: [jumpSize > 65535]) ifTrue:
- 		[^self outOfRangeError: 'block size' index: jumpSize range: 0 to: 65535].
- 	(numCopied < 0 or: [numCopied > 127]) ifTrue:
- 		[^self outOfRangeError: 'num copied' index: numCopied range: 0 to: 127].
- 	(numArgs < 0 or: [numArgs > 127]) ifTrue:
- 		[^self outOfRangeError: 'num args' index: numArgs range: 0 to: 127].
- 	extA := numExtensions := 0.
- 	(numArgsMod8 := numArgs) > 7 ifTrue:
- 		[extA := numArgs // 8.
- 		 numArgsMod8 := numArgsMod8 \\ 8].
- 	(numCopiedMod8 := numCopied) > 7 ifTrue:
- 		[extA := extA + (numCopied // 8 * 16).
- 		 numCopiedMod8 := numCopiedMod8 \\ 8].
- 	extA ~= 0 ifTrue:
- 		[self genUnsignedSingleExtendA: extA.
- 		 numExtensions := 1].
- 	jumpSize > 255 ifTrue:
- 		[numExtensions := numExtensions + 1.
- 		 self genUnsignedSingleExtendB: jumpSize // 256].
- 	stream
- 		nextPut: 250;
- 		nextPut: (numExtensions bitShift: 6) + (numCopiedMod8 bitShift: 3) + numArgsMod8;
- 		nextPut: (jumpSize bitAnd: 16rFF)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushConsArray: (in category 'bytecode generation') -----
- genPushConsArray: size
- 	(size < 0 or: [size > 127]) ifTrue:
- 		[^self outOfRangeError: 'size' index: size range: 0 to: 127].
- 	"231		11100111	jkkkkkkk	Push (Array new: kkkkkkk) (j = 0)
- 									&	Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
- 	stream
- 		nextPut: 231;
- 		nextPut: size + 128!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied: (in category 'extended bytecode generation') -----
- genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied
- 	"By default the closure will have an outer context and the receiver will be fetched from the current context"
- 	self genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: false ignoreOuterContext: false!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushFullClosure:numCopied:receiverOnStack:ignoreOuterContext: (in category 'extended bytecode generation') -----
- genPushFullClosure: compiledBlockLiteralIndex numCopied: numCopied receiverOnStack: receiverOnStack ignoreOuterContext: ignoreOuterContext
- 	"*	249		11111001 	xxxxxxxx	siyyyyyy	push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
- 	| extendedIndex |
- 	(numCopied < 0 or: [numCopied > 64]) ifTrue:
- 		[self outOfRangeError: 'num copied' index: numCopied range: 1 to: 64].
- 	(compiledBlockLiteralIndex < 0 or: [compiledBlockLiteralIndex > 32767]) ifTrue:
- 		[^self outOfRangeError: 'index' index: compiledBlockLiteralIndex range: 0 to: 32767].
- 	(extendedIndex := compiledBlockLiteralIndex) > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 256.
- 		 extendedIndex := extendedIndex \\ 256].
- 	stream
- 		nextPut: 249;
- 		nextPut: extendedIndex;
- 		nextPut: receiverOnStack asBit << 7 + (ignoreOuterContext asBit << 6) + numCopied!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushInstVar: (in category 'bytecode generation') -----
- genPushInstVar: instVarIndex
- 	(instVarIndex between: 0 and: 15) ifTrue:
- 		["0-15 	0000iiii 	Push Receiver Variable #iiii"
- 		 stream nextPut: 0 + instVarIndex.
- 		 ^self].
- 	self genPushInstVarLong: instVarIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushInstVarLong: (in category 'bytecode generation') -----
- genPushInstVarLong: instVarIndex
- 	"226		11100010	i i i i i i i i	Push Receiver Variable #iiiiiiii (+ Extend A * 256)"
- 	"See also MaybeContextInstanceVariableNode"
- 	(instVarIndex < 0 or: [instVarIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 65535].
- 	instVarIndex > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: instVarIndex // 256].
- 	stream
- 		nextPut: 226;
- 		nextPut: instVarIndex \\ 256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushInteger: (in category 'bytecode generation') -----
- genPushInteger: anInteger
- 	"80			01010000				Push 0
- 	 81			01010001				Push 1
- 	 232		11101000	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)"
- 	"Why restrict the range to 16 bits when we could encode arbitrarily large integers?
- 	 Well, 16 bits requires 4 bytes (extB + byte, 78 + byte) and so beyond this range we lose space
- 	 verses a single-byte pushLiteral and a 4 byte integer literal on 32-bits.  And generating the same
- 	 bytecode on 64-bit and 32-bit is important if we want to be able to load binary code from one to
- 	 the other (e.g. via Fuel)."
- 	anInteger = 0 ifTrue:
- 		[stream nextPut: 80.
- 		 ^self].
- 	anInteger = 1 ifTrue:
- 		[stream nextPut: 81.
- 		 ^self].
- 	(anInteger < -32768 or: [anInteger > 32767]) ifTrue:
- 		[^self outOfRangeError: 'integer' index: anInteger range: -32768 to: 32767].
- 	(anInteger < 0 or: [anInteger > 255]) ifTrue:
- 		[self genSignedSingleExtendB: (anInteger bitShift: -8)].
- 	stream
- 		nextPut: 232;
- 		nextPut: (anInteger bitAnd: 255)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushLiteral: (in category 'bytecode generation') -----
- genPushLiteral: literalIndex
- 	| extendedIndex |
- 	(literalIndex < 0 or: [literalIndex > 32768]) ifTrue:
- 		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 32768].
- 	literalIndex < 32 ifTrue: 
- 		["32-63 	001iiiii 	Push Literal #iiiii"
- 		 stream nextPut: 32 + literalIndex.
- 		 ^self].
- 	"228		11100100	i i i i i i i i	Push Literal #iiiiiiii (+ Extend A * 256)"
- 	(extendedIndex := literalIndex) > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 256.
- 		 extendedIndex := extendedIndex \\ 256].
- 	stream
- 		nextPut: 228;
- 		nextPut: extendedIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushLiteralVar: (in category 'bytecode generation') -----
- genPushLiteralVar: literalIndex
- 	| extendedIndex |
- 	(literalIndex < 0 or: [literalIndex > 32768]) ifTrue:
- 		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 32768].
- 	literalIndex < 16 ifTrue: 
- 		["16-31		0001 i i i i		Push Literal Variable #iiii"
- 		 stream nextPut: 16 + literalIndex.
- 		 ^self].
- 	"227		11100011	i i i i i i i i	Push Literal Variable #iiiiiiii (+ Extend A * 256)"
- 	(extendedIndex := literalIndex) > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 256.
- 		 extendedIndex := extendedIndex \\ 256].
- 	stream
- 		nextPut: 227;
- 		nextPut: extendedIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushNClosureTemps: (in category 'bytecode generation') -----
- genPushNClosureTemps: numTemps
- 	"backward compatibility..."
- 	numTemps timesRepeat: [ self genPushSpecialLiteral: nil ]!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushNewArray: (in category 'bytecode generation') -----
- genPushNewArray: size
- 	(size < 0 or: [size > 127]) ifTrue:
- 		[^self outOfRangeError: 'size' index: size range: 0 to: 127].
- 	"231		11100111	jkkkkkkk	Push (Array new: kkkkkkk) (j = 0)
- 									&	Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)"
- 	stream
- 		nextPut: 231;
- 		nextPut: size!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushReceiver (in category 'bytecode generation') -----
- genPushReceiver
- 	"76			01001100		Push Receiver"
- 	stream nextPut: 76!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushRemoteInstanceVariable:inObjectAt: (in category 'extended bytecode generation') -----
- genPushRemoteInstanceVariable: instanceVariableIndex inObjectAt: tempIndex
- 	"251		11111011 	kkkkkkkk	sjjjjjjj		Push Temp At kkkkkkkk In Temp Vector At: jjjjjjj, s = 1 implies remote inst var access instead of remote temp vector access"
- 
- 	(instanceVariableIndex < 0 or: [instanceVariableIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'instanceVariableIndex' index: instanceVariableIndex range: 0 to: 65535].
- 	(tempIndex < 0 or: [tempIndex >= 128]) ifTrue:
- 		[^self outOfRangeError: 'tempVectorIndex' index: tempIndex range: 0 to: 127].
- 	instanceVariableIndex > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: instanceVariableIndex // 256].
- 	stream
- 		nextPut: 251;
- 		nextPut: instanceVariableIndex \\ 256;
- 		nextPut: 1 << 7 + tempIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
- genPushRemoteTemp: tempIndex inVectorAt: tempVectorIndex
- 	"251		11111011 	kkkkkkkk	sjjjjjjj		Push Temp At kkkkkkkk In Temp Vector At: jjjjjjj, s = 1 implies remote inst var access instead of remote temp vector access"
- 	(tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
- 		[^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
- 	(tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
- 		[^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
- 	stream
- 		nextPut: 251;
- 		nextPut: tempIndex;
- 		nextPut: tempVectorIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushSpecialLiteral: (in category 'bytecode generation') -----
- genPushSpecialLiteral: aLiteral
- 	"77			01001101			Push true
- 	 78			01001110			Push false
- 	 79			01001111			Push nil
- 	 80			01010000			Push 0
- 	 81			01010001			Push 1
- 	 232		11101000	iiiiiiii		Push Integer #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
- 	| index |
- 	aLiteral isInteger ifTrue:
- 		[aLiteral == 0 ifTrue:
- 			[stream nextPut: 80.
- 			 ^self].
- 		 aLiteral == 1 ifTrue:
- 			[stream nextPut: 81.
- 			 ^self].
- 		 ^self genPushInteger: aLiteral].
- 	index := #(true false nil)
- 					indexOf: aLiteral
- 					ifAbsent: [^self error: 'push special literal: ', aLiteral printString,  ' is not one of true false nil'].
- 	stream nextPut: 76 + index!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushTemp: (in category 'bytecode generation') -----
- genPushTemp: tempIndex
- 	(tempIndex < 0 or: [tempIndex > 63]) ifTrue:
- 		[^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
- 	tempIndex < 12 ifTrue: 
- 		["64-71		01000 i i i		Push Temporary Variable #iii
- 		   72-75	010010 i i		Push Temporary Variable #ii + 8"
- 		 stream nextPut: 64 + tempIndex.
- 		 ^self].
- 	"229		11100101	i i i i i i i i	Push Temporary Variable #iiiiiiii"
- 	stream
- 		nextPut: 229;
- 		nextPut: tempIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genPushThisContext (in category 'bytecode generation') -----
- genPushThisContext
- 	"82			01010010			Push thisContext, (then e.g. Extend B 1 = push thisProcess)"
- 	stream nextPut: 82!

Item was removed:
- ----- Method: EncoderForSistaV1>>genReturnReceiver (in category 'bytecode generation') -----
- genReturnReceiver
- 	"88-91		010110 ii			Return Receiver/true/false/nil"
- 	stream nextPut: 88!

Item was removed:
- ----- Method: EncoderForSistaV1>>genReturnSpecialLiteral: (in category 'bytecode generation') -----
- genReturnSpecialLiteral: aLiteral
- 	"88-91		010110 ii			Return Receiver/true/false/nil"
- 	| index |
- 	index := #(true false nil) indexOf: aLiteral ifAbsent: 0.
- 	index = 0 ifTrue:
- 		[^self error: 'return special literal: ', aLiteral printString,  ' is not one of true false nil'].
- 	stream nextPut: 88 + index!

Item was removed:
- ----- Method: EncoderForSistaV1>>genReturnTop (in category 'bytecode generation') -----
- genReturnTop
- 	"92		1011100		Return Stack Top From Message"
- 	stream nextPut: 92!

Item was removed:
- ----- Method: EncoderForSistaV1>>genReturnTopToCaller (in category 'bytecode generation') -----
- genReturnTopToCaller
- 	"94		01011110		Return Stack Top From Block [* return from enclosing block N, ExtA]"
- 	"If extended, the least significant bit of the extension determines if we return to the caller or not
- 	 and the most significant bits determine how many levels of the static chain to return from.
- 		ExtA = iiiiiiij
- 		iiiiiii=0,j=0	=>	return to caller
- 		iiiiiii=0,j=1	=>	illegal
- 		iiiiiii=1,j=0	=>	return to outerContext
- 		iiiiiii=1,j=1	=>	return to outerContext sender/return from outerContext
- 		iiiiiii=2,j=0	=>	return to outerContext outerContext
- 		iiiiiii=2,j=1	=>	return to outerContext outerContext sender/return from outerContext outerContext
- 		etc"
- 
- 	stream nextPut: 94!

Item was removed:
- ----- Method: EncoderForSistaV1>>genSend:numArgs: (in category 'bytecode generation') -----
- genSend: selectorLiteralIndex numArgs: nArgs
- 	| extendedIndex extendedNArgs |
- 	(selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
- 	(nArgs < 0 or: [nArgs > 31]) ifTrue:
- 		[^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
- 	(selectorLiteralIndex < 16 and: [nArgs < 3]) ifTrue: 
- 	 	["128-143	1000 iiii			Send Literal Selector #iiii With 0 Argument
- 		  144-159	1001 iiii			Send Literal Selector #iiii With 1 Arguments
- 		  160-175	1010 iiii			Send Literal Selector #iiii With 2 Arguments"
- 		 stream nextPut: 128 + (nArgs * 16) + selectorLiteralIndex.
- 		 ^self].
- 	(extendedIndex := selectorLiteralIndex) > 31 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 32.
- 		 extendedIndex := extendedIndex \\ 32].
- 	(extendedNArgs := nArgs) > 7 ifTrue:
- 		[self genUnsignedSingleExtendB: extendedNArgs // 8.
- 		 extendedNArgs := extendedNArgs \\ 8].
- 	"234		11101010	i i i i i j j j	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 	stream
- 		nextPut: 234;
- 		nextPut: extendedNArgs + (extendedIndex * 8)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genSendDirectedSuper:numArgs: (in category 'extended bytecode generation') -----
- genSendDirectedSuper: selectorLiteralIndex numArgs: nArgs
- 	| extendedIndex |
- 	(selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
- 	(nArgs < 0 or: [nArgs > 31]) ifTrue:
- 		[^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
- 	(extendedIndex := selectorLiteralIndex) > 31 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 32.
- 		 extendedIndex := extendedIndex \\ 32].
- 	"Bit 6 of the ExtB byte is the directed send flag.  Bit 6 allows for future expansion to up to 255 args."
- 	self genUnsignedSingleExtendB: nArgs // 8 + 64.
- 	"235		11101011	iiiiijjj		Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 	stream
- 		nextPut: 235;
- 		nextPut: nArgs \\ 8 + (extendedIndex * 8)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genSendSpecial:numArgs: (in category 'bytecode generation') -----
- genSendSpecial: specialSelectorIndex numArgs: nArgs
- 	self assert: (specialSelectorIndex between: 1 and: Smalltalk specialSelectorSize).
- 	self assert: nArgs = (Smalltalk specialNargsAt: specialSelectorIndex).
- 	"Special selector sends.
- 		96-111		0110 iiii			Send Arithmetic Message #iiii #(#+ #- #< #> #'<=' #'>=' #= #'~=' #* #/ #'\\' #@ #bitShift: #'//' #bitAnd: #bitOr:)
- 		112-119	01110 iii			Send Special Message #iii #(#at: #at:put: #size ? ? ? #'==' class ? value value: ? ? ? ? ?)"
- 
- 	stream nextPut: specialSelectorIndex + 95!

Item was removed:
- ----- Method: EncoderForSistaV1>>genSendSuper:numArgs: (in category 'bytecode generation') -----
- genSendSuper: selectorLiteralIndex numArgs: nArgs
- 	| extendedIndex extendedNArgs |
- 	(selectorLiteralIndex < 0 or: [selectorLiteralIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'selectorLiteralIndex' index: selectorLiteralIndex range: 0 to: 65535].
- 	(nArgs < 0 or: [nArgs > 31]) ifTrue:
- 		[^self outOfRangeError: 'numArgs' index: nArgs range: 0 to: 31 "!!!!"].
- 	(extendedIndex := selectorLiteralIndex) > 31 ifTrue:
- 		[self genUnsignedSingleExtendA: extendedIndex // 32.
- 		 extendedIndex := extendedIndex \\ 32].
- 	(extendedNArgs := nArgs) > 7 ifTrue:
- 		[self genUnsignedSingleExtendB: extendedNArgs // 8.
- 		 extendedNArgs := extendedNArgs \\ 8].
- 	"235		11101011	iiiiijjj		Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
- 	stream
- 		nextPut: 235;
- 		nextPut: extendedNArgs + (extendedIndex * 8)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genSignedSingleExtendB: (in category 'bytecode generation') -----
- genSignedSingleExtendB: extendedIndex
- 	(extendedIndex between: -128 and: 127) ifFalse:
- 		[^self outOfRangeError: 'index' index: extendedIndex range: -128 to: 127].
- 	"225		11100001	sbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)"
- 	stream
- 		nextPut: 225;
- 		nextPut: (extendedIndex >= 0 ifTrue: [extendedIndex] ifFalse: [extendedIndex + 256]) !

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreFlagExtensionIgnoreStoreCheck:maybeContext:ignoreReadOnlyCheck: (in category 'extended bytecode generation') -----
- genStoreFlagExtensionIgnoreStoreCheck: ignoreStoreCheck maybeContext: maybeContext ignoreReadOnlyCheck: ignoreReadOnlyCheck
- 	"ignoreStoreCheck: 
- 	Can be applied to the long form of store and store pop of literal variable, remote inst var, remote temp, receiver inst var.
- 	If present, the VM does not generate the GC store check. 
- 	The main reasons the compiler can ignore the store check are one of these two:
- 	- the mutated object is always young
- 	- the object stored is immediate
- 	Currently the store check is for the remembered table, but we may have it for tri color marking later. So the compiler cannot really remove the store check if the object stored is old.
- 
- 	maybeContext:
- 	Can be used only with remote instance variable stores and receiver variable stores. If marked, the object can be a context and hence needs specific VM code. Receiver inst var have a separate encoding, temp vectors and literal variable can't be contexts
- 	
- 	ignoreReadOnlyCheck:
- 	no read-only check will be performed by the VM. Normally each store has a read-only check.
- 	"
- 	self genUnsignedSingleExtendB: ignoreStoreCheck asBit + (maybeContext asBit << 1) + (ignoreReadOnlyCheck asBit << 2)!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreInstVar: (in category 'bytecode generation') -----
- genStoreInstVar: instVarIndex
- 	"243		11110011	iiiiiiii		Store Receiver Variable #iiiiiii (+ Extend A * 256)"
- 	self genStoreInstVarLong: instVarIndex maybeContext: false!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreInstVarLong: (in category 'bytecode generation') -----
- genStoreInstVarLong: instVarIndex
- 	"243		11110011	iiiiiiii		Store Receiver Variable #iiiiiii (+ Extend A * 256)"
- 	^self genStoreInstVarLong: instVarIndex maybeContext: instVarIndex < MethodContext instSize!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreInstVarLong:maybeContext: (in category 'bytecode generation') -----
- genStoreInstVarLong: instVarIndex maybeContext: maybeContext
- 	"243		11110011	iiiiiiii		Store Receiver Variable #iiiiiii (+ Extend A * 256)"
- 	(instVarIndex < 0 or: [instVarIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 65535].
- 	maybeContext ifTrue:
- 		[self genStoreFlagExtensionIgnoreStoreCheck: false maybeContext: maybeContext ignoreReadOnlyCheck: false].
- 	instVarIndex > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: instVarIndex // 256].
- 	stream
- 		nextPut: 243;
- 		nextPut: instVarIndex \\ 256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreLiteralVar: (in category 'bytecode generation') -----
- genStoreLiteralVar: literalIndex
- 	"244		11110100	iiiiiiii		Store Literal Variable #iiiiiiii (+ Extend A * 256)"
- 	(literalIndex < 0 or: [literalIndex > 32768]) ifTrue:
- 		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 32768].
- 	literalIndex > 255 ifTrue: 
- 		[self genUnsignedSingleExtendA: literalIndex // 256].
- 	stream
- 		nextPut: 244;
- 		nextPut: literalIndex \\ 256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStorePopInstVar: (in category 'bytecode generation') -----
- genStorePopInstVar: instVarIndex
- 	"200-207	11001 iii			Pop and Store Receiver Variable #iii
- 	 240		11110000	iiiiiiii	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
- 	(instVarIndex < 0 or: [instVarIndex > 7]) ifTrue:
- 		[^self genStorePopInstVarLong: instVarIndex].
- 	stream nextPut: 200 + instVarIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStorePopInstVarLong: (in category 'bytecode generation') -----
- genStorePopInstVarLong: instVarIndex
- 	"240		11110000	iiiiiiii		Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
- 	(instVarIndex < 0 or: [instVarIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 65535].
- 	instVarIndex > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: instVarIndex // 256].
- 	stream
- 		nextPut: 240;
- 		nextPut: instVarIndex \\ 256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStorePopLiteralVar: (in category 'bytecode generation') -----
- genStorePopLiteralVar: literalIndex
- 	"241		11110001	iiiiiiii		Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)"
- 	(literalIndex < 0 or: [literalIndex > 32768]) ifTrue:
- 		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 32768].
- 	literalIndex > 255 ifTrue: 
- 		[self genUnsignedSingleExtendA: literalIndex // 256].
- 	stream
- 		nextPut: 241;
- 		nextPut: literalIndex \\ 256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStorePopRemoteInstanceVariable:inObjectAt: (in category 'extended bytecode generation') -----
- genStorePopRemoteInstanceVariable: instanceVariableIndex inObjectAt: tempIndex
- 	"*253	(3)	11111101 	kkkkkkkk	sjjjjjjj		Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
- 
- 	(instanceVariableIndex < 0 or: [instanceVariableIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'instanceVariableIndex' index: instanceVariableIndex range: 0 to: 65535].
- 	(tempIndex < 0 or: [tempIndex >= 128]) ifTrue:
- 		[^self outOfRangeError: 'tempVectorIndex' index: tempIndex range: 0 to: 127].
- 	instanceVariableIndex > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: instanceVariableIndex // 256].
- 	stream
- 		nextPut: 253;
- 		nextPut: instanceVariableIndex \\ 256;
- 		nextPut: 1 << 7 + tempIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStorePopRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
- genStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex
- 	"*	253	(3)	11111101 	kkkkkkkk	sjjjjjjj		Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
- 	(tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
- 		[^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
- 	(tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
- 		[^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
- 	stream
- 		nextPut: 253;
- 		nextPut: tempIndex;
- 		nextPut: tempVectorIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStorePopTemp: (in category 'bytecode generation') -----
- genStorePopTemp: tempIndex
- 	"208-215	11010 iii			Pop and Store Temporary Variable #iii
- 	 242		11110010	iiiiiiii	Pop and Store Temporary Variable #iiiiiiii"
- 	(tempIndex < 0 or: [tempIndex > 63]) ifTrue:
- 		[^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
- 	tempIndex < 8 ifTrue:
- 		[stream nextPut: 208 + tempIndex.
- 		 ^self].
- 	stream
- 		nextPut: 242;
- 		nextPut: tempIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreRemoteInstanceVariable:inObjectAt: (in category 'extended bytecode generation') -----
- genStoreRemoteInstanceVariable: instanceVariableIndex inObjectAt: tempIndex
- 	"*252	(3)	11111100 	kkkkkkkk	sjjjjjjj		Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
- 
- 	(instanceVariableIndex < 0 or: [instanceVariableIndex > 65535]) ifTrue:
- 		[^self outOfRangeError: 'instanceVariableIndex' index: instanceVariableIndex range: 0 to: 65535].
- 	(tempIndex < 0 or: [tempIndex >= 128]) ifTrue:
- 		[^self outOfRangeError: 'tempVectorIndex' index: tempIndex range: 0 to: 127].
- 	instanceVariableIndex > 255 ifTrue:
- 		[self genUnsignedSingleExtendA: instanceVariableIndex // 256].
- 	stream
- 		nextPut: 252;
- 		nextPut: instanceVariableIndex \\ 256;
- 		nextPut: 1 << 7 + tempIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
- genStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex
- 	"*252	(3)	11111100 	kkkkkkkk	sjjjjjjj		Store Temp At kkkkkkkk In Temp Vector At: jjjjjjj s = 1 implies remote inst var access instead of remote temp vector access"
- 	(tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
- 		[^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
- 	(tempVectorIndex < 0 or: [tempVectorIndex >= 128]) ifTrue:
- 		[^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 127].
- 	stream
- 		nextPut: 252;
- 		nextPut: tempIndex;
- 		nextPut: tempVectorIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genStoreTemp: (in category 'bytecode generation') -----
- genStoreTemp: tempIndex
- 	"245		11110110	iiiiiiii		Store Temporary Variable #iiiiiiii"
- 	(tempIndex < 0 or: [tempIndex > 63]) ifTrue:
- 		[^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
- 	stream
- 		nextPut: 245;
- 		nextPut: tempIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genTrap (in category 'extended bytecode generation') -----
- genTrap
- 	"217		11011001			Unconditionnal trap"
- 	stream nextPut: 217!

Item was removed:
- ----- Method: EncoderForSistaV1>>genUnsignedMultipleExtendA: (in category 'bytecode generation') -----
- genUnsignedMultipleExtendA: extendedIndex
- 	"224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)"
- 	extendedIndex > 255 ifTrue:
- 		[self genUnsignedMultipleExtendA: extendedIndex // 256].
- 	stream
- 		nextPut: 224;
- 		nextPut: extendedIndex \\ 256!

Item was removed:
- ----- Method: EncoderForSistaV1>>genUnsignedSingleExtendA: (in category 'bytecode generation') -----
- genUnsignedSingleExtendA: extendedIndex
- 	(extendedIndex between: 0 and: 255) ifFalse:
- 		[^self outOfRangeError: 'index' index: extendedIndex range: 0 to: 255].
- 	"224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
- 	ExtA is normally unsigned."
- 	stream
- 		nextPut: 224;
- 		nextPut: extendedIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>genUnsignedSingleExtendB: (in category 'bytecode generation') -----
- genUnsignedSingleExtendB: extendedIndex
- 	(extendedIndex between: 0 and: 255) ifFalse:
- 		[^self outOfRangeError: 'index' index: extendedIndex range: 0 to: 255].
- 	"225		11100001	sbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B).
- 	ExtB is normally signed"
- 	stream
- 		nextPut: 225;
- 		nextPut: extendedIndex!

Item was removed:
- ----- Method: EncoderForSistaV1>>isSpecialLiteralForPush: (in category 'special literal encodings') -----
- isSpecialLiteralForPush: literal
- 	^literal == false
- 	  or: [literal == true
- 	  or: [literal == nil
- 	  or: [(literal isInteger and: [literal between: -32768 and: 32767])
- 	  or: [(literal isCharacter and: [literal asInteger between: 0 and: 65535])]]]]!

Item was removed:
- ----- Method: EncoderForSistaV1>>maxIndexableLiterals (in category 'accessing') -----
- maxIndexableLiterals
- 	"Answer the maximum number of literals supported by the receiver's
- 	 bytecode set."
- 	^65536!

Item was removed:
- ----- Method: EncoderForSistaV1>>supportsClosureOpcodes (in category 'bytecode generation') -----
- supportsClosureOpcodes
- 	^true!

Item was removed:
- ----- Method: EncoderForSistaV1>>supportsFullBlocks (in category 'testing') -----
- supportsFullBlocks
- 	"Answer if the instruction set supports full closures (closure creation from
- 	 specfic methods instead of bytecodes embedded in an outer home method)."
- 	
- 	^true!

Item was removed:
- ----- Method: EncoderForV3>>isSpecialLiteralForPush: (in category '*BytecodeSets-special literal encodings') -----
- isSpecialLiteralForPush: literal
- 	^literal == false
- 	  or: [literal == true
- 	  or: [literal == nil
- 	  or: [literal isInteger and: [literal between: -1 and: 2]]]]!

Item was removed:
- BlockClosure variableSubclass: #FullBlockClosure
- 	instanceVariableNames: 'receiver'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'BytecodeSets-SistaV1'!
- 
- !FullBlockClosure commentStamp: 'cb 5/24/2016 11:30' prior: 0!
- I contain a sequence of operations. I am defined by Smalltalk expressions inside square brackets. I permit to defer the enclosed operations until I execute a variant of #value. I can have my own arguments and temporaries as a regular method, but I am also able to use external variables: my enclosing method or block temporaries, arguments and receiver.
- 
- examples :
- [ 1 + 2 ] value
- [ :arg | 
- 	| temp | 
- 	temp := arg. 
- 	temp ] value: 5
- [ ^ 5 ] value
- 
- My return value corresponds to my final expression. A non local return (^) has the same effect as if I did not exist: it returns from my enclosing method, even if I'm nested in other blocks. 
- 
- Implementation:
- 
- A FullBlockClosure is a closure that can be independent of any outerContext if desired.  It has its own method (currently reusing the startpc inst var) and its own receiver.  outerContext can be either a MethodContext/Context or nil.
- 
- This closure design, implemented by Eliot Miranda and Clement Bera along the sista work aims to simplify the block closure model while enhacing its capabilities. It allows lazy compilation of closures and fast machine code dispatch in Cog's JIT, while allowing inlining of methods and blocks to be independent from their enclosing blocks.
- 
- At closure creation time, the bytecode specifies:
- - the compiledBlock/compiledMethod to execute when executing this block's code (in the literal frame)
- - if the receiver is the current receiver or a receiver passed on stack before the copied values.
- - if the closure needs an outerContext. outerContexts are used for non local returns and debugging. Blocks with non local returns have to set their outerContext. For other blocks (97% of blocks), it's a trade-off between performance and debuggability.
- 
- Instance Variables
- 	outerContext:			<Context/MethodContext|nil> 
- 	compiledBlock(startpc) <CompiledMethod/CompiledBlock>
- 	numArgs				<SmallInteger> 
- 	receiver:				<Object>
- !

Item was removed:
- ----- Method: FullBlockClosure>>asContextWithSender: (in category 'private') -----
- asContextWithSender: aContext
- 	"Inner private support method for evaluation.  Do not use unless you know what you're doing."
- 
- 	^(MethodContext newForMethod: self compiledBlock)
- 		setSender: aContext
- 		receiver: self receiver
- 		method: self compiledBlock
- 		closure: self
- 		startpc: self startpc;
- 		privRefresh!

Item was removed:
- ----- Method: FullBlockClosure>>compiledBlock (in category 'accessing') -----
- compiledBlock
- 	"To be able to inherit from BlockClosure"
- 	^ startpc!

Item was removed:
- ----- Method: FullBlockClosure>>compiledBlock: (in category 'accessing') -----
- compiledBlock: aCompiledMethod
- 	"To be able to inherit from BlockClosure"
- 	startpc := aCompiledMethod!

Item was removed:
- ----- Method: FullBlockClosure>>home (in category 'accessing') -----
- home
- 	^ outerContext ifNotNil: [ outerContext home ]!

Item was removed:
- ----- Method: FullBlockClosure>>method (in category 'accessing') -----
- method
- 	^ self compiledBlock!

Item was removed:
- ----- Method: FullBlockClosure>>numArgs: (in category 'accessing') -----
- numArgs: n
- 	numArgs := n!

Item was removed:
- ----- Method: FullBlockClosure>>numTemps (in category 'accessing') -----
- numTemps
- 	^ self compiledBlock numTemps!

Item was removed:
- ----- Method: FullBlockClosure>>outerContext: (in category 'accessing') -----
- outerContext: ctxt
- 	outerContext := ctxt!

Item was removed:
- ----- Method: FullBlockClosure>>receiver (in category 'accessing') -----
- receiver
- 	^ receiver!

Item was removed:
- ----- Method: FullBlockClosure>>receiver: (in category 'accessing') -----
- receiver: anObject
- 	receiver := anObject!

Item was removed:
- ----- Method: FullBlockClosure>>startpc (in category 'accessing') -----
- startpc
- 	^ self compiledBlock initialPC!

Item was removed:
- ----- Method: FullBlockClosure>>value (in category 'evaluating') -----
- value
- 	"Activate the receiver, creating a closure activation (MethodContext)
- 	 whose closure is the receiver and whose caller is the sender of this
- 	 message. Supply the copied values to the activation as its copied
- 	 temps. Primitive. Essential."
- 	<primitive: 207>
- 	| newContext |
- 	numArgs ~= 0 ifTrue:
- 		[self numArgsError: 0].
- 	false
- 		ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
- 			[newContext := self asContextWithSender: thisContext sender.
- 			thisContext privSender: newContext]
- 		ifFalse: [self primitiveFailed]!

Item was removed:
- ----- Method: FullBlockClosure>>value: (in category 'evaluating') -----
- value: firstArg
- 	"Activate the receiver, creating a closure activation (MethodContext)
- 	 whose closure is the receiver and whose caller is the sender of this
- 	 message. Supply the argument and copied values to the activation
- 	 as its argument and copied temps. Primitive. Essential."
- 	<primitive: 207>
- 	| newContext |
- 	numArgs ~= 1 ifTrue:
- 		[self numArgsError: 1].
- 	false
- 		ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
- 			[newContext := self asContextWithSender: thisContext sender.
- 			newContext at: 1 put: firstArg.
- 			thisContext privSender: newContext]
- 		ifFalse: [self primitiveFailed]!

Item was removed:
- ----- Method: FullBlockClosure>>value:value: (in category 'evaluating') -----
- value: firstArg value: secondArg
- 	"Activate the receiver, creating a closure activation (MethodContext)
- 	 whose closure is the receiver and whose caller is the sender of this
- 	 message. Supply the arguments and copied values to the activation
- 	 as its arguments and copied temps. Primitive. Essential."
- 	<primitive: 207>
- 	| newContext |
- 	numArgs ~= 2 ifTrue:
- 		[self numArgsError: 2].
- 	false
- 		ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
- 			[newContext := self asContextWithSender: thisContext sender.
- 			newContext at: 1 put: firstArg.
- 			newContext at: 2 put: secondArg.
- 			thisContext privSender: newContext]
- 		ifFalse: [self primitiveFailed]!

Item was removed:
- ----- Method: FullBlockClosure>>value:value:value: (in category 'evaluating') -----
- value: firstArg value: secondArg value: thirdArg
- 	"Activate the receiver, creating a closure activation (MethodContext)
- 	 whose closure is the receiver and whose caller is the sender of this
- 	 message. Supply the arguments and copied values to the activation
- 	 as its arguments and copied temps. Primitive. Essential."
- 	<primitive: 207>
- 	| newContext |
- 	numArgs ~= 3 ifTrue:
- 		[self numArgsError: 3].
- 	false
- 		ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
- 			[newContext := self asContextWithSender: thisContext sender.
- 			newContext at: 1 put: firstArg.
- 			newContext at: 2 put: secondArg.
- 			newContext at: 3 put: thirdArg.
- 			thisContext privSender: newContext]
- 		ifFalse: [self primitiveFailed]!

Item was removed:
- ----- Method: FullBlockClosure>>value:value:value:value: (in category 'evaluating') -----
- value: firstArg value: secondArg value: thirdArg value: fourthArg
- 	"Activate the receiver, creating a closure activation (MethodContext)
- 	 whose closure is the receiver and whose caller is the sender of this
- 	 message. Supply the arguments and copied values to the activation
- 	 as its arguments and copied temps. Primitive. Essential."
- 	<primitive: 207>
- 	| newContext |
- 	numArgs ~= 4 ifTrue:
- 		[self numArgsError: 4].
- 	false
- 		ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
- 			[newContext := self asContextWithSender: thisContext sender.
- 			newContext at: 1 put: firstArg.
- 			newContext at: 2 put: secondArg.
- 			newContext at: 3 put: thirdArg.
- 			newContext at: 4 put: fourthArg.
- 			thisContext privSender: newContext]
- 		ifFalse: [self primitiveFailed]!

Item was removed:
- ----- Method: FullBlockClosure>>valueNoContextSwitch (in category 'evaluating') -----
- valueNoContextSwitch
- 	"An exact copy of BlockClosure>>value except that this version will not preempt
- 	 the current process on block activation if a higher-priority process is runnable.
- 	 Primitive. Essential."
- 	<primitive: 209>
- 	numArgs ~= 0 ifTrue:
- 		[self numArgsError: 0].
- 	self primitiveFailed!

Item was removed:
- ----- Method: FullBlockClosure>>valueNoContextSwitch: (in category 'evaluating') -----
- valueNoContextSwitch: anArg
- 	"An exact copy of BlockClosure>>value: except that this version will not preempt
- 	 the current process on block activation if a higher-priority process is runnable.
- 	 Primitive. Essential."
- 	<primitive: 209>
- 	numArgs ~= 1 ifTrue:
- 		[self numArgsError: 1].
- 	self primitiveFailed!

Item was removed:
- ----- Method: FullBlockClosure>>valueWithArguments: (in category 'evaluating') -----
- valueWithArguments: anArray
- 	"Activate the receiver, creating a closure activation (MethodContext)
- 	 whose closure is the receiver and whose caller is the sender of this
- 	 message. Supply the arguments in an anArray and copied values to
- 	 the activation as its arguments and copied temps. Primitive. Essential."
- 	<primitive: 208>
- 	| newContext |
- 	numArgs ~= anArray size ifTrue:
- 		[self numArgsError: anArray size].
- 	false
- 		ifTrue: "Old code to simulate the closure value primitive on VMs that lack it."
- 			[newContext := self asContextWithSender: thisContext sender.
- 			1 to: numArgs do:
- 				[:i| newContext at: i put: (anArray at: i)].
- 			thisContext privSender: newContext]
- 		ifFalse: [self primitiveFailed]!

Item was removed:
- ----- Method: InstructionClient>>blockReturnConstant: (in category '*BytecodeSets-instruction decoding') -----
- blockReturnConstant: value
- 	"Return Constant From Block bytecode."
- 
- !

Item was removed:
- ----- Method: InstructionClient>>directedSuperSend:numArgs: (in category '*BytecodeSets-instruction decoding') -----
- directedSuperSend: selector numArgs: numArgs
- 	"Send Message Above Specific Class With Selector, selector, bytecode.
- 	 Start the lookup above the class that is the value of the association on
- 	 top of stack. The arguments  of the message are found in the top numArgs
- 	 stack locations beneath the association, and the receiver just below them."!

Item was removed:
- ----- Method: InstructionClient>>pushFullClosure:numCopied: (in category '*BytecodeSets-instruction decoding') -----
- pushFullClosure: compiledBlock numCopied: numCopied
- 	"Creates and push a fullBlockClosure"!

Item was removed:
- ----- Method: InstructionPrinter>>blockReturnConstant: (in category '*BytecodeSets-instruction decoding') -----
- blockReturnConstant: value 
- 	"Print the Return Constant From Block bytecode."
- 
- 	self print: 'blockReturn: ', value printString!

Item was removed:
- ----- Method: InstructionPrinter>>directedSuperSend:numArgs: (in category '*BytecodeSets-instruction decoding') -----
- directedSuperSend: selector "<Symbol>" numArgs: numArgs "<SmallInteger>"
- 	self print: 'directedSuperSend: ' , (self stringForSelector: selector numArgs: numArgs)!

Item was removed:
- ----- Method: InstructionPrinter>>pushFullClosure:numCopied: (in category '*BytecodeSets-instruction decoding') -----
- pushFullClosure: cb numCopied: num
- 	self print: 'pushFullClosure: ' , cb selector , ' numCopied: ' , num!

Item was removed:
- ----- Method: InstructionPrinter>>trapIfNotInstanceOf: (in category '*BytecodeSets-SistaV1-decoding') -----
- trapIfNotInstanceOf: behaviorOrArrayOfBehavior
- 	"If the top of stack is not an instance of either the argument, or, if the argument is an Array,
- 	  any of the elements of the argument, send the class trap message to the current context."
- 	self print: 'trapIfNotInstanceOf: ', behaviorOrArrayOfBehavior printString!

Item was removed:
- ----- Method: InstructionStream>>interpretNext2ByteSistaV1Instruction:for:extA:extB:startPC: (in category '*BytecodeSets-SistaV1-decoding') -----
- interpretNext2ByteSistaV1Instruction: bytecode for: client extA: extA extB: extB startPC: startPC
- 	"Send to the argument, client, a message that specifies the next instruction.
- 	 This method handles the two-byte codes.
- 	 For a table of the bytecode set, see EncoderForV1's class comment."
- 
- 	| byte method |
- 	method := self method.
- 	byte := self method at: pc.
- 	pc := pc + 1.
- 	"We do an inline quasi-binary search on bytecode"
- 	bytecode < 234 ifTrue: "pushes"
- 		[bytecode < 231 ifTrue:
- 			[bytecode < 229 ifTrue:
- 				[| literal |
- 				 bytecode = 226 ifTrue:
- 					[^client pushReceiverVariable: (extA bitShift: 8) + byte].
- 				 literal := method literalAt: (extA bitShift: 8) + byte + 1.
- 				 bytecode = 227 ifTrue:
- 					[^client pushLiteralVariable: literal].
- 				 ^client pushConstant: literal].
- 			bytecode = 229 ifTrue:
- 				[^client pushTemporaryVariable: byte]. 
- 			^client pushClosureTemps: byte]. 
- 		bytecode = 231 ifTrue:
- 			[^byte < 128
- 				ifTrue: [client pushNewArrayOfSize: byte]
- 				ifFalse: [client pushConsArrayWithElements: byte - 128]].
- 		bytecode = 232 ifTrue:
- 			[^client pushConstant: (extB bitShift: 8) + byte].
- 		^client pushConstant: (Character value: (extB bitShift: 8) + byte)].
- 	bytecode < 240 ifTrue: "sends and jump"
- 		[bytecode < 236 ifTrue: "sends"
- 			[(bytecode = 235 and: [extB >= 64]) ifTrue:
- 				[^client
- 					directedSuperSend: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
- 					numArgs: (extB - 64 bitShift: 3) + (byte \\ 8)].
- 			 ^client
- 				send: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
- 				super: bytecode = 235
- 				numArgs: (extB bitShift: 3) + (byte \\ 8)].
- 		 bytecode = 236 ifTrue:
- 			[^self unusedBytecode: client at: startPC].
- 		bytecode = 237 ifTrue:
- 			[^client jump: (extB bitShift: 8) + byte].
- 		 ^client jump: (extB bitShift: 8) + byte if: bytecode = 238].
- 	bytecode < 243 ifTrue:
- 		[bytecode = 240 ifTrue:
- 			[^client popIntoReceiverVariable: (extA bitShift: 8) + byte].
- 		 bytecode = 241 ifTrue:
- 			[^client popIntoLiteralVariable: (method literalAt: (extA bitShift: 8) + byte + 1)].
- 		 ^client popIntoTemporaryVariable: byte].
- 	bytecode = 243 ifTrue:
- 		[^client storeIntoReceiverVariable: (extA bitShift: 8) + byte].
- 	bytecode = 244 ifTrue:
- 		[^client storeIntoLiteralVariable: (method literalAt: (extA bitShift: 8) + byte + 1)].
- 	bytecode = 245 ifTrue:
- 		[^client storeIntoTemporaryVariable: byte].
- 	"246-247	1111011 i	xxxxxxxx	UNASSIGNED"
- 	^self unusedBytecode: client at: startPC!

Item was removed:
- ----- Method: InstructionStream>>interpretNext3ByteSistaV1Instruction:for:extA:extB:startPC: (in category '*BytecodeSets-SistaV1-decoding') -----
- interpretNext3ByteSistaV1Instruction: bytecode for: client extA: extA extB: extB startPC: startPC
- 	"Send to the argument, client, a message that specifies the next instruction.
- 	 This method handles the three-byte codes.
- 	 For a table of the bytecode set, see EncoderForSistaV1's class comment."
- 
- 	| method byte2 byte3 literal |
- 	method := self method.
- 	byte2 := method at: pc.
- 	byte3 := method at: pc + 1.
- 	pc := pc + 2.
- 
- 	"**	248	(2)	11111000 	iiiiiiii		mssjjjjj		Call Primitive #iiiiiiii + (jjjjj * 256) 
- 									m=1 means inlined primitive, no hard return after execution. 
- 									ss defines the unsafe operation set used to encode the operations. 
- 									(ss = 0 means sista unsafe operations, ss = 01 means lowcode operations, other numbers are not used)
- 									Lowcode inlined primitives may have extensions."
- 	bytecode = 248 ifTrue:
- 		[| primitiveSetSelector primitiveNumber |
- 		 byte3 < 128 ifTrue:
- 			[ "Maybe this should be restricted to the 13 bit primitiveNumber too..."
- 			 ^client callPrimitive: byte2 + (byte3 bitShift: 8)].
- 		 primitiveSetSelector := (byte3 bitShift: -5) bitAnd: 3.
- 		 primitiveNumber := byte2 + ((byte3 bitAnd: 31) bitShift: 8).
- 		 primitiveSetSelector = 0 ifTrue: "Sista inline primitives"
- 			[^client callInlinePrimitive: byte2 + (byte3 - 128 bitShift: 8)].
- 		 primitiveSetSelector = 1 ifTrue: "Lowcode inline primitives"
- 			[^client callLowcodeInlinePrimitive: byte2 + (byte3 - 128 bitShift: 8) extA: extA extB: extB].
- 		 "fall through to ^self unusedBytecode: client at: startPC below"].
- 
- 	"*	249		11111001	xxxxxxxx	siyyyyyy	push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
- 	bytecode = 249 ifTrue:
- 		[literal := method literalAt: (extA bitShift: 8) + byte2 + 1.
- 		 (byte3 noMask: 16rC0) ifTrue:
- 			[^client pushFullClosure: literal numCopied: byte3].
- 		 ^client
- 			pushFullClosure: literal
- 			numCopied: (byte3 bitAnd: 16r3F)
- 			receiverOnStack: (byte3 anyMask: 16r80)
- 			ignoreOuterContext: (byte3 anyMask: 16r40)].
- 	bytecode = 250 ifTrue:
- 		["**	250  11111010  eeiiikkk  jjjjjjjj  Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
- 		 ^client
- 			pushClosureCopyNumCopiedValues: ((byte2 bitShift: -3) bitAnd: 7) + (extA // 16 bitShift: 3)
- 			numArgs: (byte2 bitAnd: 7) + (extA \\ 16 bitShift: 3)
- 			blockSize: byte3 + (extB bitShift: 8)].
- 	bytecode = 251 ifTrue:
- 		[^client pushRemoteTemp: byte2 inVectorAt: byte3].
- 	bytecode = 252 ifTrue:
- 		[^client storeIntoRemoteTemp: byte2 inVectorAt: byte3].
- 	bytecode = 253 ifTrue:
- 		[^client popIntoRemoteTemp: byte2 inVectorAt: byte3].
- 	"**	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
- 	bytecode = 254 ifTrue: "The sign bit of extB inverts the operation.  Would like to have extB < -128, but this is good enough for now."
- 		[literal := method literalAt: (extA bitShift: 8) + byte2 + 1.
- 		 extB < 0 ifTrue: [^client branchIfInstanceOf: literal distance: (extB + 128 bitShift: 8) + byte3].
- 		 ^client branchIfNotInstanceOf: literal distance: (extB bitShift: 8) + byte3].
- 	^self unusedBytecode: client at: startPC!

Item was removed:
- ----- Method: InstructionStream>>interpretNextSistaV1InstructionFor: (in category '*BytecodeSets-SistaV1-decoding') -----
- interpretNextSistaV1InstructionFor: client
- 	"Send to the argument, client, a message that specifies the next instruction."
- 
- 	| byte div16 offset method extA extB savedPC |
- 	method := self method.
- 	"For a table of the bytecode set, see EncoderForSistaV1's class comment."
- 	"consume and compute any extensions first."
- 	extA := extB := 0.
- 	savedPC := pc.
- 	[byte := self method at: pc.
- 	 pc := pc + 1.
- 	 byte >= 16rE0 and: [byte <= 16rE1]] whileTrue:
- 		[| extByte |
- 		 extByte := self method at: pc.
- 		 pc := pc + 1.
- 		 byte = 16rE0
- 			ifTrue:
- 				[extA := (extA bitShift: 8) + extByte]
- 			ifFalse:
- 				[extB := (extB = 0 and: [extByte > 127])
- 							ifTrue: [extByte - 256]
- 							ifFalse: [(extB bitShift: 8) + extByte]]].
- 	div16 := byte // 16.
- 	offset := byte \\ 16.
- 	"We do an inline quasi-binary search on each of the possible 16 values of div16"
- 	div16 < 11 ifTrue:
- 		[div16 < 6 ifTrue:
- 			[div16 < 4 ifTrue:
- 				[div16 < 2 ifTrue:
- 					[div16 = 0 ifTrue:
- 						 [^client pushReceiverVariable: offset].
- 					^client pushLiteralVariable: (method literalAt: offset + 1)]. "div16 = 1"
- 				 ^client pushConstant: (method literalAt: byte \\ 32 + 1)].
- 			 div16 = 4 ifTrue:
- 				[offset < 12 ifTrue:
- 					[^client pushTemporaryVariable: offset].
- 				 offset = 12 ifTrue:
- 					[^client pushReceiver].
- 				 offset = 13 ifTrue:
- 					[^client pushConstant: true].
- 				 offset = 14 ifTrue:
- 					[^client pushConstant: false].
- 				 offset = 15 ifTrue:
- 					[^client pushConstant: nil]].
- 			"div16 = 5"
- 			 offset < 2 ifTrue:
- 				[^client pushConstant: offset].
- 			 offset = 2 ifTrue:
- 				[^self interpretSistaV1ExtendedPush: extB for: client].
- 			 offset = 3 ifTrue:
- 				[^client doDup].
- 			
- 			 offset = 8 ifTrue:
- 				[^client methodReturnReceiver].
- 			 offset = 9 ifTrue:
- 				[^client methodReturnConstant: true].
- 			 offset = 10 ifTrue:
- 				[^client methodReturnConstant: false].
- 			 offset = 11 ifTrue:
- 				[^client methodReturnConstant: nil].
- 			 offset = 12 ifTrue:
- 				[^client methodReturnTop].
- 			 offset = 13 ifTrue:
- 				[^client blockReturnConstant: nil].
- 			 offset = 14 ifTrue:
- 				[^client blockReturnTop].
- 			 offset = 15 ifTrue:
- 				[^client doNop].
- 			 ^self unusedBytecode: client at: savedPC].
- 		"short sends"
- 		div16 = 6 ifTrue:
- 			[^client
- 				send: (Smalltalk specialSelectorAt: offset + 1)
- 				super: false
- 				numArgs: (Smalltalk specialNargsAt: offset + 1)].
- 		 div16 = 7 ifTrue:
- 			[^client
- 				send: (Smalltalk specialSelectorAt: offset + 17)
- 				super: false
- 				numArgs: (Smalltalk specialNargsAt: offset + 17)].
- 		^client
- 			send: (method literalAt: offset + 1)
- 			super: false
- 			numArgs: div16 - 8].
- 	"div16 >= 11; bytecode >= 176"
- 	div16 < 14 ifTrue:
- 		[div16 = 11 ifTrue:
- 			[offset < 8 ifTrue:
- 				[^client jump: offset + 1].
- 			 ^client jump: offset - 7 if: true].
- 		 div16 = 12 ifTrue:
- 			[offset < 8 ifTrue:
- 				[^client jump: offset + 1 if: false].
- 			 ^client popIntoReceiverVariable: offset - 8].
- 		 "div16 = 13"
- 		 offset < 8 ifTrue:
- 		 	[^client popIntoTemporaryVariable: offset].
- 		 offset = 8 ifTrue: [ ^ client doPop ].
- 		 offset = 9 ifTrue: [ ^ client trap ].
- 		 ^self unusedBytecode: client at: savedPC].
- 	"2 byte and 3 byte codes"
- 	byte < 248 ifTrue:
- 		[^self interpretNext2ByteSistaV1Instruction: byte for: client extA: extA extB: extB startPC: savedPC].
- 	^self interpretNext3ByteSistaV1Instruction: byte for: client extA: extA extB: extB startPC: savedPC!

Item was removed:
- ----- Method: InstructionStream>>interpretSistaV1ExtendedPush:for: (in category '*BytecodeSets-SistaV1-decoding') -----
- interpretSistaV1ExtendedPush: extB for: client
- 	"Implement the extended push for non-zero extensions."
- 	"*	82			01010010			Push thisContext, (then Extend B = 1 => push thisProcess)"
- 	extB = 0 ifTrue:
- 		[^client pushActiveContext].
- 	extB = 1 ifTrue:
- 		[^client pushActiveProcess].
- 	self error: 'undefined extended push'!

Item was removed:
- ----- Method: InstructionStream>>interpretSistaV1Jump (in category '*BytecodeSets-SistaV1-decoding') -----
- interpretSistaV1Jump
- 	"If the instruction at pc is an unconditional jump, interpret it, advancing the pc,
- 	 and answering the jump distance. Otherwise answer nil."
- 
- 	"	176-183	10110 iii				Jump iii + 1 (i.e., 1 through 8)
- 	 *	225/16rE1	11100001	sbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	 *	237		11101101	iiiiiiii		Jump #iiiiiiii (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
- 	| method byte nextpc extB |
- 	method := self method.
- 	"consume and compute any extension first."
- 	extB := 0.
- 	nextpc := pc. "must not advance pc unless this is a jump."
- 	[byte := self method at: nextpc.
- 	 nextpc := nextpc + 1.
- 	 byte = 16rE1] whileTrue:
- 		[| extByte |
- 		 extByte := self method at: nextpc.
- 		 nextpc := nextpc + 1.
- 		 extB := (extB = 0 and: [extByte > 127])
- 					ifTrue: [extByte - 256]
- 					ifFalse: [(extB bitShift: 8) + extByte]].
- 	(byte between: 176 and: 183) ifTrue:
- 		[pc := nextpc.
- 		 ^byte - 191].
- 	byte = 237 ifTrue:
- 		[byte := method at: nextpc.
- 		 pc := nextpc + 1.
- 		 ^(extB bitShift: 8) + byte].
- 	^nil!

Item was removed:
- ----- Method: InstructionStream>>interpretSistaV1JumpIfCond (in category '*BytecodeSets-SistaV1-decoding') -----
- interpretSistaV1JumpIfCond
- 	"If the instruction at pc is a conditional jump, interpret it, advancing the pc,
- 	 and answering the jump distance. Otherwise answer nil."
- 
- 	"	184-191	10111 iii				Pop and Jump 0n True iii +1 (i.e., 1 through 8)
- 		192-199	11000 iii				Pop and Jump 0n False iii +1 (i.e., 1 through 8)
- 	 *	225/E1		11100001	sbbbbbbb	Extend B (Ext B = Ext B prev * 256 + Ext B)
- 	 *	238		11101110	iiiiiiii		Pop and Jump 0n True #iiiiiiii (+ Extend B * 256, where Extend B >= 0)
- 	 *	239		11101111	iiiiiiii		Pop and Jump 0n False #iiiiiiii (+ Extend B * 256, where Extend B >= 0)"
- 	| method byte nextpc extB |
- 	method := self method.
- 	"consume and compute any extension first."
- 	extB := 0.
- 	nextpc := pc. "must not advance pc unless this is a jump."
- 	[byte := self method at: nextpc.
- 	 nextpc := nextpc + 1.
- 	 byte = 16rE1] whileTrue:
- 		[| extByte |
- 		 extByte := self method at: nextpc.
- 		 nextpc := nextpc + 1.
- 		 extB := (extB = 0 and: [extByte > 127])
- 					ifTrue: [extByte - 256]
- 					ifFalse: [(extB bitShift: 8) + extByte]].
- 	(byte between: 184 and: 199) ifTrue:
- 		[pc := nextpc.
- 		 ^(byte bitAnd: 7) + 1].
- 	(byte between: 238 and: 239) ifTrue:
- 		[byte := method at: nextpc.
- 		 pc := nextpc + 1.
- 		 ^(extB bitShift: 8) + byte].
- 	^nil!

Item was removed:
- ----- Method: MethodNode>>primitive (in category '*BytecodeSets-accessing') -----
- primitive
- 	^primitive!

Item was removed:
- ----- Method: StackDepthFinder>>branchIfNotInstanceOf:distance: (in category '*BytecodeSets-SistaV1-decoding') -----
- branchIfNotInstanceOf: behaviorOrArrayOfBehavior distance: delta 
- 	self drop.
- 	self doJump: delta!



More information about the Vm-dev mailing list