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

commits at source.squeak.org commits at source.squeak.org
Thu Jun 21 20:43:39 UTC 2012


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

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

Name: VMMaker.oscog-eem.163
Author: eem
Time: 21 June 2012, 1:41:16.462 pm
UUID: 886d6e40-a3f6-4483-bdfc-f71a846f0737
Ancestors: VMMaker.oscog-eem.162

Fix warning due to wakeHighestPriority changes.
Add abstractions for setting frame context and frame has context flag.
Set all unused StackInterpreter frame offsets to #undefined in CoInterpreter.
Fix asking to close the VM window twice.
Ask before nuking the transcript.

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

Item was changed:
  ----- Method: CoInterpreter class>>initializeFrameIndices (in category 'initialization') -----
  initializeFrameIndices
  	"Format of a stack frame.  Word-sized indices relative to the frame pointer.
  	 Terminology
  		Frames are either single (have no context) or married (have a context).
  		Contexts are either single (exist on the heap), married (have a context) or widowed (had a frame that has exited).
  	 Stacks grow down:
  
  			receiver for method activations/closure for block activations
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (initialized to nil)
  			frame flags (interpreter only)
  			saved method ip (initialized to 0; interpreter only)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  
  	In an interpreter frame
  		frame flags holds
  			the number of arguments (since argument temporaries are above the frame)
  			the flag for a block activation
  			and the flag indicating if the context field is valid (whether the frame is married).
  		saved method ip holds the saved method ip when the callee frame is a machine code frame.
  		This is because the saved method ip is actually the ceReturnToInterpreterTrampoline address.
  	In a machine code frame
  		the flag indicating if the context is valid is the least significant bit of the method pointer
  		the flag for a block activation is the next most significant bit of the method pointer
  
  	Interpreter frames are distinguished from method frames by the method field which will
  	be a pointer into the heap for an interpreter frame and a pointer into the method zone for
  	a machine code frame.
  
  	The first frame in a stack page is the baseFrame and is marked as such by a saved fp being its stackPage,
  	in which case the first word on the stack is the caller context (possibly hybrid) beneath the base frame."
  
  	| fxCallerSavedIP fxSavedFP fxMethod fxIFrameFlags fxThisContext fxIFReceiver fxMFReceiver fxIFSavedIP |
  	fxCallerSavedIP := 1.
  	fxSavedFP := 0.
  	fxMethod := -1.
  	fxThisContext := -2.
  	fxIFrameFlags := -3.	"Can find numArgs, needed for fast temp access. args are above fxCallerSavedIP.
  							 Can find ``is block'' bit
  							 Can find ``has context'' bit"
  	fxIFSavedIP := -4.
  	fxIFReceiver := -5.
  	fxMFReceiver := -3.
  
  	"For debugging nil out values that differ in the StackInterpreter."
+ 	FrameSlots := #undeclared asSymbol.
- 	FrameSlots := nil.
  	IFrameSlots := fxCallerSavedIP - fxIFReceiver + 1.
  	MFrameSlots := fxCallerSavedIP - fxMFReceiver + 1.
  
  	FoxCallerSavedIP := fxCallerSavedIP * BytesPerWord.
  	"In Cog a base frame's caller context is stored on the first word of the stack page."
+ 	FoxCallerContext := #undeclared asSymbol.
- 	FoxCallerContext := nil.
  	FoxSavedFP := fxSavedFP * BytesPerWord.
  	FoxMethod := fxMethod * BytesPerWord.
  	FoxThisContext := fxThisContext * BytesPerWord.
+ 	FoxFrameFlags := #undeclared asSymbol.
- 	FoxFrameFlags := nil.
  	FoxIFrameFlags := fxIFrameFlags * BytesPerWord.
  	FoxIFSavedIP := fxIFSavedIP * BytesPerWord.
  	FoxReceiver := #undeclared asSymbol.
  	FoxIFReceiver := fxIFReceiver * BytesPerWord.
  	FoxMFReceiver := fxMFReceiver * BytesPerWord.
  
  	"N.B.  There is room for one more flag given the current 8 byte alignment of methods (which
  	 is at least needed to distinguish the checked and uncecked entry points by their alignment."
  	MFMethodFlagHasContextFlag := 1.
  	MFMethodFlagIsBlockFlag := 2.
  	MFMethodFlagsMask := MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag.
  	MFMethodMask := (MFMethodFlagsMask + 1) negated!

