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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 7 16:53:45 UTC 2014


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

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

Name: BytecodeSets-eem.9
Author: eem
Time: 7 August 2014, 9:53:36.312 am
UUID: 5fd2cbc4-c3d2-4147-8f43-bdf9530bb8d8
Ancestors: BytecodeSets-eem.8

Adapt to Compiler-eem.286 (some code moved to
Compiler, e.g. SpecialLiteralNode).

Fix bug in 1-byte SistaV1 decoder.
Implement 3-byte SistaV1 decoder. 
Fix comments.

=============== Diff against BytecodeSets-eem.8 ===============

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

Item was added:
+ ----- Method: EncoderForNewsqueakV4 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.
+ 	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
+ 	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)
+ 	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"
+ 
+ 	| byte |
+ 	byte := method at: pc.
+ 	byte < 80 ifTrue:
+ 		[^anInstructionStream].
+ 	byte <= 175 ifTrue: 
+ 		["special byte or short send"
+ 		 ^byte >= 112
+ 			ifTrue: [method literalAt: (byte bitAnd: 15) + 1]
+ 			ifFalse: [Smalltalk specialSelectorAt: byte - 79]].
+ 	byte < 238 ifTrue:
+ 		[(byte >= 224 and: [byte <= 225]) ifTrue:
+ 			[^self extensionsAt: pc in: method into:
+ 				[:extA :extB :delta| | byteAfter index |
+ 				byteAfter := method at: pc + delta.
+ 				(byteAfter >= 238 and: [byteAfter <= 241])
+ 					ifTrue:
+ 						[index := ((method at: pc + delta + 1) bitShift: -3) + (extA bitShift: 5).
+ 						 method literalAt: index + 1]
+ 					ifFalse: [anInstructionStream]]].
+ 		^anInstructionStream].
+ 	byte > 241 ifTrue:
+ 		[^anInstructionStream].
+ 	"they could be extended..."
+ 	^self extensionsAt: pc in: method into:
+ 		[:extA :extB| | index |
+ 		 index := ((method at: pc + 1) bitShift: -3) + (extA bitShift: 5).
+ 		 method literalAt: index + 1]!

Item was changed:
  ----- 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"
+ 	+ numLits
+ 	+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])!
- 	+ ((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)])!

Item was added:
+ ----- Method: EncoderForNewsqueakV4>>isSpecialLiteralForPush: (in category 'special literal encodings') -----
+ isSpecialLiteralForPush: literal
+ 	^literal == false
+ 	  or: [literal == #nil
+ 	  or: [literal isInteger and: [literal between: -32768 and: 32767]]]!

Item was changed:
  ----- Method: EncoderForSistaV1>>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"
+ 	+ numLits
+ 	+ (primitiveIndex > 0 ifTrue: [1 bitShift: 16] ifFalse: [0])!
- 	+ ((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)])!

