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

commits at source.squeak.org commits at source.squeak.org
Sat May 17 00:14:35 UTC 2014


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

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

Name: BytecodeSets-eem.1
Author: eem
Time: 16 May 2014, 5:14:31.444 pm
UUID: ed4a147c-9560-4e82-8daf-914b1afe14f5
Ancestors: 

Newspeak bytecode sets NewsqueakV3 and NewsqueakV4
using the newer CompiledMethod>>encoderClass
scheme (i.e. no vague "alternate" set).

Needs Compiler-eem.281 plus an as-yet-unpublished
Kernel that provides CompiledMethod>>encoderClass.

==================== Snapshot ====================

SystemOrganization addCategory: #'BytecodeSets-NewsqueakV3'!
SystemOrganization addCategory: #'BytecodeSets-NewsqueakV4'!

----- Method: InstructionPrinter>>pushExplicitOuter: (in category '*BytecodeSets-NewsqueakV3-instruction decoding') -----
pushExplicitOuter: n 
	"Print the Push Active Context's Receiver for an outer send of aSymbol on Top Of Stack bytecode."

	self print: 'pushExplicitOuter: ', n asString!

----- Method: InstructionPrinter>>pushImplicitReceiverForMessage: (in category '*BytecodeSets-NewsqueakV3-instruction decoding') -----
pushImplicitReceiverForMessage: aSymbol 
	"Print the Push Active Context's Receiver for an outer send of aSymbol on Top Of Stack bytecode."

	self print: 'pushImplicitReceiverFor: ', aSymbol asString!

----- Method: InstructionPrinter>>sendToAbsentDynamicSuperclass:numArgs: (in category '*BytecodeSets-NewsqueakV4-instruction decoding') -----
sendToAbsentDynamicSuperclass: selector "<Symbol>" numArgs: arity "<SmallInteger>"
	self print: '(absent receiver) dynamicSuperSend: ', selector!

----- Method: InstructionPrinter>>sendToAbsentImplicitReceiver:numArgs: (in category '*BytecodeSets-NewsqueakV4-instruction decoding') -----
sendToAbsentImplicitReceiver: selector "<Symbol>" numArgs: arity "<SmallInteger>"
	self print: '(absent receiver) implicitReceiverSend: ', selector!

EncoderForV3PlusClosures subclass: #EncoderForNewsqueakV3
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'BytecodeSets-NewsqueakV3'!

----- Method: EncoderForNewsqueakV3 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 interpretNextNSV3InstructionFor: aClient!

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

