[Vm-dev] VM Maker: VMMaker.oscog-cb.1768.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 6 00:33:48 UTC 2016


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

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

Name: VMMaker.oscog-cb.1768
Author: cb
Time: 5 April 2016, 5:30:34.345 pm
UUID: 5027b1a4-9d8d-4358-91f7-d3de094ebd59
Ancestors: VMMaker.oscog-cb.1767

extract constant from JIT code.
Added support in the interpreter for remote inst var access and access flags in other instructions.

=============== Diff against VMMaker.oscog-cb.1767 ===============

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSistaV1 (in category 'initialization') -----
  initializeBytecodeTableForSistaV1
  	"See e.g. the cass comment for EncoderForSistaV1"
  	"StackInterpreter initializeBytecodeTableForSistaV1"
  	"Note: This table will be used to generate a C switch statement."
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForSistaV1.
  	BytecodeSetHasDirectedSuperSend := true.
  
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 pushConstantTrueBytecode)
  		( 78	 pushConstantFalseBytecode)
  		( 79	 pushConstantNilBytecode)
  		( 80	 pushConstantZeroBytecode)
  		( 81	 pushConstantOneBytecode)
  		( 82	 extPushPseudoVariable)
  		( 83	 duplicateTopBytecode)
  	
  		( 84 87	unknownBytecode)
  		( 88	returnReceiver)
  		( 89	returnTrue)
  		( 90	returnFalse)
  		( 91	returnNil)
  		( 92	returnTopFromMethod)
  		( 93	returnNilFromBlock)
  		( 94	returnTopFromBlock)
  		( 95	extNopBytecode)
  
  		( 96	 bytecodePrimAdd)
  		( 97	 bytecodePrimSubtract)
  		( 98	 bytecodePrimLessThanSistaV1) "for booleanCheatSistaV1:"
  		( 99	 bytecodePrimGreaterThanSistaV1) "for booleanCheatSistaV1:"
  		(100	 bytecodePrimLessOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(101	 bytecodePrimGreaterOrEqualSistaV1) "for booleanCheatSistaV1:"
  		(102	 bytecodePrimEqualSistaV1) "for booleanCheatSistaV1:"
  		(103	 bytecodePrimNotEqualSistaV1) "for booleanCheatSistaV1:"
  		(104	 bytecodePrimMultiply)
  		(105	 bytecodePrimDivide)
  		(106	 bytecodePrimMod)
  		(107	 bytecodePrimMakePoint)
  		(108	 bytecodePrimBitShift)
  		(109	 bytecodePrimDiv)
  		(110	 bytecodePrimBitAnd)
  		(111	 bytecodePrimBitOr)
  
  		(112	 bytecodePrimAt)
  		(113	 bytecodePrimAtPut)
  		(114	 bytecodePrimSize)
  		(115	 bytecodePrimNext)		 "i.e. a 0 arg special selector"
  		(116	 bytecodePrimNextPut)		 "i.e. a 1 arg special selector"
  		(117	 bytecodePrimAtEnd)
  		(118	 bytecodePrimIdenticalSistaV1) "for booleanCheatSistaV1:"
  		(119	 bytecodePrimClass)
  		(120	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(121	 bytecodePrimValue)
  		(122	 bytecodePrimValueWithArg)
  		(123	 bytecodePrimDo)			"i.e. a 1 arg special selector"
  		(124	 bytecodePrimNew)			"i.e. a 0 arg special selector"
  		(125	 bytecodePrimNewWithArg)	"i.e. a 1 arg special selector"
  		(126	 bytecodePrimPointX)		"i.e. a 0 arg special selector"
  		(127	 bytecodePrimPointY)		"i.e. a 0 arg special selector"
  
  		(128 143	sendLiteralSelector0ArgsBytecode)
  		(144 159	sendLiteralSelector1ArgBytecode)
  		(160 175	sendLiteralSelector2ArgsBytecode)
  
  		(176 183	shortUnconditionalJump)
  		(184 191	shortConditionalJumpTrue)
  		(192 199	shortConditionalJumpFalse)
  	
  		(200 207	storeAndPopReceiverVariableBytecode)
  		(208 215	storeAndPopTemporaryVariableBytecode)
  		(216		popStackBytecode)
  		(217		unconditionnalTrapBytecode)
  
  		(218 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		pushClosureTempsBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
  		(236		unknownBytecode)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
+ 		(240		extSistaStoreAndPopReceiverVariableBytecode)
+ 		(241		extSistaStoreAndPopLiteralVariableBytecode)
- 		(240		extStoreAndPopReceiverVariableBytecode)
- 		(241		extStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
+ 		(243		extSistaStoreReceiverVariableBytecode)
+ 		(244		extSistaStoreLiteralVariableBytecode)
- 		(243		extStoreReceiverVariableBytecode)
- 		(244		extStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
+ 		(251		extPushRemoteTempOrInstVarLongBytecode)
+ 		(252		extStoreRemoteTempOrInstVarLongBytecode)
+ 		(253		extStoreAndPopRemoteTempOrInstVarLongBytecode)
- 		(251		pushRemoteTempLongBytecode)
- 		(252		storeRemoteTempLongBytecode)
- 		(253		storeAndPopRemoteTempLongBytecode)
  				
  		(254		extJumpIfNotInstanceOfBehaviorsOrPopBytecode)
  
  		(255		unknownBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>extPushRemoteTempOrInstVarLongBytecode (in category 'stack bytecodes') -----
+ extPushRemoteTempOrInstVarLongBytecode
+ 	| slotIndex tempIndex object |
+ 	slotIndex := self fetchByte.
+ 	tempIndex := self fetchByte.
+ 	self fetchNextBytecode.
+ 	(tempIndex noMask: self remoteIsInstVarAccess)
+ 		ifTrue: [self pushRemoteTemp: slotIndex inVectorAt: tempIndex]
+ 		ifFalse: 
+ 			[ slotIndex := slotIndex + (extA << 8).
+ 			extA := extB := 0.
+ 			object := self temporary: tempIndex in: localFP.
+ 			self pushMaybeContext: object receiverVariable: slotIndex ]!

Item was added:
+ ----- Method: StackInterpreter>>extSistaStoreAndPopLiteralVariableBytecode (in category 'stack bytecodes') -----
+ extSistaStoreAndPopLiteralVariableBytecode
+ 	"236		11101100	i i i i i i i i	Pop and Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 	(3) ExtB lowest bit implies no store check is needed, ExtB next bit implies the object may be a context, other bits in the extension are unused."
+ 	| variableIndex value |
+ 	variableIndex := self fetchByte + (extA << 8).
+ 	value := self internalStackTop.
+ 	self internalPop: 1.
+ 	extA := extB := 0..
+ 	self storeLiteralVariable: variableIndex withValue: value.
+ 	self fetchNextBytecode.!

Item was added:
+ ----- Method: StackInterpreter>>extSistaStoreAndPopReceiverVariableBytecode (in category 'stack bytecodes') -----
+ extSistaStoreAndPopReceiverVariableBytecode
+ 	"235		11101011	i i i i i i i i	Pop and Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ 	(3) ExtB lowest bit implies no store check is needed, ExtB next bit implies the object may be a context, other bits in the extension are unused."
+ 	| variableIndex value |
+ 	variableIndex := self fetchByte + (extA << 8).
+ 	extA := extB := 0.
+ 	value := self internalStackTop.
+ 	self internalPop: 1.
+ 	self storeMaybeContextReceiverVariable: variableIndex withValue: value.
+ 	self fetchNextBytecode.!

Item was added:
+ ----- Method: StackInterpreter>>extSistaStoreLiteralVariableBytecode (in category 'stack bytecodes') -----
+ extSistaStoreLiteralVariableBytecode
+ 	"233		11101001	i i i i i i i i	Store Literal Variable #iiiiiiii (+ Extend A * 256)
+ 	(3) ExtB lowest bit implies no store check is needed, ExtB next bit implies the object may be a context, other bits in the extension are unused."
+ 	| variableIndex |
+ 	variableIndex := self fetchByte + (extA << 8).
+ 	extA := extB := 0.
+ 	self storeLiteralVariable: variableIndex withValue: self internalStackTop.
+ 	self fetchNextBytecode.!

Item was added:
+ ----- Method: StackInterpreter>>extSistaStoreReceiverVariableBytecode (in category 'stack bytecodes') -----
+ extSistaStoreReceiverVariableBytecode
+ 	"232		11101000	i i i i i i i i	Store Receiver Variable #iiiiiii (+ Extend A * 256)
+ 	(3) ExtB lowest bit implies no store check is needed, ExtB next bit implies the object may be a context, other bits in the extension are unused."
+ 	| variableIndex |
+ 	variableIndex := self fetchByte + (extA << 8).
+ 	extA := extB := 0.
+ 	self storeMaybeContextReceiverVariable: variableIndex withValue: self internalStackTop.
+ 	self fetchNextBytecode.!

Item was added:
+ ----- Method: StackInterpreter>>extStoreAndPopRemoteTempOrInstVarLongBytecode (in category 'stack bytecodes') -----
+ extStoreAndPopRemoteTempOrInstVarLongBytecode
+ 	self extStoreRemoteTempOrInstVarLongBytecode.
+ 	self internalPop: 1!

Item was added:
+ ----- Method: StackInterpreter>>extStoreRemoteTempOrInstVarLongBytecode (in category 'stack bytecodes') -----
+ extStoreRemoteTempOrInstVarLongBytecode
+ 	| slotIndex tempIndex object |
+ 	slotIndex := self fetchByte.
+ 	tempIndex := self fetchByte.
+ 	self fetchNextBytecode.
+ 	(tempIndex noMask: self remoteIsInstVarAccess)
+ 		ifTrue: [self storeRemoteTemp: slotIndex inVectorAt: tempIndex]
+ 		ifFalse: 
+ 			[ slotIndex := slotIndex + (extA << 8).
+ 			extA := extB := 0.
+ 			object := self temporary: tempIndex in: localFP.
+ 			self storeMaybeContext: object receiverVariable: slotIndex withValue: self internalStackTop ]!

Item was added:
+ ----- Method: StackInterpreter>>pushMaybeContext:receiverVariable: (in category 'stack bytecodes') -----
+ pushMaybeContext: obj receiverVariable: fieldIndex
+ 	"Must trap accesses to married and widowed contexts.
+ 	 But don't want to check on all inst var accesses.  This
+ 	 method is only used by the long-form bytecodes, evading
+ 	 the cost. Note that the method, closure and receiver fields
+ 	 of married contexts are correctly initialized so they don't
+ 	 need special treatment on read.  Only sender, instruction
+ 	 pointer and stack pointer need to be intercepted on reads."
+ 	<inline: true>
+ 	((self isReadMediatedContextInstVarIndex: fieldIndex)
+ 	and: [objectMemory isContextNonImm: obj])
+ 		ifTrue:
+ 			[self internalPush: (self instVar: fieldIndex ofContext: obj)]
+ 		ifFalse:
+ 			[self internalPush: (objectMemory fetchPointer: fieldIndex ofObject: obj)]!

Item was changed:
  ----- Method: StackInterpreter>>pushMaybeContextReceiverVariable: (in category 'stack bytecodes') -----
  pushMaybeContextReceiverVariable: fieldIndex
  	"Must trap accesses to married and widowed contexts.
  	 But don't want to check on all inst var accesses.  This
  	 method is only used by the long-form bytecodes, evading
  	 the cost. Note that the method, closure and receiver fields
  	 of married contexts are correctly initialized so they don't
  	 need special treatment on read.  Only sender, instruction
  	 pointer and stack pointer need to be intercepted on reads."
- 	| rcvr |
  	<inline: true>
+ 	self pushMaybeContext: self receiver receiverVariable: fieldIndex!
- 	rcvr := self receiver.
- 	((self isReadMediatedContextInstVarIndex: fieldIndex)
- 	and: [objectMemory isContextNonImm: rcvr])
- 		ifTrue:
- 			[self internalPush: (self instVar: fieldIndex ofContext: rcvr)]
- 		ifFalse:
- 			[self internalPush: (objectMemory fetchPointer: fieldIndex ofObject: rcvr)]!

Item was added:
+ ----- Method: StackInterpreter>>remoteIsInstVarAccess (in category 'stack bytecodes') -----
+ remoteIsInstVarAccess
+ 	"If this byte is set in the second byte (zero-based) of the instruction, 
+ 	the remote temp instruction is in fact a remote inst var access"
+ 	<api>
+ 	<cmacro>
+ 	^ 128 "1 << 7"!

Item was added:
+ ----- Method: StackInterpreter>>storeMaybeContext:receiverVariable:withValue: (in category 'stack bytecodes') -----
+ storeMaybeContext: obj receiverVariable: fieldIndex withValue: anObject
+ 	"Must trap accesses to married and widowed contexts.
+ 	 But don't want to check on all inst var accesses.  This
+ 	 method is only used by the long-form bytecodes, evading the cost."
+ 	<inline: true>
+ 	((self isWriteMediatedContextInstVarIndex: fieldIndex)
+ 	and: [(objectMemory isContextNonImm: obj)
+ 	and: [self isMarriedOrWidowedContext: obj]])
+ 		ifTrue:
+ 			[self instVar: fieldIndex ofContext: obj put: anObject]
+ 		ifFalse:
+ 			[objectMemory storePointerImmutabilityCheck: fieldIndex ofObject: obj withValue: anObject]
+ !

Item was changed:
  ----- Method: StackInterpreter>>storeMaybeContextReceiverVariable:withValue: (in category 'stack bytecodes') -----
  storeMaybeContextReceiverVariable: fieldIndex withValue: anObject
  	"Must trap accesses to married and widowed contexts.
  	 But don't want to check on all inst var accesses.  This
  	 method is only used by the long-form bytecodes, evading the cost."
+ 	self storeMaybeContext: self receiver receiverVariable: fieldIndex withValue: anObject
- 	| rcvr |
- 	rcvr := self receiver.
- 	((self isWriteMediatedContextInstVarIndex: fieldIndex)
- 	and: [(objectMemory isContextNonImm: rcvr)
- 	and: [self isMarriedOrWidowedContext: rcvr]])
- 		ifTrue:
- 			[self instVar: fieldIndex ofContext: rcvr put: anObject]
- 		ifFalse:
- 			[objectMemory storePointerImmutabilityCheck: fieldIndex ofObject: rcvr withValue: anObject]
  !

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genExtPushRemoteTempOrInstVarLongBytecode (in category 'bytecode generators') -----
  genExtPushRemoteTempOrInstVarLongBytecode
  	| index maybeContext |
+ 	^ (byte2 noMask: coInterpreter remoteIsInstVarAccess)
- 	^ (byte2 noMask: 1 << 7)
  		ifTrue: [ self genPushRemoteTempLongBytecode ]
  		ifFalse: 
  			[ maybeContext := self extBSpecifiesMaybeContext.
  			index := byte1 + (extA << 8).
  			extA := 0.
  			extB := 0.
  			((coInterpreter isReadMediatedContextInstVarIndex: index) and: [ maybeContext ])
+ 				ifTrue: [ self genPushMaybeContextRemoteInstVar: index inObjectAt: byte2 - coInterpreter remoteIsInstVarAccess ]
+ 				ifFalse: [ self genPushRemoteInstVar: index inObjectAt: byte2 - coInterpreter remoteIsInstVarAccess ] ]!
- 				ifTrue: [ self genPushMaybeContextRemoteInstVar: index inObjectAt: byte2 - (1 << 7) ]
- 				ifFalse: [ self genPushRemoteInstVar: index inObjectAt: byte2 - (1 << 7) ] ]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genExtStorePopRemoteTempOrInstVarLongBytecode: (in category 'bytecode generators') -----
  genExtStorePopRemoteTempOrInstVarLongBytecode: boolean
  	| index maybeContext needsStoreCheck |
  	needsStoreCheck := self sistaNeedsStoreCheck.
  	maybeContext := self extBSpecifiesMaybeContext.
  	extB := 0.
+ 	(byte2 noMask: coInterpreter remoteIsInstVarAccess)
- 	(byte2 noMask: 1 << 7)
  		ifTrue: 
  			[ self genStorePop: boolean RemoteTemp: byte1 At: byte2 needsStoreCheck: needsStoreCheck.
  			self cppIf: IMMUTABILITY ifTrue: [ self annotateBytecode: self Label ] ]
  		ifFalse: 
  			[ index := byte1 + (extA << 8).
  			extA := 0.
  			((coInterpreter isWriteMediatedContextInstVarIndex: index) and: [ maybeContext ])
  				ifTrue: [ self 
  						genStorePop: boolean 
  						MaybeContextRemoteInstVar: index 
+ 						ofObjectAt: byte2 - coInterpreter remoteIsInstVarAccess 
- 						ofObjectAt: byte2 - (1 << 7) 
  						needsStoreCheck: needsStoreCheck ]
  				ifFalse: [ self 
  						genStorePop: boolean 
  						RemoteInstVar: index 
+ 						ofObjectAt: byte2 - coInterpreter remoteIsInstVarAccess 
- 						ofObjectAt: byte2 - (1 << 7) 
  						needsStoreCheck: needsStoreCheck ] ].
  	^ 0!



More information about the Vm-dev mailing list