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

commits at source.squeak.org commits at source.squeak.org
Tue Jun 26 02:54:30 UTC 2012


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

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

Name: VMMaker.oscog-eem.171
Author: eem
Time: 25 June 2012, 7:52:11.789 pm
UUID: c7fe70ad-ea30-4ba0-9645-a4060894480e
Ancestors: VMMaker.oscog-eem.170

Fix super expansions once again.  Eliding the final return is ok, but
it means ReturnNode needs to add it back in.  Further, AssignmentNode
would need to do something special for super expansions with
returns at other than the last statement, so raise an error if seen.

Move add of bytecodeSetSelector to fetchNextBytecode from
interpret so that e.g. dispatch in sqGnu.h doesn't have to duplicate
offset by bytecodeSetSelector.

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

Item was added:
+ ----- Method: AssignmentNode>>anyReturns: (in category '*VMMaker-C translation') -----
+ anyReturns: aSequenceOfNodes
+ 	aSequenceOfNodes do:
+ 		[:node|
+ 		node nodesDo:
+ 			[:n|
+ 			n isReturn ifTrue:
+ 				[^true]]].
+ 	^false!

Item was changed:
  ----- Method: AssignmentNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"make a CCodeGenerator equivalent of me"
  	| varNode valueNode |
  	varNode := variable asTranslatorNodeIn: aTMethod.
  	valueNode := value asTranslatorNodeIn: aTMethod.
  	valueNode isStmtList ifFalse:
  		[^TAssignmentNode new
  			setVariable: varNode
  			expression: valueNode;
  			comment: comment].
+ 	 "This is a super expansion.  We are in trouble if any statement other than the last is a return."
+ 	(self anyReturns: valueNode statements allButLast) ifTrue:
+ 		[self error: 'haven''t implemented pushing down assignments into other than the last return'].
+ 	"As of 6/25/2012 19:30 superExpansionNodeFor:args: elides the final return."
+ 	self assert: valueNode statements last isReturn not.
  	^TStmtListNode new
  		setStatements: valueNode statements allButLast,
  					{ TAssignmentNode new
  						setVariable: varNode
  						expression: valueNode statements last;
  						comment: comment };
  		yourself!

Item was changed:
  ----- Method: CoInterpreter>>baseFrameReturn (in category 'return bytecodes') -----
  baseFrameReturn
+ 	<inline: true>
  	| contextToReturnTo retToContext theFP theSP thePage newPage frameAbove |
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #newPage type: #'StackPage *'>
  	<var: #frameAbove type: #'char *'>
  	contextToReturnTo := self frameCallerContext: localFP.
  
  	"The stack page is effectively free now, so free it.  We must free it to be
  	 correct in determining if contextToReturnTo is still married, and in case
  	 makeBaseFrameFor: cogs a method, which may cause a code compaction,
  	 in which case the frame must be free to avoid the relocation machinery
  	 tracing the dead frame.  Since freeing now temporarily violates the page-list
  	 ordering invariant, use the assert-free version."
  	stackPages freeStackPageNoAssert: stackPage.
  	retToContext := self isContext: contextToReturnTo.
  	(retToContext
  	 and: [self isStillMarriedContext: contextToReturnTo])
  		ifTrue:
  			[theFP := self frameOfMarriedContext: contextToReturnTo.
  			 thePage := stackPages stackPageFor: theFP.
  			 theFP = thePage headFP
  				ifTrue:
  					[theSP := thePage headSP]
  				ifFalse:
  					["Returning to some interior frame, presumably because of a sender assignment.
  					  Move the frames above to another page (they may be in use, e.g. via coroutining).
  					  Make the interior frame the top frame."
  					 frameAbove := self findFrameAbove: theFP inPage: thePage.
  					 "Since we've just deallocated a page we know that newStackPage won't deallocate an existing one."
  					 newPage := self newStackPage.
  					 self assert: newPage = stackPage.
  					 self moveFramesIn: thePage through: frameAbove toPage: newPage.
  					 stackPages markStackPageMostRecentlyUsed: newPage.
  					 theFP := thePage headFP.
  					 theSP := thePage headSP]]
  		ifFalse:
  			[(retToContext
  			  and: [objectMemory isIntegerObject: (objectMemory fetchPointer: InstructionPointerIndex ofObject: contextToReturnTo)]) ifFalse:
  				[| contextToReturnFrom |
  				 contextToReturnFrom := stackPages longAt: stackPage baseAddress - BytesPerWord.
  				 self tearDownAndRebuildFrameForCannotReturnBaseFrameReturnFrom: contextToReturnFrom
  					to: contextToReturnTo
  					returnValue: localReturnValue.
  				^self externalCannotReturn: localReturnValue from: contextToReturnFrom].
  			 "We must void the instructionPointer to stop it being updated if makeBaseFrameFor:
  			  cogs a method, which may cause a code compaction."
  			 instructionPointer := 0.
  			 thePage := self makeBaseFrameFor: contextToReturnTo.
  			 theFP := thePage headFP.
  			 theSP := thePage headSP].
  	self setStackPageAndLimit: thePage.
  	self assert: (stackPages stackPageFor: theFP) = stackPage.
  	localSP := theSP.
  	localFP := theFP.
  	localIP := self pointerForOop: self internalStackTop.
  	localIP asUnsignedInteger < objectMemory startOfMemory ifTrue:
  		[localIP asUnsignedInteger ~= cogit ceReturnToInterpreterPC ifTrue:
  			["localIP in the cog method zone indicates a return to machine code."
  			 ^self returnToMachineCodeFrame].
  		 localIP := self pointerForOop: (self iframeSavedIP: localFP)].
  	self assert: (self checkIsStillMarriedContext: contextToReturnTo currentFP: localFP).
  	self setMethod: (self iframeMethod: localFP).
  	self internalStackTopPut: localReturnValue.
  	^self fetchNextBytecode!