----- Method: InstructionStream>>interpretNext2ByteNSV4Instruction:for:extA:extB:startPC: (in category '*BytecodeSets-NewsqueakV4-decoding') -----
interpretNext2ByteNSV4Instruction: 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 EncoderForNewsqueakV2'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 < 235 ifTrue:
		[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 pushConstant: (extB bitShift: 8) + byte].
			^client pushTemporaryVariable: byte].
		bytecode = 231 ifTrue:
			[^byte < 128
				ifTrue: [client pushNewArrayOfSize: byte]
				ifFalse: [client pushConsArrayWithElements: byte - 128]].
		bytecode = 232 ifTrue:
			[^client storeIntoReceiverVariable: (extA bitShift: 8) + byte].
		bytecode = 233 ifTrue:
			[^client storeIntoLiteralVariable: (method literalAt: (extA bitShift: 8) + byte + 1)].
		^client storeIntoTemporaryVariable: byte].
	bytecode < 238 ifTrue:
		[bytecode = 235 ifTrue:
			[^client popIntoReceiverVariable: (extA bitShift: 8) + byte].
		 bytecode = 236 ifTrue:
			[^client popIntoLiteralVariable: (method literalAt: (extA bitShift: 8) + byte + 1)].
		 ^client popIntoTemporaryVariable: byte].
	bytecode < 242 ifTrue:
		[| selector numArgs |
		 selector := method literalAt: (extA bitShift: 5) + (byte // 8) + 1.
		 numArgs := (extB bitShift: 3) + (byte \\ 8).
		 bytecode = 238 ifTrue:
			[^client send: selector super: false numArgs: numArgs].
		 bytecode = 239 ifTrue:
			[^client send: selector super: true numArgs: numArgs].
		 bytecode = 240 ifTrue:
			[^client sendToAbsentImplicitReceiver: selector numArgs: numArgs].
		 ^client sendToAbsentDynamicSuperclass: selector numArgs: numArgs].
	bytecode < 245 ifTrue:
		[bytecode = 242 ifTrue:
			[^client jump: (extB bitShift: 8) + byte].
		 ^client jump: (extB bitShift: 8) + byte if: bytecode = 243].
	"245		11110101	xxxxxxxx	UNASSIGNED"
	"246-247	1111011 i	xxxxxxxx	UNASSIGNED
	 248-249	1111100 i	xxxxxxxx	UNASSIGNED"
	^self unusedBytecode: client at: startPC!

----- Method: InstructionStream>>interpretNext3ByteNSV4Instruction:for:extA:extB:startPC: (in category '*BytecodeSets-NewsqueakV4-decoding') -----
interpretNext3ByteNSV4Instruction: 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 EncoderForNewsqueakV2's class comment."

	| method byte2 byte3 |
	method := self method.
	byte2 := method at: pc.
	byte3 := method at: pc + 1.
	pc := pc + 2.
	"we search the bytecodes by static frequency"
	bytecode = 253 ifTrue:
		["253		11111101 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"
		 ^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 = 250 ifTrue:
		[^client pushRemoteTemp: byte2 inVectorAt: byte3].
	bytecode = 252 ifTrue:
		[^client popIntoRemoteTemp: byte2 inVectorAt: byte3].
	bytecode = 251 ifTrue:
		[^client storeIntoRemoteTemp: byte2 inVectorAt: byte3].
	bytecode = 249 ifTrue:
			[^client callPrimitive: byte2 + (byte3 bitShift: 8)].
	"254-255	1111111 i	xxxxxxxx	yyyyyyyy	UNASSIGNED"
	^self unusedBytecode: client at: startPC!

----- Method: InstructionStream>>interpretNextNSV3InstructionFor: (in category '*BytecodeSets-NewsqueakV3-decoding') -----
interpretNextNSV3InstructionFor: client 
	"Send to the argument, client, a message that specifies the type of the 
	 next instruction."

	| byte type offset method |
	method := self method.  
	byte := method at: pc.
	type := byte // 16.  
	offset := byte \\ 16.  
	pc := pc+1.
	"We do an inline binary search on each of the possible 16 values of type."
	type < 8 ifTrue:
		[type < 4 ifTrue:
			[type < 2 ifTrue:
				[type = 0 ifTrue:
					[^ client pushReceiverVariable: offset].
				^ client pushTemporaryVariable: offset].				"type = 1"
			type = 2 ifTrue: 
				[^ client pushConstant: (method literalAt: offset + 1)].
			^ client pushConstant: (method literalAt: offset + 17)].		"type = 3"
		type < 6 ifTrue:
			[type = 4 ifTrue:
				[^ client pushLiteralVariable: (method literalAt: offset + 1)].
			^ client pushLiteralVariable: (method literalAt: offset + 17)]."type = 5"
		type = 6 ifTrue:
			[offset < 8 ifTrue:
				[^ client popIntoReceiverVariable: offset].
			^ client popIntoTemporaryVariable: offset - 8].
		"type = 7"
		offset = 0 ifTrue: [^ client pushReceiver].
		offset < 8 ifTrue: [^ client pushConstant: (SpecialConstants at: offset)].
		offset = 8 ifTrue: [^ client methodReturnReceiver].
		offset < 12 ifTrue: [^ client methodReturnConstant: (SpecialConstants at: offset - 8)].
		offset = 12 ifTrue: [^ client methodReturnTop].
		offset = 13 ifTrue: [^ client blockReturnTop].
		offset = 14 ifTrue:
			[| byte2 |
			byte := method at: pc.
			pc := pc+1.
			byte2 := method at: pc.
			pc := pc+1.
			^ client sendToDynamicSuperclass: (method literalAt: byte2 + 1) numArgs: byte].
		 "offset = 15"
		byte := method at: pc.
		pc := pc+1.
		^ client pushImplicitReceiverForMessage: (method literalAt: byte + 1)].
	type < 12 ifTrue:
		[type < 10 ifTrue:
			[type = 8 ifTrue:
				[^ self
					interpretNSV3Extension: offset
					in: method
					for: client].
			"type = 9 (short jumps)"
			offset < 8 ifTrue: [^ client jump: offset + 1].
			^ client jump: offset - 8 + 1 if: false].
		type = 10 ifTrue: "(long jumps)"
			[byte := method at: pc.
			pc := pc + 1.
			offset < 8 ifTrue: [^ client jump: offset - 4 * 256 + byte].
			^ client jump: (offset bitAnd: 3) * 256 + byte if: offset < 12].
		"type = 11; arithmetic special selector sends"
		^ client
			send: (Smalltalk specialSelectorAt: offset + 1)
			super: false
			numArgs: (Smalltalk specialNargsAt: offset + 1)].
		type = 12 ifTrue: "non-arithmetic special selector sends"
			[^ client
				send: (Smalltalk specialSelectorAt: offset + 17)
				super: false
				numArgs: (Smalltalk specialNargsAt: offset + 17)].
	"type = 13, 14 or 15"
	^ client
		send: (method literalAt: offset + 1)
		super: false
		numArgs: type - 13 "0, 1 & 2"!

----- Method: InstructionStream>>interpretNextNSV4InstructionFor: (in category '*BytecodeSets-NewsqueakV4-decoding') -----
interpretNextNSV4InstructionFor: 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 EncoderForNewsqueakV2's class comment."
	"consume and compute any extensions first."
	extA := extB := 0.
	savedPC := pc.
	[byte := self method at: pc.
	 pc := pc + 1.
	 byte >= 224 and: [byte <= 225]] whileTrue:
		[| extByte |
		 extByte := self method at: pc.
		 pc := pc + 1.
		 byte = 224
			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 < 12 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 < 14 ifTrue:
				[offset = 12 ifTrue:
					[^client pushReceiver].
				 extB = 0 ifTrue:
					[^client pushConstant: false].
				 ^self alternateInterpretExtendedPush: extB for: client].
			 ^client pushConstant: offset - 14]. "0 & 1"
		"short sends"
		div16 < 7 ifTrue: "special selector sends"
			[div16 = 5 ifTrue:
				[^client
					send: (Smalltalk specialSelectorAt: offset + 1)
					super: false
					numArgs: (Smalltalk specialNargsAt: offset + 1)].
			 ^client
				send: (Smalltalk specialSelectorAt: offset + 17)
				super: false
				numArgs: (Smalltalk specialNargsAt: offset + 17)].
		div16 < 10 ifTrue: "vanilla sends, div16 = 7, 8 & 9"
			[^client
				send: (method literalAt: offset + 1)
				super: false
				numArgs: div16 - 7].
		"implicit receiver send, div16 = 10"
		 div16 = 10 ifTrue:
			[^client
				sendToAbsentImplicitReceiver: (method literalAt: offset + 1)
				numArgs: 0].
		"short store pops"
		offset < 8 ifTrue:
			[^client popIntoReceiverVariable: offset].
		^client popIntoTemporaryVariable: offset - 8].
	"div16 >= 12"
	div16 < 14 ifTrue:
		[div16 = 12 ifTrue:
			[offset < 8 ifTrue:
				[^client jump: offset + 1].
			 ^client jump: offset - 7 if: true].
		 offset < 8 ifTrue:
			[^client jump: offset + 1 if: false].
		 offset < 11 ifTrue:
		 	[offset = 8 ifTrue: [^client methodReturnReceiver].
			 offset = 9 ifTrue: [^client methodReturnTop].
			 extA > 0 ifTrue:
				[^client blockReturnTopFromLevel: extA].
			 ^client blockReturnTop].
		 offset = 11 ifTrue:
			[^client doDup].
		 offset = 12 ifTrue:
			[^client doPop].
		 offset = 13 ifTrue:
			[^client doNop].
		"222		11011110		break ?  could have blockCopy: send break, but need a receiver and a pop result"
		"223		11011111		UNASSIGNED"
		^self unusedBytecode: client at: savedPC].
	"2 byte and 3 byte codes"
	byte < 249 ifTrue:
		[^self interpretNext2ByteNSV4Instruction: byte for: client extA: extA extB: extB startPC: savedPC].
	^self interpretNext3ByteNSV4Instruction: byte for: client extA: extA extB: extB startPC: savedPC!

BytecodeEncoder subclass: #EncoderForNewsqueakV4
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'BytecodeSets-NewsqueakV4'!

!EncoderForNewsqueakV4 commentStamp: 'eliot 12/3/2012 17:23' prior: 0!
EncoderForNewsqueakV4 encodes a bytecode set for Squeak and Newspeak that lifts limits on number of literals and branch distances, has a single bytecode for send to implicit receiver and extended push integer and push character bytecodes.  Byteodes 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.

1 Byte Bytecodes
	0-15		0000 i i i i 		Push Receiver Variable #iiii
	16-31		0001 i i i i		Push Literal Variable #iiii
	32-63		001 i i i i i		Push Literal #iiiii
	64-71		01000 i i i		Push Temporary Variable #iii
	72-75		010010 i i		Push Temporary Variable #ii + 8
	76			01001100		Push Receiver
*	77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]
	78			01001110		Push 0
	79			01001111		Push 1
	80-95		0101 i i i i		Send Arithmetic Message #iiii
	96-111		0110 i i i i		Send Special Message #iiii
	112-127	0111 i i i i		Send Literal Selector #iiii With 0 Arguments
	128-143	1000 i i i i		Send Literal Selector #iiii With 1 Argument
	144-159	1001 i i i i		Send Literal Selector #iiii With 2 Arguments
	160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments
	176-183	10110 i i i		Pop and Store Receiver Variable #iii
	184-191	10111 i i i		Pop and Store Temporary Variable #iii
	192-199	11000 i i i		Jump iii + 1 (i.e., 1 through 8)
	200-207	11001 i i i		Pop and Jump 0n True iii +1 (i.e., 1 through 8)
	208-215	11010 i i i		Pop and Jump 0n False iii +1 (i.e., 1 through 8)
	216		11011000		Return Receiver From Message
	217		11011001		Return Stack Top From Message
