[Vm-dev] VM Maker: BytecodeSets.spur-cb.52.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 24 09:05:42 UTC 2016


ClementBera uploaded a new version of BytecodeSets to project VM Maker:
http://source.squeak.org/VMMaker/BytecodeSets.spur-cb.52.mcz

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

Name: BytecodeSets.spur-cb.52
Author: cb
Time: 24 May 2016, 11:05:37.135424 am
UUID: b86ffaac-ba7b-4347-bcfe-518fad49fc72
Ancestors: BytecodeSets.spur-cb.51

Some fix-ups related to recent changes in the SistaV1 bytecode set.

I wonder if we should keep the pushNClosureTemps: instruction any more with the FullBlockClosure scheme. I believe it's useless.

=============== Diff against BytecodeSets.spur-cb.51 ===============

Item was changed:
  BytecodeEncoder subclass: #EncoderForSistaV1
(excessive size, no diff calculated)

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

Item was added:
+ ----- Method: InstructionClient>>branchIfNotInstanceOf:distance: (in category '*BytecodeSets-instruction decoding') -----
+ branchIfNotInstanceOf: literal distance: distance
+ 	"If the object on top of stack has the type -or one of the type- present in the literal (the literal is a behavior or an array of behavior), then pop it. Else jumps by the distance."
+ 	!

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

Item was added:
+ ----- Method: InstructionClient>>trap (in category '*BytecodeSets-instruction decoding') -----
+ trap
+ 	"triggers a specific call-back in the runtime"!

Item was removed:
- ----- 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 changed:
  ----- Method: InstructionStream>>interpretNext2ByteSistaV1Instruction:for:extA:extB:startPC: (in category '*BytecodeSets-SistaV1-decoding') -----
  interpretNext2ByteSistaV1Instruction: bytecode for: client extA: extA extB: extB startPC: startPC
  	"Send to the argument, client, a message that specifies the next instruction.
  	 This method handles the two-byte codes.
  	 For a table of the bytecode set, see EncoderForV1's class comment."
  
  	| byte method |
  	method := self method.
  	byte := self method at: pc.
  	pc := pc + 1.
  	"We do an inline quasi-binary search on bytecode"
  	bytecode < 234 ifTrue: "pushes"
  		[bytecode < 231 ifTrue:
  			[bytecode < 229 ifTrue:
  				[| literal |
  				 bytecode = 226 ifTrue:
  					[^client pushReceiverVariable: (extA bitShift: 8) + byte].
  				 literal := method literalAt: (extA bitShift: 8) + byte + 1.
  				 bytecode = 227 ifTrue:
  					[^client pushLiteralVariable: literal].
  				 ^client pushConstant: literal].
  			bytecode = 229 ifTrue:
  				[^client pushTemporaryVariable: byte]. 
  			^client pushClosureTemps: byte]. 
  		bytecode = 231 ifTrue:
  			[^byte < 128
  				ifTrue: [client pushNewArrayOfSize: byte]
  				ifFalse: [client pushConsArrayWithElements: byte - 128]].
  		bytecode = 232 ifTrue:
  			[^client pushConstant: (extB bitShift: 8) + byte].
  		^client pushConstant: (Character value: (extB bitShift: 8) + byte)].
