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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 30 14:33:03 UTC 2016


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

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

Name: BytecodeSets.spur-eem.56
Author: eem
Time: 30 August 2016, 3:32:54.862873 pm
UUID: c6cb6456-6083-4dbf-847c-f271bfa173e9
Ancestors: BytecodeSets.spur-cb.55

Bring some of the InstructionStream decoding machinery up-to-date w.r.t. the specification (EncoderForSistaV1's class comment).
Implement back-end generation of some of the Sista bytecodes.
Have InstructionPrinter>>callInlinePrimitive: be the keeper of the truth w.r.t. inline primitives.

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

Item was added:
+ ----- Method: BytecodeEncoder>>sizeBranchIfNotInstanceOf:distance: (in category '*BytecodeSets-opcode sizing') -----
+ sizeBranchIfNotInstanceOf: behaviorOrArrayOfBehaviorLiteralIndex distance: jumpDistance
+ 	^self sizeOpcodeSelector: #genBranchIfNotInstanceOf:distance:
+ 			withArguments: {behaviorOrArrayOfBehaviorLiteralIndex. jumpDistance}!

Item was added:
+ ----- Method: BytecodeEncoder>>sizeTrap (in category '*BytecodeSets-opcode sizing') -----
+ sizeTrap
+ 	^self sizeOpcodeSelector: #genTrap withArguments: #()!

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

Item was added:
+ ----- Method: InstructionPrinter>>branchIfNotInstanceOf:distance: (in category '*BytecodeSets-SistaV1-decoding') -----
+ branchIfNotInstanceOf: behaviorOrArrayOfBehavior 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."
+ 	self print: 'branchIfNotInstanceOf: ', behaviorOrArrayOfBehavior printString, ' distance: ', distance printString!

Item was changed:
  ----- Method: InstructionPrinter>>callInlinePrimitive: (in category '*BytecodeSets-instruction decoding') -----
  callInlinePrimitive: index
  	"Print the callInlinePrimitive."
+ 	self print: 'callInlinePrimitive: ' , ((#((1000 ' class')
+ 										(1001 ' pointer numSlots')
+ 										(1002 ' pointer basicSize')
+ 										(1003 ' byte8Type format numBytes')
+ 										(1004 ' short16Type format numSho')
+ 										(1005 ' word32Type format numWord')
+ 										(1006 ' doubleWord64Type format n')
+ 										(1011 ' fixed pointer basicNew')
+ 										(2000 ' SmallInteger #+')
+ 										(2001 ' SmallInteger #-')
+ 										(2002 ' SmallInteger #*')
+ 										(2003 ' SmallInteger #/')
+ 										(2004 ' SmallInteger #//')
+ 										(2005 ' SmallInteger #\\')
+ 										(2006 ' SmallInteger #quo:')
+ 										(2016 ' SmallInteger #bitAnd:')
+ 										(2017 ' SmallInteger #bitOr:')
+ 										(2018 ' SmallInteger #bitXor:')
+ 										(2019 ' SmallInteger #bitShift:')
+ 										(2032 ' SmallInteger #>')
+ 										(2033 ' SmallInteger #<')
+ 										(2034 ' SmallInteger #>=')
+ 										(2035 ' SmallInteger #<=')
+ 										(2036 ' SmallInteger #=')
+ 										(2037 ' SmallInteger #~=')
+ 										(2064 ' Pointer Object>>at:')
+ 										(2065 ' Byte Object>>at:')
+ 										(2066 ' 16-bit Word Object>>at:')
+ 										(2067 ' Word Object>>at:')
+ 										(2068 ' DoubleWord Object>>at:')
+ 										(2069 ' QuadWord Object>>at:')
+ 										(3000 ' Pointer Object>>at:put:')
+ 										(3001 ' Byte Object>>at:put:')
+ 										(3002 ' Word Object>>at:put:')
+ 										(3003 ' DoubleWord Object>>at:put')
+ 										(3004 ' QuadWord Object>>at:put:'))
+ 											detect: [:tuple| tuple first = index]
+ 											ifNone: [])
+ 										ifNil: [index printString]
+ 										ifNotNil: [:tuple| tuple last])!
- 
- 	self print: 'callInlinePrimitive: ' , index printString!

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	siyyyyyy	push Closure Compiled block literal index xxxxxxxx (+ Extend A * 256) numCopied yyyyyy receiverOnStack: s = 1 ignoreOuterContext: i = 1"
+ 	bytecode = 249 ifTrue:
+ 		[literal := method literalAt: (extA bitShift: 8) + byte2 + 1.
+ 		 ^client pushFullClosure: literal numCopied: (byte3 bitAnd: 16r3F)].
- 	"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)"
+ 	bytecode = 254 ifTrue: 
- 	literal := method literalAt: (extA bitShift: 8) + byte2 + 1.
- 	bytecode = 253 ifTrue: 
  		[^ client branchIfNotInstanceOf: literal distance: (extB bitShift: 8) + byte3 ].
+ 	^self unusedBytecode: client at: startPC!
- 	"*	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).!

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 = 9 ifTrue: [ ^ client trap ].
- 		 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!

Item was added:
+ ----- Method: StackDepthFinder>>branchIfNotInstanceOf:distance: (in category '*BytecodeSets-SistaV1-decoding') -----
+ branchIfNotInstanceOf: behaviorOrArrayOfBehavior distance: anInteger 
+ 	self drop!



More information about the Vm-dev mailing list