Item was changed:
  ----- 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."
  
  	<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 fetchNextBytecode.
  	[true] whileTrue:
  		[self assertValidExecutionPointers.
  		 atEachStepBlock value. "N.B. may be nil"
+ 		 self dispatchOn: currentBytecode in: BytecodeTable.
- 		 self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable.
  		 self incrementByteCount].
  	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
  	self externalizeIPandSP.
  	^nil
  !

Item was changed:
  ----- Method: ReturnNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
+ 	"Make a CCodeGenerator equivalent of a return."
+ 	| exprTranslation lastExpr |
+ 	exprTranslation := expr asTranslatorNodeIn: aTMethod.
- 	"Make a CCodeGenerator equivalent of a return.
- 	 Since super calls are expanded the return must be elided from super expansions."
  	(expr isMessage
+ 	 and: [expr receiver isVariableNode
+ 	 and: [expr receiver key = 'super'
+ 	 and: [exprTranslation isStmtList]]]) ifTrue:
+ 		["super expansions containing returns are fine, and (as of 6/25/2012 19:27) the last
+ 		  return is elided from the expansion by TMethod>>superExpansionNodeFor:args:. 
+ 		  So we need to ensure the last expression is a return and simply reuse any other
+ 		  returns in the expansion."
+ 		exprTranslation statements last isReturn ifFalse:
+ 			[lastExpr := exprTranslation statements removeLast.
+ 			 exprTranslation statements addLast:
+ 				(TReturnNode new 
+ 					setExpression: lastExpr;
+ 					comment: comment;
+ 					yourself)].
+ 		 ^exprTranslation].
- 	 and: [expr receiver isVariableNode and: [expr receiver key = 'super']]) ifTrue:
- 		[^expr asTranslatorNodeIn: aTMethod].
  	^TReturnNode new 
+ 		setExpression: exprTranslation;
+ 		comment: comment;
+ 		yourself!
- 		setExpression: (expr asTranslatorNodeIn: aTMethod);
- 		comment: comment!

Item was changed:
  ----- Method: StackInterpreter>>baseFrameReturn (in category 'return bytecodes') -----
  baseFrameReturn
+ 	<inline: true>
  	| contextToReturnTo isAContext theFP theSP thePage frameAbove |
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #frameAbove type: #'char *'>
  	contextToReturnTo := self frameCallerContext: localFP.
  	isAContext := self isContext: contextToReturnTo.
  	(isAContext
  	 and: [self isStillMarriedContext: contextToReturnTo])
  		ifTrue:
  			[theFP := self frameOfMarriedContext: contextToReturnTo.
  			 thePage := stackPages stackPageFor: theFP.
  			 theFP = thePage headFP
  				ifTrue:
  					[theSP := thePage headSP.
  					 stackPages freeStackPageNoAssert: stackPage "for a short time invariant is violated; assert follows"]
  				ifFalse:
  					["Returning to some interior frame, presumably because of a sender assignment.
  					  Move the frames above to another page (they may be in use, e.g. via coroutining).
  					  Make the interior frame the top frame."
  					 frameAbove := self findFrameAbove: theFP inPage: thePage.
  					 "Reuse the page we're exiting, which avoids allocating a new page and
  					  manipulating the page list to mark the page we're entering as least recently
  					  used (to avoid it being deallocated when allocating a new page)."
  					 self moveFramesIn: thePage through: frameAbove toPage: stackPage.
  					 theFP := thePage headFP.
  					 theSP := thePage headSP]]
  		ifFalse:
  			[(isAContext
  			  and: [objectMemory isIntegerObject: (objectMemory fetchPointer: InstructionPointerIndex ofObject: contextToReturnTo)]) ifFalse:
  				[^self internalCannotReturn: localReturnValue].
  			 thePage := self makeBaseFrameFor: contextToReturnTo.
  			 theFP := thePage headFP.
  			 theSP := thePage headSP.
  			 stackPages freeStackPageNoAssert: stackPage "for a short time invariant is violated; assert follows"].
  	self setStackPageAndLimit: thePage.
  	self assert: (stackPages stackPageFor: theFP) = stackPage.
  	localSP := theSP.
  	localFP := theFP.
  	self setMethod: (self frameMethod: localFP).
  	localIP := self pointerForOop: self internalStackTop.
  	self internalStackTopPut: localReturnValue.
  	self assert: (self checkIsStillMarriedContext: contextToReturnTo currentFP: localFP).
  	^self fetchNextBytecode!

Item was changed:
  ----- Method: StackInterpreter>>fetchNextBytecode (in category 'interpreter shell') -----
  fetchNextBytecode
  	"This method fetches the next instruction (bytecode). Each bytecode method is responsible for fetching the next bytecode, preferably as early as possible to allow the memory system time to process the request before the next dispatch."
  
+ 	self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [currentBytecode := self fetchByte + bytecodeSetSelector]
+ 		ifFalse: [currentBytecode := self fetchByte]!
- 	currentBytecode := self fetchByte.
- !

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 internalizeIPandSP.
  	self fetchNextBytecode.
+ 	[true] whileTrue: [self dispatchOn: currentBytecode in: BytecodeTable].
- 	[true] whileTrue: [self dispatchOn: currentBytecode + bytecodeSetSelector in: BytecodeTable].
  	localIP := localIP - 1.  "undo the pre-increment of IP before returning"
  	self externalizeIPandSP.
  	^nil
  !



More information about the Vm-dev mailing list