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

commits at source.squeak.org commits at source.squeak.org
Thu Oct 29 18:50:45 UTC 2020


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

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

Name: VMMaker.oscog-eem.2861
Author: eem
Time: 29 October 2020, 11:50:34.437951 am
UUID: fe74d94b-c82c-47d0-8e6d-f2ac85eda597
Ancestors: VMMaker.oscog-eem.2860

Cog: Eliminate ceEnterInterpreterOnReturnFromCogCode and have the ceReturnToInterpreterTrampoline invoke interpret directly, using the same code as ceInvokeInterpret.  Do this by moving the setMethod: send into interpret from senders; setMethod: is key because it sets the bytecodeSetSelector to enable multiple bytecode set support, but machine code is (and should remain) ignorant of the details of bytecode set selection in compiled method headers.

Simulation:
Eliminate teh simulator versions of interpret (too easy to get out of sync with the real versions).  Do this by providing stubs for breakpointing and inctrementing of the bytecode count, in the real VMs and have these stubs implemented in teh simulators as they were in their own interpret imlementations.

Sista: fix a pseeling rorre.

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

Item was added:
+ ----- Method: CoInterpreter>>aboutToDispatchBytecode (in category 'interpreter shell') -----
+ aboutToDispatchBytecode
+ 	"This is a hook for the simulator; null in production"
+ 	<inline: #always>!

Item was removed:
- ----- Method: CoInterpreter>>ceEnterInterpreterOnReturnFromCogCode (in category 'trampolines') -----
- ceEnterInterpreterOnReturnFromCogCode
- 	"Perform a return from a machine code frame to an interpreted frame.
- 	 The machine code has executed a return instruction when the return address
- 	 is set to ceReturnToInterpreterPC.  Push the result and call interpret."
- 	<api>
- 	self assert: (objectMemory addressCouldBeOop: self stackTop).
- 	self deny: (self isMachineCodeFrame: framePointer).
- 	self setMethod: (self iframeMethod: framePointer).
- 	instructionPointer := self iframeSavedIP: framePointer.
- 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
- 	cogit ceInvokeInterpret.
- 	"NOTREACHED"
- 	^nil!

Item was changed:
  ----- Method: CoInterpreter>>enterSmalltalkExecutiveImplementation (in category 'initialization') -----
  enterSmalltalkExecutiveImplementation
  	"Main entry-point into the interpreter at each execution level, where an execution
  	 level is either the start of execution or reentry for a callback.  Capture the C stack
  	 pointers so that calls from machine-code into the C run-time occur at this level.
  	 This is the actual implementation, separated from enterSmalltalkExecutive so the
  	 simulator can wrap it in an exception handler and hence simulate the setjmp/longjmp."
  	<inline: false>
  	cogit assertCStackWellAligned.
  	cogit ceCaptureCStackPointers.
  	(self isMachineCodeFrame: framePointer) ifTrue:
  		[self returnToExecutive: false postContextSwitch: true
  		 "NOTREACHED"].
- 	self setMethod: (self iframeMethod: framePointer).
- 	instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
- 		[instructionPointer := self iframeSavedIP: framePointer].
- 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	self interpret.
  	^0!

