[Vm-dev] Making a Slower VM

tim Rowledge tim at rowledge.org
Mon Feb 10 20:33:17 UTC 2014


On 10-02-2014, at 11:53 AM, Eliot Miranda <eliot.miranda at gmail.com> wrote:
> 
> I *think* the issue is the internal/external split brought abut by the introduction of the localFoo variables, such as localSP and localIP. 

It’s really hard to be sure but I suspect that this isn’t the (only) issue. IIRC we used to be able to make non-inlined VMs at one point and that was well after the internalFoo code was added.

OK, some quick email searching reveals some work done in ’03 by johnMcI, Craig & me. 
Craig found the following code helped -

!'From Squeak3.6alpha of ''17 March 2003'' [latest update: #5325] on 21 July 2003 at 1:11:25 pm'!

!Interpreter methodsFor: 'contexts' stamp: 'crl 7/19/2003 15:59'!
primitiveFindNextUnwindContext
	"Primitive. Search up the context stack for the next method context marked for unwind handling from the receiver up to but not including the argument. Return nil if none found."
	| thisCntx nilOop aContext isUnwindMarked header meth pIndex |
	aContext _ self popStack.
	thisCntx _ self fetchPointer: SenderIndex ofObject: self popStack.
	nilOop _ nilObj.

	[(thisCntx = aContext) or: [thisCntx = nilOop]] whileFalse: [

	header _ self baseHeader: aContext.

	(self isMethodContextHeader: header)
		ifTrue: [
			meth _ self fetchPointer: MethodIndex ofObject: aContext.
			pIndex _ self primitiveIndexOf: meth.
			isUnwindMarked _ pIndex == 198]
		ifFalse: [isUnwindMarked _ false].
		isUnwindMarked ifTrue:[
			self push: thisCntx.
			^nil].
		thisCntx _ self fetchPointer: SenderIndex ofObject: thisCntx].

	^self push: nilOop! !

!Interpreter methodsFor: 'interpreter shell' stamp: 'crl 7/19/2003 15:33'!
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."

	"record entry time when running as a browser plug-in"
	"self browserPluginInitialiseIfNeeded"
	self internalizeIPandSP.
	self fetchNextBytecode.
	[true] whileTrue: [self dispatchOn: currentBytecode in: BytecodeTable].
	localIP _ localIP - 1.  "undo the pre-increment of IP before returning"
	self externalizeIPandSP.
! !

!Interpreter methodsFor: 'return bytecodes' stamp: 'crl 7/19/2003 16:05'!
returnValueTo
	"Note: Assumed to be inlined into the dispatch loop."

	| nilOop thisCntx contextOfCaller localCntx localVal isUnwindMarked header meth pIndex |
	self inline: true.
	self sharedCodeNamed: 'commonReturn' inCase: 120.

	nilOop _ nilObj. "keep in a register"
	thisCntx _ activeContext.
	localCntx _ cntx.
	localVal _ val.

	"make sure we can return to the given context"
	((localCntx = nilOop) or:
	 [(self fetchPointer: InstructionPointerIndex ofObject: localCntx) = nilOop]) ifTrue: [
		"error: sender's instruction pointer or context is nil; cannot return"
		^self internalCannotReturn: localVal].

	"If this return is not to our immediate predecessor (i.e. from a method to its sender, or from a block to its caller), scan the stack for the first unwind marked context and inform this context and let it deal with it. This provides a chance for ensure unwinding to occur."
	thisCntx _ self fetchPointer: SenderIndex ofObject: activeContext.

	"Just possibly a faster test would be to compare the homeContext and activeContext - they are of course different for blocks. Thus we might be able to optimise a touch by having a different returnTo for the blockreteurn (since we know that must return to caller) and then if active ~= home we must be doing a non-local return. I think. Maybe."
	[thisCntx = localCntx] whileFalse: [
		thisCntx = nilObj ifTrue:[
			"error: sender's instruction pointer or context is nil; cannot return"
			^self internalCannotReturn: localVal].
		"Climb up stack towards localCntx. Break out to a send of #aboutToReturn:through: if an unwind marked context is found"
	header _ self baseHeader: thisCntx.

	(self isMethodContextHeader: header)
		ifTrue: [
			meth _ self fetchPointer: MethodIndex ofObject: thisCntx.
			pIndex _ self primitiveIndexOf: meth.
			isUnwindMarked _ pIndex == 198]
		ifFalse: [isUnwindMarked _ false].

		isUnwindMarked ifTrue:[
			"context is marked; break out"
			^self internalAboutToReturn: localVal through: thisCntx].
		thisCntx _ self fetchPointer: SenderIndex ofObject: thisCntx.
].

	"If we get here there is no unwind to worry about. Simply terminate the stack up to the localCntx - often just the sender of the method"
	thisCntx _ activeContext.
	[thisCntx = localCntx]
		whileFalse:
		["climb up stack to localCntx"
		contextOfCaller _ self fetchPointer: SenderIndex ofObject: thisCntx.

		"zap exited contexts so any future attempted use will be caught"
		self storePointerUnchecked: SenderIndex ofObject: thisCntx withValue: nilOop.
		self storePointerUnchecked: InstructionPointerIndex ofObject: thisCntx withValue: nilOop.
		reclaimableContextCount > 0 ifTrue:
			["try to recycle this context"
			reclaimableContextCount _ reclaimableContextCount - 1.
			self recycleContextIfPossible: thisCntx].
		thisCntx _ contextOfCaller].

	activeContext _ thisCntx.
	(thisCntx < youngStart) ifTrue: [ self beRootIfOld: thisCntx ].

	self internalFetchContextRegisters: thisCntx.  "updates local IP and SP"
	self fetchNextBytecode.
	self internalPush: localVal.
! !

Shortly after that I released the VMMaker3.6 with a note that it couldn’t produce a completely non-inlined VM because of a problem in fetchByte if globalstruct was enabled, and some odd problems in B2DPlugin. When VMMaker3.7 was released a year late (march 04) I apparently thought it could make the core vm non-inlined. Since this is all a bazillion years ago I can’t remember any context to help extend the history.

tim
--
tim Rowledge; tim at rowledge.org; http://www.rowledge.org/tim
Science is imagination equipped with grappling hooks.



More information about the Vm-dev mailing list