*	218		11011010		Return Stack Top From Block [* return from enclosing block N, N = Extend A]
	219		11011011		Duplicate Stack Top
	220		11011100		Pop Stack Top
*	221		11011101		Nop
	222		11011110		break ?  could have blockCopy: send break, but need pushReceiver & pop result
	223		11011111		UNASSIGNED

2 Byte Bytecodes
*	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)
*	226		11100010	i i i i i i i i	Push Receiver Variable #iiiiiiii (+ Extend A * 256)
*	227		11100011	i i i i i i i i	Push Literal Variable #iiiiiiii (+ Extend A * 256)
*	228		11100100	i i i i i i i i	Push Literal #iiiiiiii (+ Extend A * 256)
*	229		11100101	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)
	230		11100110	i i i i i i i i	Push Temporary Variable #iiiiiiii
	231		11100111	jkkkkkkk	Push (Array new: kkkkkkk) (j = 0)
									&	Pop kkkkkkk elements into: (Array new: kkkkkkk) (j = 1)
*	232		11101000	i i i i i i i i	Store Receiver Variable #iiiiiii (+ Extend A * 256)
*	233		11101001	i i i i i i i i	Store Literal Variable #iiiiiiii (+ Extend A * 256)
	234		11101010	i i i i i i i i	Store Temporary Variable #iiiiiiii
*	235		11101011	i i i i i i i i	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
*	236		11101100	i i i i i i i i	Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
	237		11101101	i i i i i i i i	Pop and Store Temporary Variable #iiiiiiii
**	238		11101110	i i i i i j j j	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
**	239		11101111	i i i i i j j j	Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
**	240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
**	241		11110001	i i i i i j j j	Send To Absent Dynamic Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments
*	242		11110010	i i i i i i i i	Jump i i i i i i i i (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)
*	243		11110011	i i i i i i i i	Pop and Jump 0n True i i i i i i i i (+ Extend B * 256, where Extend B >= 0)
*	244		11110100	i i i i i i i i	Pop and Jump 0n False i i i i i i i i (+ Extend B * 256, where Extend B >= 0)

	245		11110101	xxxxxxxx	UNASSIGNED
	246-247	1111011 i	xxxxxxxx	UNASSIGNED
	248		11111000	xxxxxxxx	UNASSIGNED