Item was changed:
  ----- Method: CoInterpreter>>interpret (in category 'interpreter shell') -----
  interpret
  	"This is the main interpreter loop.
  	 In a pure interpreter it loops forever, fetching and executing bytecodes.
  	 With the Cogit JIT executing code as well, the interpreter is reentered from machine code
  	 whenever the machine code wants to interpret a method instead of executing its machine
  	 code.  Entry into the interpreter is done via a ''jump call'' in machine code that uses
  	 CFramePointer and CStackPointer to find the base of the C stack (set in CoInterpreter>>
  	 enterSmalltalkExecutiveImplementation) and substitutes CReturnAddress as the return
  	 address in the code so it always appears that interpret has been called from
  	 CoInterpreter>>enterSmalltalkExecutiveImplementation, which may be important to,
  	 for example, C exception handling inside the VM.
  
  	 When running in the context of a browser plugin VM the interpreter must return control
  	 to the browser periodically. This should done only when the state of the currently running
  	 Squeak thread is safely stored in the object heap. Since this is the case at the moment
  	 that a check for interrupts is performed, that is when we return to the browser if it is time
  	 to do so. Interrupt checks happen quite frequently."
  
  	<inline: false>
  	"If stacklimit is zero then the stack pages have not been initialized."
  	stackLimit = 0 ifTrue:
  		[^self initStackPagesAndInterpret].
  	"An unchecked write is probably faster, so instead of
  	 CReturnAddress ifNil:
  		[CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t]
  	 we have simply"
  	self assert: (CReturnAddress isNil or: [CReturnAddress = (self cCoerceSimple: self getReturnAddress to: #usqIntptr_t)]).
  	CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t.
+ 
+ 	self useCogitBreakBlockIfNone.
  	"record entry time when running as a browser plug-in"
  	self browserPluginInitialiseIfNeeded.
+ 	self setMethod: (self iframeMethod: framePointer).
+ 	self deny: instructionPointer = cogit ceReturnToInterpreterPC.
+ 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	self internalizeIPandSP.
  	self initExtensions.
  	self fetchNextBytecode.
+ 	[true] whileTrue:
+ 		[self aboutToDispatchBytecode.
+ 		 self dispatchOn: currentBytecode in: BytecodeTable].
- 	[true] whileTrue: [self dispatchOn: currentBytecode in: BytecodeTable].
  	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
  	self externalizeIPandSP.
  	^nil!

Item was added:
+ ----- Method: CoInterpreter>>useCogitBreakBlockIfNone (in category 'interpreter shell') -----
+ useCogitBreakBlockIfNone
+ 	"This is a hook for the simulator; null in production"
+ 	<inline: #always>!

Item was added:
+ ----- Method: CogVMSimulator>>aboutToDispatchBytecode (in category 'interpreter shell') -----
+ aboutToDispatchBytecode
+ 	self incrementByteCount.
+ 	self assertValidExecutionPointers.
+ 	atEachStepBlock value "N.B. may be nil"!

Item was removed:
- ----- Method: CogVMSimulator>>interpret (in category 'interpreter shell') -----
- interpret
- 	"This is the main interpreter loop. It normally loops forever, fetching and executing bytecodes.
- 	 When running in the context of a web browser plugin VM, however, it must return control to the
- 	 web browser periodically. This should done only when the state of the currently running Squeak
- 	 thread is safely stored in the object heap. Since this is the case at the moment that a check for
- 	 interrupts is performed, that is when we return to the browser if it is time to do so.  Interrupt
- 	 checks happen quite frequently.
- 
- 	Override for simulation to insert bytecode breakpoint support."
- 
- 	"If stacklimit is zero then the stack pages have not been initialized."
- 	stackLimit = 0 ifTrue:
- 		[^self initStackPagesAndInterpret].
- 
- 	"An unchecked write is probably faster, so instead of
- 	 CReturnAddress ifNil:
- 		[CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t]
- 	 we have simply"
- 	self assert: (CReturnAddress isNil or: [CReturnAddress = self getReturnAddress]).
- 	CReturnAddress := self cCoerceSimple: self getReturnAddress to: #usqIntptr_t.
- 
- 	self useCogitBreakBlockIfNone.
- 	"record entry time when running as a browser plug-in"
- 	self browserPluginInitialiseIfNeeded.
- 	self internalizeIPandSP.
- 	self initExtensions.
- 	self fetchNextBytecode.
- 	[true] whileTrue:
- 		[self assertValidExecutionPointers.
- 		 atEachStepBlock value. "N.B. may be nil"
- 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self incrementByteCount].
- 	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
- 	self externalizeIPandSP.
- 	^nil
- !

Item was changed:
  ----- Method: Cogit>>genReturnToInterpreterTrampoline (in category 'initialization') -----
  genReturnToInterpreterTrampoline
+ 	| startAddress |
+ 	<inline: false>
+ 	startAddress := methodZoneBase.
  	self zeroOpcodeIndex.
+ 	"Push the result, set the instruction pointer to the interpreter frame's saved ip,
+ 	 set the method and the bytecode set offset, then call interpret."
- 	"Set the instruction pointer to the interpreter frame's saved ip, set the method and the bytecode set offset,
- 	 then call interpret."
  	self PushR: ReceiverResultReg. "The result"
+ 	"Assign the iframeSavedIP to instructionPointer"
+ 	self MoveMw: FoxIFSavedIP r: FPReg R: TempReg.
+ 	self MoveR: TempReg Aw: coInterpreter instructionPointerAddress.
+ 	self genSmalltalkToCStackSwitch: false "pushLinkReg".
+ 	cFramePointerInUse
+ 		ifTrue: [backEnd genLoadCStackPointers]
+ 		ifFalse: [backEnd genLoadCStackPointer].
+ 	"Sideways call interpret so that the stack looks correct, for exception handling etc"
+ 	backEnd genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[self MoveAw: coInterpreter cReturnAddressAddress R: LinkReg]
+ 		ifFalse:
+ 			[self MoveAw: coInterpreter cReturnAddressAddress R: ABIResultReg.
+ 			 backEnd genSubstituteReturnAddressR: ABIResultReg].
+ 	self JumpFullRT: (self
+ 						cCode: [#interpret asUnsignedInteger]
+ 						inSmalltalk: [self simulatedTrampolineFor: #interpret]).
+ 	self outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	self recordGeneratedRunTime: 'ceReturnToInterpreterTrampoline' address: startAddress.
+ 	^self cCoerceSimple: startAddress to: #'void (*)(void)'!
- 	^self genTrampolineFor: #ceEnterInterpreterOnReturnFromCogCode
- 		called: 'ceEnterInterpreterOnReturnFromCogCode'
- 		numArgs: 0 arg: nil arg: nil arg: nil arg: nil
- 		regsToSave: self emptyRegisterMask
- 		pushLinkReg: false
- 		resultReg: NoReg
- 		appendOpcodes: true!

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: (SistaV1BytecodeSet := true).
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForSistaV1.
  	BytecodeSetHasDirectedSuperSend := true.
  	BytecodeSetHasExtensions := true.
  	LongStoreBytecode := 245.
  	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	 bytecodePrimNotIdenticalSistaV1) "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		unconditionalTrapBytecode)
- 		(217		unconditionnalTrapBytecode)
  
  		(218 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(224		extABytecode)
  		(225		extBBytecode)
  
  		(226		extPushReceiverVariableBytecode)
  		(227		extPushLiteralVariableBytecode)
  		(228		extPushLiteralBytecode)
  		(229		longPushTemporaryVariableBytecode)
  		(230		unknownBytecode)
  		(231		pushNewArrayBytecode)
  		(232		extPushIntegerBytecode)
  		(233		extPushCharacterBytecode)
  
  		(234		extSendBytecode)
  		(235		extSendSuperBytecode)
  
  		(236		callMappedInlinedPrimitive)
  
  		(237		extUnconditionalJump)
  		(238		extJumpIfTrue)
  		(239		extJumpIfFalse)
  
  		(240		extStoreAndPopReceiverVariableBytecode)
  		(241		extStoreAndPopLiteralVariableBytecode)
  		(242		longStoreAndPopTemporaryVariableBytecode)
  
  		(243		extStoreReceiverVariableBytecode)
  		(244		extStoreLiteralVariableBytecode)
  		(245		longStoreTemporaryVariableBytecode)
  
  		(246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(248		callPrimitiveBytecode)
  		(249		extPushFullClosureBytecode)
  
  		(250		extPushClosureBytecode)
  		(251		pushRemoteTempLongBytecode)
  		(252		storeRemoteTempLongBytecode)
  		(253		storeAndPopRemoteTempLongBytecode)
  				
  		(254 255	unknownBytecode)
  	)!

Item was added:
+ ----- Method: StackInterpreter>>aboutToDispatchBytecode (in category 'interpreter shell') -----
+ aboutToDispatchBytecode
+ 	"This is a hook for the simulator; null in production"
+ 	<inline: #always>!

Item was changed:
  ----- Method: StackInterpreter>>enterSmalltalkExecutiveImplementation (in category 'initialization') -----
  enterSmalltalkExecutiveImplementation
  	"Main entry-point into the interpreter at each execution level, where an execution
  	 level is either the start of execution or reentry for a callback.
  	 This is the actual implementation, separated from enterSmalltalkExecutive so the
  	 simulator can wrap it in an exception handler and hence simulate the setjmp/longjmp."
  	<inline: false>
  	"Setjmp for reentry into interpreter from elsewhere, e.g. FFI exception primitive failure."
  	self _setjmp: reenterInterpreter.
- 	self setMethod: (self frameMethod: framePointer).
- 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	self interpret.
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>interpret (in category 'interpreter shell') -----
  interpret
  	"This is the main interpreter loop. It normally loops forever, fetching and executing bytecodes. When running in the context of a browser plugin VM, however, it must return control to the browser periodically. This should done only when the state of the currently running Squeak thread is safely stored in the object heap. Since this is the case at the moment that a check for interrupts is performed, that is when we return to the browser if it is time to do so. Interrupt checks happen quite frequently."
  
  	<inline: false>
  	"If stacklimit is zero then the stack pages have not been initialized."
  	stackLimit = 0 ifTrue:
  		[^self initStackPagesAndInterpret].
  	"record entry time when running as a browser plug-in"
  	self browserPluginInitialiseIfNeeded.
+ 	self setMethod: (self frameMethod: framePointer).
+ 	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: #'__LINE__'.
  	self internalizeIPandSP.
  	self initExtensions.
  	self fetchNextBytecode.
+ 	[true] whileTrue:
+ 		[self aboutToDispatchBytecode.
+ 		 self dispatchOn: currentBytecode in: BytecodeTable].
- 	[true] whileTrue: [self dispatchOn: currentBytecode in: BytecodeTable].
  	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
  	self externalizeIPandSP.
+ 	^nil!
- 	^nil
- !

Item was changed:
  ----- Method: StackInterpreter>>respondToSistaTrap (in category 'sista bytecodes') -----
  respondToSistaTrap
  	| ourContext |
+ 	<sharedCodeInCase: #unconditionalTrapBytecode>
- 	<sharedCodeInCase: #unconditionnalTrapBytecode>
  	messageSelector := objectMemory splObj: SelectorSistaTrap.
  	ourContext := self ensureFrameIsMarried: localFP SP: localSP.
  	self internalPush: ourContext.
  	argumentCount := 0.
  	self normalSend!

Item was added:
+ ----- Method: StackInterpreter>>unconditionalTrapBytecode (in category 'sista bytecodes') -----
+ unconditionalTrapBytecode
+ 	"SistaV1: *	217	Trap"
+ 	SistaVM 
+ 		ifTrue: [^self respondToSistaTrap]
+ 		ifFalse: [^self respondToUnknownBytecode]!

Item was removed:
- ----- Method: StackInterpreter>>unconditionnalTrapBytecode (in category 'sista bytecodes') -----
- unconditionnalTrapBytecode
- 	"SistaV1: *	217	Trap"
- 	SistaVM 
- 		ifTrue: [^self respondToSistaTrap]
- 		ifFalse: [^self respondToUnknownBytecode]!

Item was added:
+ ----- Method: StackInterpreterSimulator>>aboutToDispatchBytecode (in category 'interpreter shell') -----
+ aboutToDispatchBytecode
+ 	self incrementByteCount.
+ 	self assertValidExecutionPointers.
+ 	atEachStepBlock value "N.B. may be nil"!

Item was removed:
- ----- Method: StackInterpreterSimulator>>interpret (in category 'interpreter shell') -----
- interpret
- 	"This is the main interpreter loop. It normally loops forever, fetching and executing bytecodes.
- 	 When running in the context of a web browser plugin VM, however, it must return control to the
- 	 web browser periodically. This should done only when the state of the currently running Squeak
- 	 thread is safely stored in the object heap. Since this is the case at the moment that a check for
- 	 interrupts is performed, that is when we return to the browser if it is time to do so.  Interrupt
- 	 checks happen quite frequently.
- 
- 	Override for simulation to insert bytecode breakpoint support."
- 
- 	<inline: false>
- 	"If stacklimit is zero then the stack pages have not been initialized."
- 	stackLimit = 0 ifTrue:
- 		[^self initStackPagesAndInterpret].
- 	"record entry time when running as a browser plug-in"
- 	self browserPluginInitialiseIfNeeded.
- 	self internalizeIPandSP.
- 	self initExtensions.
- 	self fetchNextBytecode.
- 	[true] whileTrue:
- 		[self assertValidExecutionPointers.
- 		 atEachStepBlock value. "N.B. may be nil"
- 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self incrementByteCount].
- 	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
- 	self externalizeIPandSP.
- 	^nil!



More information about the Vm-dev mailing list