[Vm-dev] VM Maker: VMMaker.oscog-eem.1778.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Apr 7 02:50:54 UTC 2016


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

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

Name: VMMaker.oscog-eem.1778
Author: eem
Time: 6 April 2016, 7:48:57.63562 pm
UUID: cdfc4d49-1f47-4ec4-a4e1-af37cd734fed
Ancestors: VMMaker.oscog-eem.1777

Split the FullBlockClosure>>value[:...] support into its own set of primitives (531 through 538).  Make these optional, depending on SistaV1BytecodeSet.

No longer follow the method and context fields in a closure in activateNewClosureMethod:numArgs:mayContextSwitch:; the caller will have failed if these are forwarders, so there is no need to check again.

Simulator:
Fix StackInterpreterSimulator>>endPCOf: for CompiledBlocks, where a blockReturn is the last bytecode of a block method.

Slang:
To allow methods to be optional upon a bytecode set add the name of the bytecode set as a key to the value true in initializationOptions in all of the bytecode set initializers, with names SqueakV3PlusClosuresBytecodeSet, NewsqueakV4BytecodeSet, SistaV1BytecodeSet.

=============== Diff against VMMaker.oscog-eem.1777 ===============

Item was changed:
  ----- Method: CoInterpreter>>activateNewClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod.
  	 Override to handle the various interpreter/machine code transitions
  	 and to create an appropriate frame layout."
  	| numCopied outerContext theMethod methodHeader inInterpreter closureIP switched |
  	<inline: true>
+ 	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
+ 	self assert: (objectMemory isContext: outerContext).
- 	outerContext := objectMemory followField: ClosureOuterContextIndex ofObject: blockClosure.
  	self assert: outerContext ~= blockClosure.
  	numCopied := self copiedValueCountOfClosure: blockClosure.
+ 	theMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
+ 	self assert: (objectMemory isOopCompiledMethod: theMethod).
- 	theMethod := objectMemory followField: MethodIndex ofObject: outerContext.
  	methodHeader := self rawHeaderOf: theMethod.
  	(self isCogMethodReference: methodHeader) ifTrue:
  		[^self executeCogBlock: (self cogMethodOf: theMethod)
  			closure: blockClosure
  			mayContextSwitch: mayContextSwitch].
  	"How do we know when to compile a block method?
  	 One simple criterion is to check if the block is running within its inner context,
  	 i.e. if the outerContext is married.
  	 Even simpler is to remember the previous block entered via the interpreter and
  	 compile if this is the same one.  But we can thrash trying to compile an uncoggable
  	 method unless we try and remember which ones can't be cogged.  So also record
  	 the last block method we failed to compile and avoid recompiling it."
  	(self methodWithHeaderShouldBeCogged: methodHeader)
  		ifTrue:
  			[theMethod = lastCoggableInterpretedBlockMethod
  				ifTrue:
  					[theMethod ~= lastUncoggableInterpretedBlockMethod ifTrue:
  						[cogit cog: theMethod selector: objectMemory nilObject.
  						 (self methodHasCogMethod: theMethod) ifTrue:
  							[^self executeCogBlock: (self cogMethodOf: theMethod)
  								closure: blockClosure
  								mayContextSwitch: mayContextSwitch].
  						 cogCompiledCodeCompactionCalledFor ifFalse:
  							[lastUncoggableInterpretedBlockMethod := theMethod]]]
  				ifFalse:
  					[lastCoggableInterpretedBlockMethod := theMethod]]
  		ifFalse:
  			[self maybeFlagMethodAsInterpreted: theMethod].
  
  	self assert: (self methodHasCogMethod: theMethod) not.
  	"Because this is an uncogged method we need to continue via the interpreter.
  	 We could have been reached either from the interpreter, in which case we
  	 should simply return, or from a machine code frame or from a compiled
  	 primitive.  In these latter two cases we must longjmp back to the interpreter.
  	 The instructionPointer tells us which path we took.
  	 If the sender was an interpreter frame but called through a (failing) primitive
  	 then make sure we restore the saved instruction pointer and avoid pushing
  	 ceReturnToInterpreterPC which is only valid between an interpreter caller
  	 frame and a machine code callee frame."
  	(inInterpreter := instructionPointer >= objectMemory startOfMemory) ifFalse:
  		[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  			[instructionPointer := self iframeSavedIP: framePointer]].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: 0. "FoxIFSavedIP"