3 Byte Bytecodes
	249		11111001	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)
	250		11111010 kkkkkkkk	jjjjjjjj		Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj
	251		11111011 kkkkkkkk	jjjjjjjj		Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj
	252		11111100 kkkkkkkk	jjjjjjjj		Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj
**	253		11111101 eei i i kkk	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

	254-255	1111111 i	xxxxxxxx	yyyyyyyy	UNASSIGNED!

----- Method: EncoderForNewsqueakV4 class>>blockReturnCode (in category 'bytecode decoding') -----
blockReturnCode
	"218		11011010		Return Stack Top From Block [* return from enclosing block N, N = Extend A]"
	^218!

----- Method: EncoderForNewsqueakV4 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.
	 249		11111001	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
	^249!

----- Method: EncoderForNewsqueakV4 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 interpretNextNSV4InstructionFor: aClient!

----- Method: EncoderForNewsqueakV4 class>>method:readsField: (in category 'scanning') -----
method: method readsField: varIndex
	"Answer if method loads the instance variable indexed by varIndex.
	 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)"
	| varIndexCode scanner extension |
	varIndexCode := varIndex - 1.
	method isReturnField ifTrue:
		[^method returnField = varIndexCode].
	extension := 0.
	^(scanner := InstructionStream on: method) scanFor:
		[: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]]]!

----- Method: EncoderForNewsqueakV4 class>>method:writesField: (in category 'scanning') -----
method: method writesField: varIndex
	"Answer if method stores into the instance variable indexed by varIndex.
	 N.B. Don't assume the compiler uses the most compact encoding available.
		176-183	10110 i i i				Pop and Store Receiver Variable #iii
	*	224		11100000	aaaaaaaa	Extend A (Ext A = Ext A prev * 256 + Ext A)
	*	232		11101000	i i i i i i i i	Store Receiver Variable #iiiiiii (+ Extend A * 256)
	*	235		11101011	i i i i i i i i	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
	| varIndexCode scanner extension |
	method isQuick ifTrue: [^false].
	varIndexCode := varIndex - 1.
	extension := 0.
	^(scanner := InstructionStream on: method) scanFor:
		[:b| | prevext |
		prevext := extension.
		extension := b = 224 ifTrue: [scanner followingByte bitShift: 8] ifFalse: [0].
		b >= 176
		and: [b - 176 = varIndexCode
			  or: [(b = 232 or: [b = 235])
				  and: [scanner followingByte + prevext = varIndexCode]]]]!

----- Method: EncoderForNewsqueakV4 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.
	 253		11111101 eei i i kkk	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"
	| numExtensions |
	self assert: (method at: startpc - 3) = 253.
	numExtensions := (method at: startpc - 2) >> 6.
	^startpc - 3 - (numExtensions * 2)!

----- Method: EncoderForNewsqueakV4 class>>popCode (in category 'bytecode decoding') -----
popCode
	"220		11011100		Pop Stack Top"
	^220!

----- Method: EncoderForNewsqueakV4 class>>pushClosureBytecodeSize (in category 'bytecode decoding') -----
pushClosureBytecodeSize
	"Answer the size of the push closure bytecode.
	 253		11111101 eei i i kkk	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"
	^3!

----- Method: EncoderForNewsqueakV4 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!

----- Method: EncoderForNewsqueakV4>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category 'method encoding') -----
computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
	numTemps > 63 ifTrue:
		[^self error: 'Cannot compile -- too many temporary variables'].	
	numLits > 65535 ifTrue:
		[^self error: 'Cannot compile -- too many literals'].
	^SmallInteger minVal "sign bit is the flag for the alternative bytecode set"
	+ (numArgs bitShift: 24)
	+ (numTemps bitShift: 18)
	"+ (largeBit bitShift: 17)" "largeBit gets filled in later"
	+ ((Smalltalk vmParameterAt: 65) == true
		ifTrue: [numLits + (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])]
		ifFalse: [numLits > 255 ifTrue: [self error: 'vm does not support large methods'].
				primitiveIndex > 511 ifTrue: [self error: 'hack does not support primitive > 511'].
				(numLits bitShift: 9)
				+ (primitiveIndex bitAnd: 511)])!

