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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 13 05:20:33 UTC 2021


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

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

Name: BytecodeSets.spur-eem.81
Author: eem
Time: 12 September 2021, 10:20:31.001161 pm
UUID: d4391f21-0790-4132-9ae4-97941c8e3809
Ancestors: BytecodeSets.spur-eem.80

Proposed fix for CompiledCode>>#allLiteralsDo: by adding pushSpecialConstant:/sendSpecial:numArgs:.

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

Item was changed:
  ----- Method: InstructionStream>>interpretNSV4ExtendedPush:for: (in category '*BytecodeSets-NewsqueakV4-decoding') -----
  interpretNSV4ExtendedPush: extB for: client
  	"Implement the extended push for non-zero extensions."
  	"77			01001101				Push false [* 1:true, 2:nil, 3:thisContext, ..., -N: pushExplicitOuter: N, N = Extend B]"
  	extB < 0 ifTrue:
  		[^client pushExplicitOuter: extB negated].
  	extB < 2 ifTrue:
+ 		[^client pushSpecialConstant: extB = 1].
- 		[^client pushConstant: extB = 1].
  	extB = 2 ifTrue:
+ 		[^client pushSpecialConstant: nil].
- 		[^client pushConstant: nil].
  	extB = 3 ifTrue:
  		[^client pushActiveContext].
  	self error: 'undefined extended push'!

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."
  
  	| 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 pushSpecialConstant: (extB bitShift: 8) + byte].
- 				[^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].
  	bytecode = 245 ifTrue:
  		[| selector numArgs |
  		 selector := method literalAt: (extA bitShift: 5) + (byte // 8) + 1.
  		 numArgs := (extB bitShift: 3) + (byte \\ 8).
  		 ^client sendToAbsentSelf: selector numArgs: numArgs].
  	"246-247	1111011 i	xxxxxxxx	UNASSIGNED
  	 248-249	1111100 i	xxxxxxxx	UNASSIGNED"
  	^self unusedBytecode: client at: startPC!

Item was changed:
  ----- 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 pushSpecialConstant: (SpecialConstants at: offset)].
- 		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
+ 			sendSpecial: (Smalltalk specialSelectorAt: offset + 1)
- 			send: (Smalltalk specialSelectorAt: offset + 1)
- 			super: false
  			numArgs: (Smalltalk specialNargsAt: offset + 1)].
  		type = 12 ifTrue: "non-arithmetic special selector sends"
  			[^ client
+ 				sendSpecial: (Smalltalk specialSelectorAt: offset + 17)
- 				send: (Smalltalk specialSelectorAt: offset + 17)
- 				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 17)].
  	"type = 13, 14 or 15"
  	^ client
  		send: (method literalAt: offset + 1)
  		super: false
  		numArgs: type - 13 "0, 1 & 2"!

Item was 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."
  	"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 pushSpecialConstant: false].
- 					[^client pushConstant: false].
  				 ^self interpretNSV4ExtendedPush: extB for: client].
+ 			 ^client pushSpecialConstant: offset - 14]. "0 & 1"
- 			 ^client pushConstant: offset - 14]. "0 & 1"
  		"short sends"
  		div16 < 7 ifTrue: "special selector sends"
  			[div16 = 5 ifTrue:
  				[^client
+ 					sendSpecial: (Smalltalk specialSelectorAt: offset + 1)
- 					send: (Smalltalk specialSelectorAt: offset + 1)
- 					super: false
  					numArgs: (Smalltalk specialNargsAt: offset + 1)].
  			 ^client
+ 				sendSpecial: (Smalltalk specialSelectorAt: offset + 17)
- 				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!



More information about the Vm-dev mailing list