Item was removed:
- ----- Method: EncoderForV3 class>>unusedBytecode (in category '*BytecodeSets-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."
- 	^126!

Item was removed:
- ----- Method: EncoderForV3>>computeMethodHeaderForNumArgs:numTemps:numLits:primitive: (in category '*BytecodeSets-method encoding') -----
- computeMethodHeaderForNumArgs: numArgs numTemps: numTemps numLits: numLits primitive: primitiveIndex
- 	| primBits |
- 	numTemps > 63 ifTrue:
- 		[^self error: 'Cannot compile -- too many temporary variables'].	
- 	numLits > 255 ifTrue:
- 		[^self error: 'Cannot compile -- too many literals'].
- 	primBits := primitiveIndex <= 16r1FF
- 					ifTrue: [primitiveIndex]
- 					ifFalse: "For now the high bit of primitive no. is in the 29th bit of header"
- 						[primitiveIndex > 16r3FF ifTrue: [self error: 'prim num too large'].
- 						 (primitiveIndex bitAnd: 16r1FF) + ((primitiveIndex bitAnd: 16r200) bitShift: 19)].
- 	^(numArgs bitShift: 24)
- 	+ (numTemps bitShift: 18)
- 	"+ (largeBit bitShift: 17)" "largeBit gets filled in later"
- 	+ (numLits bitShift: 9)
- 	+ primBits!

Item was removed:
- ----- Method: EncoderForV3>>generateMethodOfClass:trailer:from: (in category '*BytecodeSets-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 literals header method stack |
- 	primErrNode := methodNode primitiveErrorVariableName ifNotNil:
- 						[self fixTemp: methodNode primitiveErrorVariableName].
- 	blkSize := (methodNode block sizeCodeForEvaluatedValue: self)
- 				+ (primErrNode
- 					ifNil: [0]
- 					ifNotNil: [primErrNode sizeCodeForStore: self "The VM relies on storeIntoTemp: (129)"]).
- 	header := self computeMethodHeaderForNumArgs: methodNode arguments size
- 					numTemps: self maxTemp
- 					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.
- 	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!

Item was removed:
- ----- Method: EncoderForV3PlusClosures>>generateMethodOfClass:trailer:from: (in category '*BytecodeSets-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)
- 				+ (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.
- 	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!

Item was added:
+ ----- Method: InstructionClient>>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."!

Item was added:
+ ----- 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 changed:
  ----- 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 EncoderForNewsqueakV4's class comment."
- 	 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!

Item was added:
+ ----- 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 pushClosureTemps: byte].
+ 			^client pushTemporaryVariable: 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, trap and jump"
+ 		[bytecode < 236 ifTrue: "sends"
+ 			[^client
+ 				send: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
+ 				super: bytecode = 239
+ 				numArgs: (extB bitShift: 3) + (byte \\ 8)].
+ 		 bytecode = 236 ifTrue:
+ 			[^client trapIfNotInstanceOf: (method literalAt: (extA bitShift: 8) + byte + 1)].
+ 		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 changed:
  ----- 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 EncoderForNewsqueakV4's class comment."
- 	 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!

Item was added:
+ ----- 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 |
+ 	method := self method.
+ 	byte2 := method at: pc.
+ 	byte3 := method at: pc + 1.
+ 	pc := pc + 2.
+ 	"we search the bytecodes by what we expect to be the static frequency."
+ 	bytecode = 248 ifTrue:
+ 		[^client callPrimitive: byte2 + (byte3 bitShift: 8)].
+ 	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 popIntoRemoteTemp: byte2 inVectorAt: byte3].
+ 	bytecode = 253 ifTrue:
+ 		[^client storeIntoRemoteTemp: byte2 inVectorAt: byte3].
+ 	"249		11111001 	xxxxxxxx	syyyyyyy	Reserved for Push Float"
+ 	"254-255	1111111 i	xxxxxxxx	yyyyyyyy	UNASSIGNED"
+ 	^self unusedBytecode: client at: startPC!

Item was changed:
  ----- 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 EncoderForNewsqueakV4's class comment."
- 	"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 interpretNSV4ExtendedPush: 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!

Item was changed:
  ----- 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].
- 		[div16 < 5 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 < 6
- 			ifTrue:
- 				[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]].
- 				 offset < 2 ifTrue:
- 					[^client pushConstant: offset].
- 				 offset = 3 ifTrue:
- 					[^self interpretSistaV1ExtendedPush: extB for: client].
- 				 offset = 4 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 pushReceiver].
- 					[^client methodReturnTop].
  				 offset = 13 ifTrue:
+ 					[^client pushConstant: true].
- 					[^client blockReturnConstant: nil].
  				 offset = 14 ifTrue:
+ 					[^client pushConstant: false].
- 					[^client blockReturnTop].
  				 offset = 15 ifTrue:
+ 					[^client pushConstant: nil]].
+ 			"div16 = 5"
+ 			 offset < 2 ifTrue:
+ 				[^client pushConstant: offset].
+ 			 offset = 3 ifTrue:
+ 				[^self interpretSistaV1ExtendedPush: extB for: client].
+ 			 offset = 4 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].
- 					[^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
- 		div16 < 8 ifTrue: "special selector sends"
- 			[div16 = 6 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)].
  		^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 = 9 ifTrue:
  			[^client doDup].
  		 ^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:
- LiteralNode subclass: #SpecialLiteralNode
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'BytecodeSets-ParseNodes'!

Item was removed:
- ----- Method: SpecialLiteralNode>>emitCodeForValue:encoder: (in category 'code generation (closures)') -----
- emitCodeForValue: stack encoder: encoder
- 	stack push: 1.
- 	encoder genPushSpecialLiteral: key!

Item was removed:
- ----- Method: SpecialLiteralNode>>sizeCodeForValue: (in category 'code generation (closures)') -----
- sizeCodeForValue: encoder
- 	^encoder sizePushSpecialLiteral: key!



More information about the Vm-dev mailing list