----- Method: EncoderForNewsqueakV4>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive:accessModifier: (in category 'method encoding') -----
computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex accessModifier: accessModifier
	numArgs > 15 ifTrue:
		[^self error: 'Cannot compile -- too many arguments'].
	numTemps > 63 ifTrue:
		[^self error: 'Cannot compile -- too many temporary variables'].
	numLits > 65535 ifTrue:
		[^self error: 'Cannot compile -- too many literals'].
	^SmallInteger minVal "sign bit is the flag for the alternative bytecode set"
	+ (accessModifier = #protected ifTrue: [ 1 bitShift: 29 ] ifFalse: [ 0 ])
	+ (accessModifier = #private ifTrue: [ 1 bitShift: 28 ] ifFalse: [ 0 ])
	+ (numArgs bitShift: 24)
	+ (numTemps bitShift: 18)
	"+ (largeBit bitShift: 17)" "largeBit gets filled in later"
	+ ((Smalltalk vmParameterAt: 65) == true
		ifTrue: [numLits + (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])]
		ifFalse: [numLits > 255 ifTrue: [self error: 'vm does not support large methods'].
				primitiveIndex > 511 ifTrue: [self error: 'hack does not support primitive > 511'].
				(numLits bitShift: 9)
				+ (primitiveIndex bitAnd: 511)])!

----- Method: EncoderForNewsqueakV4>>encodeLiteral: (in category 'encoding') -----
encodeLiteral: object
	| literal |
	literal := class literalScannedAs: object notifying: self.
	^(self isSpecialLiteral: literal)
		ifTrue:
			[SpecialLiteralNode new
				name: object
				key: literal
				index: nil
				type: LdLitType]
		ifFalse:
			[self
				name: object
				key: literal
				class: LiteralNode
				type: LdLitType
				set: litSet]!

----- Method: EncoderForNewsqueakV4>>genBranchPopFalse: (in category 'bytecode generation') -----
genBranchPopFalse: distance
	| distanceMod256 |
	(distance < 0 or: [distance > 32767]) ifTrue:
		[^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
	(distance > 0 and: [distance < 9]) ifTrue:
		["208-215	11010 i i i		Pop and Jump 0n False iii +1 (i.e., 1 through 8)"
		 stream nextPut: 207 + distance.
		 ^self].
	"244		11110100	i i i i i i i i	Pop and Jump 0n False i i i i i i i i (+ Extend B * 256)"
	distanceMod256 := (distance < 0 or: [distance > 255])
								ifTrue:
									[self genUnsignedSingleExtendB: (distance bitShift: -8).
									 distance bitAnd: 255]
								ifFalse: [distance].
	stream
		nextPut: 244;
		nextPut: distanceMod256!

----- Method: EncoderForNewsqueakV4>>genBranchPopTrue: (in category 'bytecode generation') -----
genBranchPopTrue: distance
	| distanceMod256 |
	(distance < 0 or: [distance > 32767]) ifTrue:
		[^self outOfRangeError: 'distance' index: distance range: 0 to: 32767].
	(distance > 0 and: [distance < 9]) ifTrue:
		["200-207	11001 i i i		Pop and Jump 0n True iii +1 (i.e., 1 through 8)"
		 stream nextPut: 199 + distance.
		 ^self].
	"243		11110011	i i i i i i i i	Pop and Jump 0n True i i i i i i i i (+ Extend B * 256)"
	distanceMod256 := (distance < 0 or: [distance > 255])
								ifTrue:
									[self genUnsignedSingleExtendB: (distance bitShift: -8).
									 distance bitAnd: 255]
								ifFalse: [distance].
	stream
		nextPut: 243;
		nextPut: distanceMod256!

----- Method: EncoderForNewsqueakV4>>genCallPrimitive: (in category 'bytecode generation') -----
genCallPrimitive: primitiveIndex
	"249		11111001	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
	"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: 249;
		nextPut: (primitiveIndex bitAnd: 255);
		nextPut: (primitiveIndex bitShift: -8)!

----- Method: EncoderForNewsqueakV4>>genDup (in category 'bytecode generation') -----
genDup
	"219		11011011		Duplicate Stack Top"
	stream nextPut: 219!

----- Method: EncoderForNewsqueakV4>>genJump: (in category 'bytecode generation') -----
genJump: distance
	(distance > 0 and: [distance < 9]) ifTrue:
		["192-199	11000 i i i		Jump iii + 1 (i.e., 1 through 8)"
		 stream nextPut: 191 + distance.
		 ^self].
	"243		11110011	i i i i i i i i	Jump i i i i i i i i (+ Extend B * 256, where bbbbbbbb = sddddddd, e.g. -32768 = i=0, a=0, s=1)"
	^self genJumpLong: distance!

----- Method: EncoderForNewsqueakV4>>genJumpLong: (in category 'bytecode generation') -----
genJumpLong: distance
	"242		11110010	i i i i i i i i	Jump i i i i i i i i (+ 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: 242;
		nextPut: (distance bitAnd: 255)!

----- Method: EncoderForNewsqueakV4>>genNop (in category 'bytecode generation') -----
genNop
	"221		11011101		Nop"
	stream nextPut: 221!

----- Method: EncoderForNewsqueakV4>>genPop (in category 'bytecode generation') -----
genPop
	"220		11011100		Pop Stack Top"
	stream nextPut: 220!

----- Method: EncoderForNewsqueakV4>>genPushClosureCopyNumCopiedValues:numArgs:jumpSize: (in category 'bytecode generation') -----
genPushClosureCopyNumCopiedValues: numCopied numArgs: numArgs jumpSize: jumpSize
	"253		11111101 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: 253;
		nextPut: (numExtensions bitShift: 6) + (numCopiedMod8 bitShift: 3) + numArgsMod8;
		nextPut: (jumpSize bitAnd: 16rFF)!

----- Method: EncoderForNewsqueakV4>>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!

----- Method: EncoderForNewsqueakV4>>genPushExplicitOuter: (in category 'bytecode generation') -----
genPushExplicitOuter: level
	"77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
	(level > 0 and: [level <= 127]) ifTrue:
		[^self outOfRangeError: 'level' index: level range: 1 to: 127].
	self genSignedSingleExtendB: level negated.
	stream nextPut: 77!

----- Method: EncoderForNewsqueakV4>>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!

----- Method: EncoderForNewsqueakV4>>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 > 4095]) ifTrue:
		[^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 4095].
	instVarIndex > 255 ifTrue:
		[self genUnsignedSingleExtendA: instVarIndex // 256].
	stream
		nextPut: 226;
		nextPut: instVarIndex \\ 256!

----- Method: EncoderForNewsqueakV4>>genPushInteger: (in category 'bytecode generation') -----
genPushInteger: anInteger
	"78			01001110				Push 0
	 79			01001111				Push 1
	 229		11100101	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: 78.
		 ^self].
	anInteger = 1 ifTrue:
		[stream nextPut: 79.
		 ^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: 229;
		nextPut: (anInteger bitAnd: 255)!

----- Method: EncoderForNewsqueakV4>>genPushLiteral: (in category 'bytecode generation') -----
genPushLiteral: literalIndex
	| extendedIndex |
	(literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65536].
	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!

----- Method: EncoderForNewsqueakV4>>genPushLiteralVar: (in category 'bytecode generation') -----
genPushLiteralVar: literalIndex
	| extendedIndex |
	(literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
	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!

----- Method: EncoderForNewsqueakV4>>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!

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

----- Method: EncoderForNewsqueakV4>>genPushRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
genPushRemoteTemp: tempIndex inVectorAt: tempVectorIndex
	"250		11111010 kkkkkkkk	jjjjjjjj		Push Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
	(tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
		[^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
	(tempVectorIndex < 0 or: [tempVectorIndex >= 256]) ifTrue:
		[^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255].
	stream
		nextPut: 250;
		nextPut: tempIndex;
		nextPut: tempVectorIndex!

----- Method: EncoderForNewsqueakV4>>genPushSpecialLiteral: (in category 'bytecode generation') -----
genPushSpecialLiteral: aLiteral
	"77			01001101				Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]
	 229		11100101	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)"
	| index |
	aLiteral isInteger ifTrue:
		[^self genPushInteger: aLiteral].
	index := #(false true nil)
					indexOf: aLiteral
					ifAbsent: [^self error: 'push special literal: ', aLiteral printString,  ' is not one of true false nil'].
	index > 1 ifTrue:
		[self genUnsignedSingleExtendB: index - 1].
	stream nextPut: 77!

----- Method: EncoderForNewsqueakV4>>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].
	"230		11100110	i i i i i i i i	Push Temporary Variable #iiiiiiii"
	stream
		nextPut: 230;
		nextPut: tempIndex!

----- Method: EncoderForNewsqueakV4>>genPushThisContext (in category 'bytecode generation') -----
genPushThisContext
	"77			01001101		Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
	self genSignedSingleExtendB: 3.
	stream nextPut: 77!

----- Method: EncoderForNewsqueakV4>>genReturnReceiver (in category 'bytecode generation') -----
genReturnReceiver
	"216		11011000		Return Receiver From Message"
	stream nextPut: 216!

----- Method: EncoderForNewsqueakV4>>genReturnSpecialLiteral: (in category 'bytecode generation') -----
genReturnSpecialLiteral: aLiteral
	self shouldNotImplement!

----- Method: EncoderForNewsqueakV4>>genReturnTop (in category 'bytecode generation') -----
genReturnTop
	"217		11011001		Return Stack Top From Message"
	stream nextPut: 217!

----- Method: EncoderForNewsqueakV4>>genReturnTopToCaller (in category 'bytecode generation') -----
genReturnTopToCaller
	"218		11011010		Return Stack Top From Block [* return from enclosing block N]"
	stream nextPut: 218!

----- Method: EncoderForNewsqueakV4>>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: 
	 	["112-127	0111 i i i i		Send Literal Selector #iiii With 0 Arguments
		   128-143	1000 i i i i		Send Literal Selector #iiii With 1 Argument
		   144-159	1001 i i i i		Send Literal Selector #iiii With 2 Arguments"
		 stream nextPut: 112 + (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].
	"238		11101110	i i i i i j j j	Send Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
	stream
		nextPut: 238;
		nextPut: extendedNArgs + (extendedIndex * 8)!

----- Method: EncoderForNewsqueakV4>>genSendAbsentDynamicSuper:numArgs: (in category 'bytecode generation') -----
genSendAbsentDynamicSuper: 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].
	"241		11110001	i i i i i j j j	Send To Absent Dynamic Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
	stream
		nextPut: 241;
		nextPut: extendedNArgs + (extendedIndex * 8)!

----- Method: EncoderForNewsqueakV4>>genSendAbsentImplicit:numArgs: (in category 'bytecode generation') -----
genSendAbsentImplicit: 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 = 0]) ifTrue: 
	 	["160-175	1010 i i i i		Send To Absent Implicit Receiver Literal Selector #iiii With 0 Arguments"
		 stream nextPut: 160 + selectorLiteralIndex.
		 ^self].
	(extendedIndex := selectorLiteralIndex) > 31 ifTrue:
		[self genUnsignedSingleExtendA: extendedIndex // 32.
		 extendedIndex := extendedIndex \\ 32].
	(extendedNArgs := nArgs) > 7 ifTrue:
		[self genUnsignedSingleExtendB: extendedNArgs // 8.
		 extendedNArgs := extendedNArgs \\ 8].
	"240		11110000	i i i i i j j j	Send To Absent Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
	stream
		nextPut: 240;
		nextPut: extendedNArgs + (extendedIndex * 8)!