Item was changed:
  ----- Method: CoInterpreter>>marryFrame:SP: (in category 'frame access') -----
  marryFrame: theFP SP: theSP
  	"Marry an unmarried frame.  This means creating a spouse context  initialized with
  	 a subset of the frame's state (state through the last argument) that references the
  	 frame. This is important enough for performance to be worth streamlining.
  
  	Override to set the ``has context'' flag appropriately for both machine code and interpreter frames
  	and to streamline the machine code/interpreter differences.."
  	| theContext methodFieldOrObj closureOrNil rcvr byteSize numArgs numStack |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: (self frameHasContext: theFP) not.
  	self assert: (self isBaseFrame: theFP) not. "base frames must aready be married for cannotReturn: processing"
  
  	"Decide how much of the stack to preserve in widowed contexts.  Preserving too much
  	 state will potentially hold onto garbage.  Holding onto too little may mean that a dead
  	 context isn't informative enough in a debugging situation.  We compromise, retaining
  	 only the arguments with no temporaries.  Note that we still set the stack pointer to its
  	 current value, but stack contents other than the arguments are nil."
  	methodFieldOrObj := self frameMethodField: theFP.
  	methodFieldOrObj asUnsignedInteger < objectMemory startOfMemory "inline (self isMachineCodeFrame: theFP)"
  		ifTrue:
  			[| cogMethod |
  			 stackPages
  				longAt: theFP + FoxMethod
  				put: methodFieldOrObj + MFMethodFlagHasContextFlag.
  			 cogMethod := self cCoerceSimple: (methodFieldOrObj bitAnd: MFMethodMask) to: #'CogMethod *'.
  			 numArgs := cogMethod cmNumArgs.
  			 cogMethod cmType = CMMethod
  				ifTrue:
  					[closureOrNil := objectMemory nilObject]
  				ifFalse:
  					[cogMethod := (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod.
  					 closureOrNil := self frameStackedReceiver: theFP numArgs: numArgs].
  			 byteSize := (cogMethod methodHeader bitAnd: LargeContextBit) ~= 0
  							ifTrue: [LargeContextSize]
  							ifFalse: [SmallContextSize].
  			 methodFieldOrObj := cogMethod methodObject.
  			 rcvr := self mframeReceiver: theFP.
  			 numStack := self stackPointerIndexForMFrame: theFP WithSP: theSP numArgs: numArgs]
  		ifFalse:
+ 			[self setIFrameHasContext: theFP.
- 			[stackPages byteAt: theFP + FoxIFrameFlags + 2 put: 1.
  			 numArgs := self iframeNumArgs: theFP.
  			 byteSize := ((self headerOf: methodFieldOrObj) bitAnd: LargeContextBit) ~= 0
  							ifTrue: [LargeContextSize]
  							ifFalse: [SmallContextSize].
  			 closureOrNil := (self iframeIsBlockActivation: theFP)
  								ifTrue: [self frameStackedReceiver: theFP numArgs: numArgs]
  								ifFalse: [objectMemory nilObject].
  			 rcvr := self iframeReceiver: theFP.
  			 numStack := self stackPointerIndexForIFrame: theFP WithSP: theSP numArgs: numArgs].
  	theContext := objectMemory eeInstantiateMethodContextByteSize: byteSize.
+ 	self setFrameContext: theFP to: theContext.
- 	stackPages longAt: theFP + FoxThisContext put: theContext.
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity)"
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: theFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: (self frameCallerFP: theFP)).
  	objectMemory storePointerUnchecked: StackPointerIndex
  		ofObject: theContext
  		withValue: (objectMemory integerObjectOf: numStack).
  	objectMemory storePointerUnchecked: MethodIndex
  		ofObject: theContext
  		withValue: methodFieldOrObj.
  	objectMemory storePointerUnchecked: ClosureIndex ofObject: theContext withValue: closureOrNil.
  	objectMemory storePointerUnchecked: ReceiverIndex
  		ofObject: theContext
  		withValue: rcvr.
  	1 to: numArgs do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext
  			withValue: (self temporary: i - 1 in: theFP)].
  	numArgs + 1 to: numStack do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext
  			withValue: objectMemory nilObject].
  
  	self assert: (self frameHasContext: theFP).
  	self assert: (self frameOfMarriedContext: theContext) = theFP.
  	self assert: numStack + ReceiverIndex < (objectMemory lengthOf: theContext).
  
  	^theContext!