+ 	"Because inst var access is not checked, we must follow the receiver in Spur to ensure it is valid."
  	self push: (objectMemory followField: ReceiverIndex ofObject: outerContext).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + ClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
  	"The initial instructions in the block nil-out remaining temps."
  
  	"the instruction pointer is a pointer variable equal to 
  	method oop + ip + BaseHeaderSize 
  	-1 for 0-based addressing of fetchByte 
  	-1 because it gets incremented BEFORE fetching currentByte"
  	closureIP := self quickFetchInteger: ClosureStartPCIndex ofObject: blockClosure.
  	instructionPointer := theMethod + closureIP + objectMemory baseHeaderSize - 2.
  	self setMethod: theMethod methodHeader: methodHeader.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
  	switched := false.
  	stackPointer < stackLimit ifTrue:
  		[switched := self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch].
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveClosureValue (in category 'control primitives') -----
  primitiveClosureValue
  	| blockClosure numArgs closureMethod outerContext |
  	blockClosure := self stackValue: argumentCount.
  	numArgs := self argumentCountOfClosure: blockClosure.
  	argumentCount = numArgs ifFalse:
  		[^self primitiveFail].
  
+ 	"Somewhat paranoiac checks we need while debugging that we may be able to discard
+ 	 in a robust system."
+ 	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
+ 	(objectMemory isContext: outerContext) ifFalse:
+ 		[^self primitiveFail].
- 	(self is: blockClosure instanceOf: (objectMemory splObj: ClassBlockClosure) compactClassIndex: ClassBlockClosureCompactIndex)
- 		ifTrue: 
- 			[ "Somewhat paranoiac checks we need while debugging that we may be able to discard
- 			 in a robust system."
- 			outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
- 			(objectMemory isContext: outerContext) ifFalse:
- 				[^self primitiveFail].
- 			closureMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
- 			"Check if the closure's method is actually a CompiledMethod."
- 			(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
- 				[^self primitiveFail].
  
+ 	closureMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
+ 	"Check if the closure's method is actually a CompiledMethod."
+ 	(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	self activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: true!
- 			"Note we use activateNewMethod, not executeNewMethod, to avoid
- 			 quickCheckForInterrupts.  Don't check until we have a full activation."
- 			self activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: true ]
- 		ifFalse: 
- 			[ closureMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
- 			(objectMemory isOopCompiledMethod: closureMethod)
- 				ifFalse: [ ^ self primitiveFail ].
- 			"Note we use activateNewMethod, not executeNewMethod, to avoid
- 			 quickCheckForInterrupts.  Don't check until we have a full activation."
- 			self activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: true ]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveClosureValueNoContextSwitch (in category 'control primitives') -----
  primitiveClosureValueNoContextSwitch
  	"An exact clone of primitiveClosureValue except that this version will not
  	 check for interrupts on stack overflow.  It may invoke the garbage collector
  	 but will not switch processes.  See checkForInterruptsMayContextSwitch:"
  	<api>
  	| blockClosure numArgs closureMethod outerContext |
  	blockClosure := self stackValue: argumentCount.
  	numArgs := self argumentCountOfClosure: blockClosure.
  	argumentCount = numArgs ifFalse:
  		[^self primitiveFail].
  
  	"Somewhat paranoiac checks we need while debugging that we may be able to discard
  	 in a robust system."
  	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	(objectMemory isContext: outerContext) ifFalse:
  		[^self primitiveFail].
+ 
  	closureMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
  	"Check if the closure's method is actually a CompiledMethod."
  	(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
  		[^self primitiveFail].
  
- 	"Note we use activateNewMethod, not executeNewMethod, to avoid
- 	 quickCheckForInterrupts.  Don't check until we have a full activation."
  	self activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: false!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveClosureValueWithArgs (in category 'control primitives') -----
  primitiveClosureValueWithArgs
  	| argumentArray arraySize blockClosure numArgs closureMethod index outerContext |
  	argumentArray := self stackTop.
  	(objectMemory isArray: argumentArray) ifFalse:
  		[^self primitiveFail].
  
  	"Check for enough space in thisContext to push all args"
  	arraySize := objectMemory numSlotsOf: argumentArray.
  	(self roomToPushNArgs: arraySize) ifFalse:
  		[^self primitiveFail].
  
  	blockClosure := self stackValue: argumentCount.
  	numArgs := self argumentCountOfClosure: blockClosure.
  	arraySize = numArgs ifFalse:
  		[^self primitiveFail].
  
  	"Somewhat paranoiac checks we need while debugging that we may be able to discard
  	 in a robust system."
  	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	(objectMemory isContext: outerContext) ifFalse:
  		[^self primitiveFail].
  	closureMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
  	"Check if the closure's method is actually a CompiledMethod."
  	(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
  		[^self primitiveFail].
  
  	self popStack.
  
  	"Copy the arguments to the stack, and activate"
  	index := 1.
+ 	[index <= numArgs] whileTrue:
- 	[index <= numArgs]
- 		whileTrue:
  		[self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray).
  		index := index + 1].
  
- 	"Note we use activateNewMethod, not executeNewMethod, to avoid
- 	 quickCheckForInterrupts.  Don't check until we have a full activation."
  	self activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: true!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveFullClosureValue (in category 'control primitives') -----
+ primitiveFullClosureValue
+ 	<option: #SistaV1BytecodeSet>
+ 	| blockClosure numArgs closureMethod |
+ 	blockClosure := self stackValue: argumentCount.
+ 	numArgs := self argumentCountOfClosure: blockClosure.
+ 	argumentCount = numArgs ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	closureMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
+ 	(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	self activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: true!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveFullClosureValueNoContextSwitch (in category 'control primitives') -----
+ primitiveFullClosureValueNoContextSwitch
+ 	"An exact clone of primitiveFullClosureValue except that this version will not
+ 	 check for interrupts on stack overflow.  It may invoke the garbage collector
+ 	 but will not switch processes.  See checkForInterruptsMayContextSwitch:"
+ 	<api>
+ 	<option: #SistaV1BytecodeSet>
+ 	| blockClosure numArgs closureMethod |
+ 	blockClosure := self stackValue: argumentCount.
+ 	numArgs := self argumentCountOfClosure: blockClosure.
+ 	argumentCount = numArgs ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	closureMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
+ 	(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	self activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: false!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveFullClosureValueWithArgs (in category 'control primitives') -----
+ primitiveFullClosureValueWithArgs
+ 	<option: #SistaV1BytecodeSet>
+ 	| argumentArray arraySize blockClosure numArgs closureMethod index |
+ 	argumentArray := self stackTop.
+ 	(objectMemory isArray: argumentArray) ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	"Check for enough space in thisContext to push all args"
+ 	arraySize := objectMemory numSlotsOf: argumentArray.
+ 	(self roomToPushNArgs: arraySize) ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	blockClosure := self stackValue: argumentCount.
+ 	numArgs := self argumentCountOfClosure: blockClosure.
+ 	arraySize = numArgs ifFalse:
+ 		[^self primitiveFail].
+ 
+ 
+ 	closureMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
+ 	(objectMemory isOopCompiledMethod: closureMethod) ifFalse:
+ 		[^self primitiveFail].
+ 
+ 	self popStack.
+ 
+ 	"Copy the arguments to the stack, and activate"
+ 	index := 1.
+ 	[index <= numArgs] whileTrue:
+ 		[self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray).
+ 		index := index + 1].
+ 
+ 	self activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: true!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForNewspeakV4 (in category 'initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackInterpreter initializeBytecodeTableForNewspeakV4"
  	"Note: This table will be used to generate a C switch statement."
  
+ 	initializationOptions at: #NewsqueakV4BytecodeSet put: true.
+ 
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForNewsqueakV4.
  	LongStoreBytecode := 234.
  	self table: BytecodeTable from:
  	#(	"1 byte bytecodes"
  		(   0  15 pushReceiverVariableBytecode)
  		( 16  31 pushLiteralVariable16CasesBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  75 pushTemporaryVariableBytecode)
  		( 76	 pushReceiverBytecode)
  		( 77	 extPushPseudoVariableOrOuterBytecode)
  		( 78	 pushConstantZeroBytecode)
  		( 79	 pushConstantOneBytecode)
  
  		( 80	 bytecodePrimAdd)
  		( 81	 bytecodePrimSubtract)
  		( 82	 bytecodePrimLessThanV4) "for booleanCheatV4:"
  		( 83	 bytecodePrimGreaterThanV4) "for booleanCheatV4:"
  		( 84	 bytecodePrimLessOrEqualV4) "for booleanCheatV4:"
  		( 85	 bytecodePrimGreaterOrEqualV4) "for booleanCheatV4:"
  		( 86	 bytecodePrimEqualV4) "for booleanCheatV4:"
  		( 87	 bytecodePrimNotEqualV4) "for booleanCheatV4:"
  		( 88	 bytecodePrimMultiply)
  		( 89	 bytecodePrimDivide)
  		( 90	 bytecodePrimMod)
  		( 91	 bytecodePrimMakePoint)
  		( 92	 bytecodePrimBitShift)
  		( 93	 bytecodePrimDiv)
  		( 94	 bytecodePrimBitAnd)
  		( 95	 bytecodePrimBitOr)
  
  		( 96	 bytecodePrimAt)
  		( 97	 bytecodePrimAtPut)
  		( 98	 bytecodePrimSize)
  		( 99	 bytecodePrimNext)
  		(100	 bytecodePrimNextPut)
  		(101	 bytecodePrimAtEnd)
  		(102	 bytecodePrimIdenticalV4) "for booleanCheatV4:"
  		(103	 bytecodePrimClass)
  		(104	 bytecodePrimSpecialSelector24) "was blockCopy:"
  		(105	 bytecodePrimValue)
  		(106	 bytecodePrimValueWithArg)
  		(107	 bytecodePrimDo)
  		(108	 bytecodePrimNew)
  		(109	 bytecodePrimNewWithArg)
  		(110	 bytecodePrimPointX)
  		(111	 bytecodePrimPointY)
  
  		(112 127	sendLiteralSelector0ArgsBytecode)
  		(128 143	sendLiteralSelector1ArgBytecode)
  		(144 159	sendLiteralSelector2ArgsBytecode)
  		(160 175	sendAbsentImplicit0ArgsBytecode)
  
  		(176 183	storeAndPopReceiverVariableBytecode)
  		(184 191	storeAndPopTemporaryVariableBytecode)
  
  		(192 199	shortUnconditionalJump)
  		(200 207	shortConditionalJumpTrue)
  		(208 215	shortConditionalJumpFalse)
  
  		(216		returnReceiver)
  		(217		returnTopFromMethod)
  		(218		extReturnTopFromBlock)
  
  		(219		duplicateTopBytecode)
  		(220		popStackBytecode)
  		(221		extNopBytecode)
  		(222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		extPushIntegerBytecode)
  		(230		longPushTemporaryVariableBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extStoreReceiverVariableBytecode)
  		(233		extStoreLiteralVariableBytecode)
  		(234		longStoreTemporaryVariableBytecode)
  		(235		extStoreAndPopReceiverVariableBytecode)
  		(236		extStoreAndPopLiteralVariableBytecode)
  		(237		longStoreAndPopTemporaryVariableBytecode)
  
  		(238		extSendBytecode)
  		(239		extSendSuperBytecode)
  		(240		extSendAbsentImplicitBytecode)
  		(241		extSendAbsentDynamicSuperBytecode)
  
  		(242		extUnconditionalJump)
  		(243		extJumpIfTrue)
  		(244		extJumpIfFalse)
  
  		(245		extSendAbsentSelfBytecode)
  
  		(246 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(249		callPrimitiveBytecode)
  
  		(250		pushRemoteTempLongBytecode)
  		(251		storeRemoteTempLongBytecode)
  		(252		storeAndPopRemoteTempLongBytecode)
  		(253		extPushClosureBytecode)
  		(254		extSendAbsentOuterBytecode)
  
  		(255		unknownBytecode)
  	)!

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."
  
+ 	initializationOptions at: #SistaV1BytecodeSet put: true.
+ 
  	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)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extSistaStoreReceiverVariableBytecode)
  		(244		extSistaStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		unknownBytecode) "reserved for Push Float"
  
  		(250		extPushClosureBytecode)
  		(251		extPushRemoteTempOrInstVarLongBytecode)
  		(252		extStoreRemoteTempOrInstVarLongBytecode)
  		(253		extStoreAndPopRemoteTempOrInstVarLongBytecode)
  				
  		(254		extJumpIfNotInstanceOfBehaviorsOrPopBytecode)
  
  		(255		extPushFullClosureBytecode)
  	)!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackInterpreter initializeBytecodeTableForSqueakV3PlusClosures"
  	"Note: This table will be used to generate a C switch statement."
  
+ 	initializationOptions at: #SqueakV3PlusClosuresBytecodeSet put: true.
+ 
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForV3PlusClosures.
  	LongStoreBytecode := 129.
  	self table: BytecodeTable from:
  	#(
  		(  0  15 pushReceiverVariableBytecode)
  		( 16  31 pushTemporaryVariableBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  95 pushLiteralVariableBytecode)
  		( 96 103 storeAndPopReceiverVariableBytecode)
  		(104 111 storeAndPopTemporaryVariableBytecode)
  		(112 pushReceiverBytecode)
  		(113 pushConstantTrueBytecode)
  		(114 pushConstantFalseBytecode)
  		(115 pushConstantNilBytecode)
  		(116 pushConstantMinusOneBytecode)
  		(117 pushConstantZeroBytecode)
  		(118 pushConstantOneBytecode)
  		(119 pushConstantTwoBytecode)
  		(120 returnReceiver)
  		(121 returnTrue)
  		(122 returnFalse)
  		(123 returnNil)
  		(124 returnTopFromMethod)
  		(125 returnTopFromBlock)
  
  		(126 127 unknownBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  
  		(137 pushActiveContextBytecode)
  		(138 pushNewArrayBytecode)),
  
  	((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  		ifTrue: [#((139 callPrimitiveBytecode))]	"V3PlusClosures on Spur"
  		ifFalse: [#((139 unknownBytecode))]),	"V3PlusClosures on V3"
  
  	  #(
  		(140 pushRemoteTempLongBytecode)
  		(141 storeRemoteTempLongBytecode)
  		(142 storeAndPopRemoteTempLongBytecode)
  		(143 pushClosureCopyCopiedValuesBytecode)
  
  		(144 151 shortUnconditionalJump)
  		(152 159 shortConditionalJumpFalse)
  		(160 167 longUnconditionalJump)
  		(168 171 longJumpIfTrue)
  		(172 175 longJumpIfFalse)
  
  		"176-191 were sendArithmeticSelectorBytecode"
  		(176 bytecodePrimAdd)
  		(177 bytecodePrimSubtract)
  		(178 bytecodePrimLessThan)
  		(179 bytecodePrimGreaterThan)
  		(180 bytecodePrimLessOrEqual)
  		(181 bytecodePrimGreaterOrEqual)
  		(182 bytecodePrimEqual)
  		(183 bytecodePrimNotEqual)
  		(184 bytecodePrimMultiply)
  		(185 bytecodePrimDivide)
  		(186 bytecodePrimMod)
  		(187 bytecodePrimMakePoint)
  		(188 bytecodePrimBitShift)
  		(189 bytecodePrimDiv)
  		(190 bytecodePrimBitAnd)
  		(191 bytecodePrimBitOr)
  
  		"192-207 were sendCommonSelectorBytecode"
  		(192 bytecodePrimAt)
  		(193 bytecodePrimAtPut)
  		(194 bytecodePrimSize)
  		(195 bytecodePrimNext)
  		(196 bytecodePrimNextPut)
  		(197 bytecodePrimAtEnd)
  		(198 bytecodePrimIdentical)
  		(199 bytecodePrimClass)
  		(200 bytecodePrimSpecialSelector24)
  		(201 bytecodePrimValue)
  		(202 bytecodePrimValueWithArg)
  		(203 bytecodePrimDo)
  		(204 bytecodePrimNew)
  		(205 bytecodePrimNewWithArg)
  		(206 bytecodePrimPointX)
  		(207 bytecodePrimPointY)
  
  		(208 223 sendLiteralSelector0ArgsBytecode)
  		(224 239 sendLiteralSelector1ArgBytecode)
  		(240 255 sendLiteralSelector2ArgsBytecode)
  	)!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter>>activateNewClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod."
  	| numCopied outerContext theMethod closureIP |
  	<inline: true>
+ 	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
+ 	self assert: (objectMemory isContext: outerContext).
- 	outerContext := objectMemory followField: ClosureOuterContextIndex ofObject: blockClosure.
  	numCopied := self copiedValueCountOfClosure: blockClosure.
  
+ 	theMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
+ 	self assert: (objectMemory isOopCompiledMethod: theMethod).
- 	theMethod := objectMemory followField: MethodIndex ofObject: outerContext.
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: objectMemory nilObject. "FxThisContext field"
+ 	"Because inst var access is not checked, we must follow the receiver in Spur to ensure it is valid."
  	self push: (objectMemory followField: ReceiverIndex ofObject: outerContext).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + ClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
  	"The initial instructions in the block nil-out remaining temps."
  
  	"the instruction pointer is a pointer variable equal to 
  	method oop + ip + BaseHeaderSize 
  	-1 for 0-based addressing of fetchByte 
  	-1 because it gets incremented BEFORE fetching currentByte"
  	closureIP := self quickFetchInteger: ClosureStartPCIndex ofObject: blockClosure.
  	instructionPointer := theMethod + closureIP + objectMemory baseHeaderSize - 2.
  	self setMethod: theMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
  	stackPointer < stackLimit ifTrue:
  		[self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch]!

Item was changed:
  ----- Method: StackInterpreter>>activateNewFullClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod."
  	| numCopied outerContext theMethod methodHeader numTemps |
  	<inline: true>
  	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	numCopied := self copiedValueCountOfFullClosure: blockClosure.
+ 	theMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
+ 	self assert: (objectMemory isOopCompiledMethod: theMethod).
- 
- 	theMethod := objectMemory followField: FullClosureCompiledBlockIndex ofObject: blockClosure.
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: objectMemory nilObject. "FxThisContext field"
+ 	"Because inst var access is not checked, we must follow the receiver in Spur to ensure it is valid."
  	self push: (objectMemory followField: FullClosureReceiverIndex ofObject: blockClosure).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + FullClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
+ 	methodHeader := objectMemory methodHeaderOf: theMethod.
- 	methodHeader := objectMemory methodHeaderOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
+ 
- 	
  	numArgs + numCopied + 1 to: numTemps do: [ :i | self push: objectMemory nilObject].
  
+ 	instructionPointer := (self initialPCForHeader: methodHeader method: theMethod) - 1.
- 	instructionPointer := (self initialPCForHeader: methodHeader method: newMethod) - 1.
  	
  	self setMethod: theMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
  	stackPointer < stackLimit ifTrue:
  		[self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch]!

Item was changed:
  ----- Method: StackInterpreterSimulator>>endPCOf: (in category 'compiled methods') -----
  endPCOf: aMethod
  	"Determine the endPC of a method in the heap using interpretation that looks for returns."
  	
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	| pc end farthestContinuation prim encoderClass inst is |
  	(prim := self primitiveIndexOf: aMethod) > 0 ifTrue:
  		[(self isQuickPrimitiveIndex: prim) ifTrue:
  			[^(self startPCOfMethod: aMethod) - 1]].
  	encoderClass := self encoderClassForHeader: (objectMemory methodHeaderOf: aMethod).
  	is := (InstructionStream
  			on: (VMCompiledMethodProxy new
  					for: aMethod
  					coInterpreter: self
  					objectMemory: objectMemory)).
  	pc := farthestContinuation := self startPCOfMethod: aMethod.
  	end := objectMemory numBytesOf: aMethod.
  	is pc: pc + 1.
  	[pc <= end] whileTrue:
  		[inst := encoderClass interpretNextInstructionFor: MessageCatcher new in: is.
  		 inst selector
  			caseOf: {
  				 [#pushClosureCopyNumCopiedValues:numArgs:blockSize:]	
  											->	[is pc: is pc + inst arguments last.
  												 farthestContinuation := farthestContinuation max: pc].
  				 [#jump:]					->	[farthestContinuation := farthestContinuation max: pc + inst arguments first].
  				 [#jump:if:]					->	[farthestContinuation := farthestContinuation max: pc + inst arguments first].
  				 [#methodReturnConstant:]	->	[pc >= farthestContinuation ifTrue: [end := pc]].
  				 [#methodReturnReceiver]	->	[pc >= farthestContinuation ifTrue: [end := pc]].
+ 				 [#methodReturnTop]		->	[pc >= farthestContinuation ifTrue: [end := pc]].
+ 				"This is for CompiledBlock/FullBlockClosure.  Since the response to pushClosure... above
+ 				 skips over all block bytecoes, we will only see a blockReturnTop if it is at the top level,
+ 				 and so it must be a blockReturnTop in a CompiledBlock for a FullBlockClosure."
+ 				 [#blockReturnTop]			->	[pc >= farthestContinuation ifTrue: [end := pc]] }
- 				 [#methodReturnTop]		->	[pc >= farthestContinuation ifTrue: [end := pc]] }
  			otherwise: [].
  		 pc := is pc - 1].
  	^end!



More information about the Vm-dev mailing list