----- Method: EncoderForNewsqueakV4>>genSendImplicit:numArgs: (in category 'bytecode generation') -----
genSendImplicit: 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 = 0]) ifTrue: 
	 	["160-175	1010 i i i i		Send To Implicit Receiver Literal Selector #iiii With 0 Arguments"
		 stream nextPut: 160 + selectorLiteralIndex.
		 ^self].
	(extendedIndex := selectorLiteralIndex) > 31 ifTrue:
		[self genUnsignedSingleExtendA: extendedIndex // 32.
		 extendedIndex := extendedIndex \\ 32].
	(extendedNArgs := nArgs) > 7 ifTrue:
		[self genUnsignedSingleExtendB: extendedNArgs // 8.
		 extendedNArgs := extendedNArgs \\ 8].
	"240		11110000	i i i i i j j j	Send To Implicit Receiver Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
	stream
		nextPut: 240;
		nextPut: extendedNArgs + (extendedIndex * 8)!

----- Method: EncoderForNewsqueakV4>>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.
		80-95		0101 i i i i		Send Arithmetic Message #iiii
		96-111		0110 i i i i		Send Special Message #iiii"
	stream nextPut: specialSelectorIndex + 79!

----- Method: EncoderForNewsqueakV4>>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].
	"239		11101111	i i i i i j j j	Send To Superclass Literal Selector #iiiii (+ Extend A * 32) with jjj (+ Extend B * 8) Arguments"
	stream
		nextPut: 239;
		nextPut: extendedNArgs + (extendedIndex * 8)!