+ 	bytecode < 240 ifTrue: "sends and jump"
- 	bytecode < 240 ifTrue: "sends, trap and jump"
  		[bytecode < 236 ifTrue: "sends"
  			[(bytecode = 235 and: [extB >= 64]) ifTrue:
  				[^client
  					directedSuperSend: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
  					numArgs: (extB - 64 bitShift: 3) + (byte \\ 8)].
  			 ^client
  				send: (method literalAt: (extA bitShift: 5) + (byte // 8) + 1)
  				super: bytecode = 235
  				numArgs: (extB bitShift: 3) + (byte \\ 8)].
  		 bytecode = 236 ifTrue:
+ 			[^self unusedBytecode: client at: startPC].
- 			[^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>>interpretNext3ByteSistaV1Instruction:for:extA:extB:startPC: (in category '*BytecodeSets-SistaV1-decoding') -----
  interpretNext3ByteSistaV1Instruction: bytecode for: client extA: extA extB: extB startPC: startPC
  	"Send to the argument, client, a message that specifies the next instruction.
  	 This method handles the three-byte codes.
  	 For a table of the bytecode set, see EncoderForSistaV1's class comment."
  
  	| method byte2 byte3 literal |
  	method := self method.
  	byte2 := method at: pc.
  	byte3 := method at: pc + 1.
  	pc := pc + 2.
  	"we search the bytecodes by what we expect to be the static frequency."
  	bytecode = 248 ifTrue:
  		[byte3 >= 128 ifTrue:
  			[^client callInlinePrimitive: byte2 + (byte3 - 128 bitShift: 8)].
  		 ^client callPrimitive: byte2 + (byte3 bitShift: 8)].
+ 	"249		11111001 	xxxxxxxx	syyyyyyy	Reserved for Push Float"
+ 	bytecode = 249 ifTrue: [^ self unusedBytecode: client at: startPC].
  	bytecode = 250 ifTrue:
  		["**	250  11111010  eeiiikkk  jjjjjjjj  Push Closure Num Copied iii (+ExtA//16*8) Num Args kkk (+ ExtA\\16*8) BlockSize jjjjjjjj (+ExtB*256). ee = num extensions"
  		 ^client
  			pushClosureCopyNumCopiedValues: ((byte2 bitShift: -3) bitAnd: 7) + (extA // 16 bitShift: 3)
  			numArgs: (byte2 bitAnd: 7) + (extA \\ 16 bitShift: 3)
  			blockSize: byte3 + (extB bitShift: 8)].
  	bytecode = 251 ifTrue:
  		[^client pushRemoteTemp: byte2 inVectorAt: byte3].
  	bytecode = 252 ifTrue:
  		[^client storeIntoRemoteTemp: byte2 inVectorAt: byte3].
  	bytecode = 253 ifTrue:
  		[^client popIntoRemoteTemp: byte2 inVectorAt: byte3].
+ 	"**	254		11111110	kkkkkkkk	jjjjjjjj		branch If Not Instance Of Behavior/Array Of Behavior kkkkkkkk (+ Extend A * 256, where Extend A >= 0) distance jjjjjjjj (+ Extend B * 256, where Extend B >= 0)"
- 	"249		11111001 	xxxxxxxx	syyyyyyy	Reserved for Push Float"
- 	"254-255	1111111 i	xxxxxxxx	yyyyyyyy	UNASSIGNED"
  	literal := method literalAt: (extA bitShift: 8) + byte2 + 1.
+ 	bytecode = 253 ifTrue: 
+ 		[^ client branchIfNotInstanceOf: literal distance: (extB bitShift: 8) + byte3 ].
+ 	"*	255		11111111	xxxxxxxx	siyyyyyy	push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
  	 ^client
  			pushFullClosure: literal
+ 			numCopied: (byte3 bitAnd: 16r3F).!
- 			numCopied: byte3.!

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].
  				 offset = 12 ifTrue:
  					[^client pushReceiver].
  				 offset = 13 ifTrue:
  					[^client pushConstant: true].
  				 offset = 14 ifTrue:
  					[^client pushConstant: false].
  				 offset = 15 ifTrue:
  					[^client pushConstant: nil]].
  			"div16 = 5"
  			 offset < 2 ifTrue:
  				[^client pushConstant: offset].
  			 offset = 2 ifTrue:
  				[^self interpretSistaV1ExtendedPush: extB for: client].
  			 offset = 3 ifTrue:
  				[^client doDup].
  			
  			 offset = 8 ifTrue:
  				[^client methodReturnReceiver].
  			 offset = 9 ifTrue:
  				[^client methodReturnConstant: true].
  			 offset = 10 ifTrue:
  				[^client methodReturnConstant: false].
  			 offset = 11 ifTrue:
  				[^client methodReturnConstant: nil].
  			 offset = 12 ifTrue:
  				[^client methodReturnTop].
  			 offset = 13 ifTrue:
  				[^client blockReturnConstant: nil].
  			 offset = 14 ifTrue:
  				[^client blockReturnTop].
  			 offset = 15 ifTrue:
  				[^client doNop].
  			 ^self unusedBytecode: client at: savedPC].
  		"short sends"
  		div16 = 6 ifTrue:
  			[^client
  				send: (Smalltalk specialSelectorAt: offset + 1)
  				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 1)].
  		 div16 = 7 ifTrue:
  			[^client
  				send: (Smalltalk specialSelectorAt: offset + 17)
  				super: false
  				numArgs: (Smalltalk specialNargsAt: offset + 17)].
  		^client
  			send: (method literalAt: offset + 1)
  			super: false
  			numArgs: div16 - 8].
  	"div16 >= 11; bytecode >= 176"
  	div16 < 14 ifTrue:
  		[div16 = 11 ifTrue:
  			[offset < 8 ifTrue:
  				[^client jump: offset + 1].
  			 ^client jump: offset - 7 if: true].
  		 div16 = 12 ifTrue:
  			[offset < 8 ifTrue:
  				[^client jump: offset + 1 if: false].
  			 ^client popIntoReceiverVariable: offset - 8].
  		 "div16 = 13"
  		 offset < 8 ifTrue:
  		 	[^client popIntoTemporaryVariable: offset].
  		 offset = 8 ifTrue: [ ^ client doPop ].
+ 		 offset = 8 ifTrue: [ ^ client trap ].
  		 ^self unusedBytecode: client at: savedPC].
  	"2 byte and 3 byte codes"
  	byte < 248 ifTrue:
  		[^self interpretNext2ByteSistaV1Instruction: byte for: client extA: extA extB: extB startPC: savedPC].
  	^self interpretNext3ByteSistaV1Instruction: byte for: client extA: extA extB: extB startPC: savedPC!



More information about the Vm-dev mailing list