Item was added:
+ ----- Method: CoInterpreter>>setIFrameHasContext: (in category 'frame access') -----
+ setIFrameHasContext: theFP
+ 	"See encodeFrameFieldHasContext:numArgs:"
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	stackPages byteAt: theFP + FoxIFrameFlags + 2 put: 1!

Item was changed:
  ----- Method: CogVMSimulator>>run (in category 'testing') -----
  run
  	"Just run"
+ 	quitBlock := [| topWindow |
+ 				  
+ 				   (displayView notNil
+ 				   and: [topWindow := displayView outermostMorphThat:
+ 									[:m| m isSystemWindow and: [World submorphs includes: m]].
+ 						topWindow notNil
+ 				   and: [UIManager default confirm: 'close?']]) ifTrue:
+ 					[topWindow delete].
- 	quitBlock := [(displayView notNil
- 				   and: [UIManager default confirm: 'close?']) ifTrue:
- 					[(displayView outermostMorphThat: [:m| m isSystemWindow]) ifNotNil:
- 						[:topWindow| topWindow delete]].
  				  ^self].
  	self initStackPages.
  	self loadInitialContext.
  	self initialEnterSmalltalkExecutive!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFileStdioHandlesInto: (in category 'simulation') -----
  sqFileStdioHandlesInto: anArray
+ 	(interpreterProxy transcript ~~ Transcript
+ 	 or: [UIManager default confirm: 'clear transcript?']) ifTrue:
+ 		[interpreterProxy transcript clear].
- 	interpreterProxy transcript clear.
  	"See FilePluginSimulator>>initialiseModule"
  	anArray
  		at: 1 put: 0;
  		at: 2 put: 1;
  		at: 3 put: 2.
  	^7!

Item was changed:
  ----- Method: StackInterpreter>>marryFrame:SP: (in category 'frame access') -----
  marryFrame: theFP SP: theSP
  	"Marry an unmarried frame.  This means creating a spouse context
  	 initialized with a subset of the frame's state (state through the last argument)
  	 that references the frame."
  	| theContext methodHeader byteSize numArgs numStack closureOrNil |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	self assert: (self frameHasContext: theFP) not.
  
  	methodHeader := self headerOf: (self frameMethod: theFP).
  	"Decide how much of the stack to preserve in widowed contexts.  Preserving too much
  	 state will potentially hold onto garbage.  Holding onto too little may mean that a dead
  	 context isn't informative enough in a debugging situation.  We compromise, retaining
  	 only the arguments with no temporaries.  Note that we still set the stack pointer to its
  	 current value, but stack contents other than the arguments are nil."
  	numArgs := self frameNumArgs: theFP.
  	numStack := self stackPointerIndexForFrame: theFP WithSP: theSP.
  
  	closureOrNil := (self frameIsBlockActivation: theFP)
  						ifTrue: [self pushedReceiverOrClosureOfFrame: theFP]
  						ifFalse: [objectMemory nilObject].
  
  	byteSize := (methodHeader bitAnd: LargeContextBit) ~= 0
  					ifTrue: [LargeContextSize]
  					ifFalse: [SmallContextSize].
  	theContext := objectMemory eeInstantiateMethodContextByteSize: byteSize.
  	self assert: numStack + ReceiverIndex << ShiftForWord + BaseHeaderSize <= byteSize. 
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity)"
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: theFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: (self frameCallerFP: theFP)).
  	objectMemory storePointerUnchecked: StackPointerIndex
  		ofObject: theContext
  		withValue: (objectMemory integerObjectOf: numStack).
  	objectMemory storePointerUnchecked: MethodIndex
  		ofObject: theContext
  		withValue: (self frameMethod: theFP).
  	objectMemory storePointerUnchecked: ClosureIndex ofObject: theContext withValue: closureOrNil.
  	objectMemory storePointerUnchecked: ReceiverIndex
  		ofObject: theContext
  		withValue: (self frameReceiver: theFP).
  	"Store just the arguments.  If the frame is divorced the context
  	 will have valid arguments but all temporaries will be nil."
  	1 to: numArgs do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext "inline self temporary: i - 1 in:theFP" 
  			withValue: (stackPages longAt: theFP
  										+ FoxCallerSavedIP
  										+ ((numArgs - i + 1) * BytesPerWord))].
  	numArgs + 1 to: numStack do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext
  			withValue: objectMemory nilObject].
  