----- Method: EncoderForNewsqueakV4>>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]) !

----- Method: EncoderForNewsqueakV4>>genStoreInstVar: (in category 'bytecode generation') -----
genStoreInstVar: instVarIndex
	"232		11101000	i i i i i i i i	Store Receiver Variable #iiiiiii (+ Extend A * 256)"
	self genStoreInstVarLong: instVarIndex!

----- Method: EncoderForNewsqueakV4>>genStoreInstVarLong: (in category 'bytecode generation') -----
genStoreInstVarLong: instVarIndex
	"232		11101000	i i i i i i i i	Store Receiver Variable #iiiiiii (+ Extend A * 256)"
	(instVarIndex < 0 or: [instVarIndex > 4095]) ifTrue:
		[^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 4095].
	instVarIndex > 255 ifTrue:
		[self genUnsignedSingleExtendA: instVarIndex // 256].
	stream
		nextPut: 232;
		nextPut: instVarIndex \\ 256!

----- Method: EncoderForNewsqueakV4>>genStoreLiteralVar: (in category 'bytecode generation') -----
genStoreLiteralVar: literalIndex
	"233		11101001	i i i i i i i i	Store Literal Variable #iiiiiiii (+ Extend A * 256)"
	(literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
	literalIndex > 255 ifTrue: 
		[self genUnsignedSingleExtendA: literalIndex // 256].
	stream
		nextPut: 233;
		nextPut: literalIndex \\ 256!

----- Method: EncoderForNewsqueakV4>>genStorePopInstVar: (in category 'bytecode generation') -----
genStorePopInstVar: instVarIndex
	"176-183	10110 i i i				Pop and Store Receiver Variable #iii
	 235		11101011	i i i i i i i i	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
	(instVarIndex < 0 or: [instVarIndex > 7]) ifTrue:
		[^self genStorePopInstVarLong: instVarIndex].
	stream nextPut: 176 + instVarIndex!

----- Method: EncoderForNewsqueakV4>>genStorePopInstVarLong: (in category 'bytecode generation') -----
genStorePopInstVarLong: instVarIndex
	"235		11101011	i i i i i i i i	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)"
	(instVarIndex < 0 or: [instVarIndex > 4095]) ifTrue:
		[^self outOfRangeError: 'index' index: instVarIndex range: 0 to: 4095].
	instVarIndex > 255 ifTrue:
		[self genUnsignedSingleExtendA: instVarIndex // 256].
	stream
		nextPut: 235;
		nextPut: instVarIndex \\ 256!

----- Method: EncoderForNewsqueakV4>>genStorePopLiteralVar: (in category 'bytecode generation') -----
genStorePopLiteralVar: literalIndex
	"236		11101100	i i i i i i i i	Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)"
	(literalIndex < 0 or: [literalIndex > 65535]) ifTrue:
		[^self outOfRangeError: 'index' index: literalIndex range: 0 to: 65535].
	literalIndex > 255 ifTrue: 
		[self genUnsignedSingleExtendA: literalIndex // 256].
	stream
		nextPut: 236;
		nextPut: literalIndex \\ 256!

----- Method: EncoderForNewsqueakV4>>genStorePopRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
genStorePopRemoteTemp: tempIndex inVectorAt: tempVectorIndex
	"252		11111100 kkkkkkkk	jjjjjjjj		Pop and Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
	(tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
		[^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
	(tempVectorIndex < 0 or: [tempVectorIndex >= 256]) ifTrue:
		[^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255].
	stream
		nextPut: 252;
		nextPut: tempIndex;
		nextPut: tempVectorIndex!

----- Method: EncoderForNewsqueakV4>>genStorePopTemp: (in category 'bytecode generation') -----
genStorePopTemp: tempIndex
	"184-191	10111 i i i				Pop and Store Temporary Variable #iii
	 237		11101101	i i i i i i i i	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: 184 + tempIndex.
		 ^self].
	stream
		nextPut: 237;
		nextPut: tempIndex!

----- Method: EncoderForNewsqueakV4>>genStoreRemoteTemp:inVectorAt: (in category 'bytecode generation') -----
genStoreRemoteTemp: tempIndex inVectorAt: tempVectorIndex
	"251		11111011 kkkkkkkk	jjjjjjjj		Store Temp At kkkkkkkk In Temp Vector At: jjjjjjjj"
	(tempIndex < 0 or: [tempIndex >= 256]) ifTrue:
		[^self outOfRangeError: 'remoteTempIndex' index: tempIndex range: 0 to: 255].
	(tempVectorIndex < 0 or: [tempVectorIndex >= 256]) ifTrue:
		[^self outOfRangeError: 'tempVectorIndex' index: tempVectorIndex range: 0 to: 255].
	stream
		nextPut: 251;
		nextPut: tempIndex;
		nextPut: tempVectorIndex!

----- Method: EncoderForNewsqueakV4>>genStoreTemp: (in category 'bytecode generation') -----
genStoreTemp: tempIndex
	"234		11101010	i i i i i i i i	Store Temporary Variable #iiiiiiii"
	(tempIndex < 0 or: [tempIndex > 63]) ifTrue:
		[^self outOfRangeError: 'index' index: tempIndex range: 0 to: 63].
	stream
		nextPut: 234;
		nextPut: tempIndex!

----- Method: EncoderForNewsqueakV4>>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!

----- Method: EncoderForNewsqueakV4>>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)"
	stream
		nextPut: 224;
		nextPut: extendedIndex!

----- Method: EncoderForNewsqueakV4>>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)"
	stream
		nextPut: 225;
		nextPut: extendedIndex!

----- Method: EncoderForNewsqueakV4>>generateMethodOfClass:trailer:from: (in category 'method encoding') -----
generateMethodOfClass: aCompiledMethodClass trailer: trailer from: methodNode
	"The receiver is the root of a parse tree. Answer an instance of aCompiledMethodClass.
	 The argument, trailer, is arbitrary but is typically either the reference to the source code
	 that is stored with every CompiledMethod, or an encoding of the method's temporary names."

	| primErrNode blkSize nLits locals literals header method stack |
	primErrNode := methodNode primitiveErrorVariableName ifNotNil:
						[self fixTemp: methodNode primitiveErrorVariableName].
	methodNode ensureClosureAnalysisDone.
	self rootNode: methodNode. "this is for BlockNode>>sizeCodeForClosureValue:"
	blkSize := (methodNode block sizeCodeForEvaluatedValue: self)
				+ (methodNode primitive > 0
					ifTrue: [self sizeCallPrimitive: methodNode primitive]
					ifFalse: [0])
				+ (primErrNode
					ifNil: [0]
					ifNotNil:
						[primErrNode
							index: methodNode arguments size + methodNode temporaries size;
							sizeCodeForStore: self "The VM relies on storeIntoTemp: (129)"]).
	locals := methodNode arguments, methodNode temporaries, (primErrNode ifNil: [#()] ifNotNil: [{primErrNode}]).
	self noteBlockExtent: methodNode block blockExtent hasLocals: locals.
	header := self computeMethodHeaderForNumArgs: methodNode arguments size
					numTemps: locals size
					numLits: (nLits := (literals := self allLiterals) size)
					primitive: methodNode primitive.
	method := trailer
					createMethod: blkSize
					class: aCompiledMethodClass
					header: header.
	1 to: nLits do: [:lit | method literalAt: lit put: (literals at: lit)].
	self streamToMethod: method.
	stack := ParseStack new init.
	methodNode primitive > 0 ifTrue:
		[self genCallPrimitive: methodNode primitive].
	primErrNode ifNotNil:
		[primErrNode emitCodeForStore: stack encoder: self].
	stack position: method numTemps.
	[methodNode block emitCodeForEvaluatedValue: stack encoder: self]
		on: Error "If an attempt is made to write too much code the method will be asked"
		do: [:ex|  "to grow, and the grow attempt will fail in CompiledMethod class>>#new:"
			ex signalerContext sender method = (CompiledMethod class>>#new:)
				ifTrue: [^self error: 'Compiler code size discrepancy']
				ifFalse: [ex pass]].
	stack position ~= (method numTemps + 1) ifTrue:
		[^self error: 'Compiler stack discrepancy'].
	self methodStreamPosition ~= (method size - trailer size) ifTrue:
		[^self error: 'Compiler code size discrepancy'].
	method needsFrameSize: stack size - method numTemps.
	^method!

----- Method: EncoderForNewsqueakV4>>if:isSpecialLiteralForReturn: (in category 'special literal encodings') -----
if: code isSpecialLiteralForReturn: aBlock
	"No special literal encodings for return."
	^false!

----- Method: EncoderForNewsqueakV4>>isSpecialLiteral: (in category 'special literal encodings') -----
isSpecialLiteral: literal
	^literal isInteger and: [literal between: -32768 and: 32767]!

----- Method: EncoderForNewsqueakV4>>litIndex: (in category 'encoding') -----
litIndex: literal
	| p |
	p := literalStream position.
	p = 65536 ifTrue:
		[self notify: 'More than 65536 literals referenced. 
You must split or otherwise simplify this method.
The 65537th literal is: ', literal printString. ^nil].
		"Would like to show where it is in the source code, 
		 but that info is hard to get."
	literalStream nextPut: literal.
	^ p!

----- Method: EncoderForNewsqueakV4>>supportsClosureOpcodes (in category 'testing') -----
supportsClosureOpcodes
	^true!

----- Method: EncoderForNewsqueakV4>>usesAlternateBytecodeSet (in category 'testing') -----
usesAlternateBytecodeSet
	"Answer if the receiver encodes the alternate bytecode set (indicated by the sign flag set in a CompiledMethod's header)."
	^true!



More information about the Vm-dev mailing list