+ 	self setFrameContext: theFP to: theContext.
+ 	self setFrameHasContext: theFP.
- 	stackPages longAt: theFP + FoxThisContext put: theContext.
- 	stackPages byteAt: theFP + FoxFrameFlags + 2 put: 1.
  
  	self assert: (self frameHasContext: theFP).
  	self assert: (self frameOfMarriedContext: theContext) = theFP.
  	self assert: numStack + ReceiverIndex < (objectMemory lengthOf: theContext).
  
  	^theContext
  !

Item was added:
+ ----- Method: StackInterpreter>>setFrameContext:to: (in category 'frame access') -----
+ setFrameContext: theFP to: aContext
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	stackPages longAt: theFP + FoxThisContext put: aContext!

Item was added:
+ ----- Method: StackInterpreter>>setFrameHasContext: (in category 'frame access') -----
+ setFrameHasContext: theFP
+ 	"See encodeFrameFieldHasContext:numArgs:"
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	stackPages byteAt: theFP + FoxFrameFlags + 2 put: 1!

Item was changed:
  ----- Method: StackInterpreter>>wakeHighestPriority (in category 'process primitive support') -----
  wakeHighestPriority
  	"Return the highest priority process that is ready to run.
  	 To save time looking at many empty lists before finding a
  	 runnable process the VM maintains a variable holding the
  	 highest priority runnable process.  If this variable is 0 then the
  	 VM does not know the highest priority and must search all lists.
  	 Note: It is a fatal VM error if there is no runnable process."
  	| schedLists p processList proc ctxt |
+ 	self externalWriteBackHeadFramePointers.
  	schedLists := objectMemory fetchPointer: ProcessListsIndex ofObject: self schedulerPointer.
  	p := highestRunnableProcessPriority = 0
  			ifTrue: [objectMemory fetchWordLengthOf: schedLists]
  			ifFalse: [highestRunnableProcessPriority].
  	[(p := p - 1) >= 0] whileTrue:
  		[processList := objectMemory fetchPointer: p ofObject: schedLists.
  	 	 [self isEmptyList: processList] whileFalse:
  			["Only answer processes with a runnable suspendedContext.
  			  Discard those that aren't; the VM would crash otherwise."
  			 proc := self removeFirstLinkOfList: processList.
  			 ctxt := objectMemory fetchPointer: SuspendedContextIndex ofObject: proc.
  			 (self isLiveContext: ctxt) ifTrue:
  				[highestRunnableProcessPriority := p + 1.
  				^proc].
  			 self warning: 'evicted zombie process from run queue']].
  	self error: 'scheduler could not find a runnable process'.
  	^nil!



More information about the Vm-dev mailing list