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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 24 19:36:27 UTC 2013


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

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

Name: VMMaker.oscog-eem.309
Author: eem
Time: 24 July 2013, 12:34:18.688 pm
UUID: 2ee24067-8c61-4855-b4b3-4bb419b4fe7f
Ancestors: VMMaker.oscog-eem.308

The Peugeot commit.

Use assertValidStackedInstructionPointers: in primitiveTerminateTo.
Fix the assert to use framePointer when on current page and
instructionPointer ~= 0.
Fix assertValidStackedInstructionPointersIn:line: usage in
commenceCogCompiledCodeCompaction.

Simplify relocateCallBeforeReturnPC:by: and elide bogus use of
signedIntToLong there-in.

Add a guard to findClassOfMethod:forReceiver:.

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

Item was changed:
  ----- Method: CoInterpreter>>assertValidStackedInstructionPointersIn:line: (in category 'debug support') -----
  assertValidStackedInstructionPointersIn: aStackPage line: ln
  	"Check that the stacked instruction pointers in the given page are correct.
  	 Checks the interpreter sender/machine code callee contract."
  	<var: #aStackPage type: #'StackPage *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
- 	<var: #theIPPtr type: #'char *'>
  	<var: #theIP type: #usqInt>
  	<var: #theMethod type: #'CogMethod *'>
  	<inline: false>
+ 	| prevFrameWasCogged theFP callerFP theMethod theIP methodObj |
- 	| prevFrameWasCogged theFP callerFP theMethod theIP theIPPtr methodObj |
  	(self asserta: (stackPages isFree: aStackPage) not l: ln) ifFalse:
  		[^false].
  	prevFrameWasCogged := false.
+ 	"The top of stack of an inactive page is always the instructionPointer.
+ 	 The top of stack of the active page may be the instructionPointer if it has been pushed,
+ 	 which is indicated by a 0 instructionPointer."
+ 	(stackPage = aStackPage and: [instructionPointer ~= 0])
+ 		ifTrue:
+ 			[theIP := instructionPointer.
+ 			theFP := framePointer]
+ 		ifFalse:
+ 			[theIP := (stackPages longAt: aStackPage headSP) asUnsignedInteger.
+ 			 theFP := aStackPage headFP.
+ 			 stackPage = aStackPage ifTrue:
+ 				[self assert: framePointer = theFP]].
- 	theIPPtr := aStackPage headSP.
- 	theFP := aStackPage headFP.
  	[(self isMachineCodeFrame: theFP)
  		ifTrue:
  			[theMethod := self mframeHomeMethod: theFP.
- 			 theIP := (stackPages longAt: theIPPtr) asUnsignedInteger.
  			 self assert: (theIP = cogit ceCannotResumePC
  						  or: [self asserta: (theIP >= theMethod asUnsignedInteger
  							   and: [theIP < (theMethod asUnsignedInteger + theMethod blockSize)])])
  				l: ln.
  			prevFrameWasCogged := true]
  		ifFalse: "assert-check the interpreter frame."
+ 			[methodObj := self iframeMethod: theFP.
- 			[theIP := (stackPages longAt: theIPPtr) asUnsignedInteger.
- 			 methodObj := self iframeMethod: theFP.
  			 prevFrameWasCogged ifTrue:
  				[self assert: theIP = cogit ceReturnToInterpreterPC l: ln].
  			 theIP = cogit ceReturnToInterpreterPC ifTrue:
  				[theIP := self iframeSavedIP: theFP].
  			 self assert: (theIP >= (methodObj + (objectMemory lastPointerOf: methodObj) + BaseHeaderSize - 1)
  						  and: [theIP < (methodObj + (objectMemory byteLengthOf: methodObj) + BaseHeaderSize)])
  				l: ln.
  			 prevFrameWasCogged := false].
+ 	 theIP := (stackPages longAt: theFP + FoxCallerSavedIP) asUnsignedInteger.
+ 	 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
+ 		[theFP := callerFP].
+ 	self assert: theIP = cogit ceBaseFrameReturnPC l: ln.
- 	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
- 		[theIPPtr := theFP + FoxCallerSavedIP.
- 		 theFP := callerFP].
  	^true!

Item was changed:
  ----- Method: CoInterpreter>>commenceCogCompiledCodeCompaction (in category 'process primitive support') -----
  commenceCogCompiledCodeCompaction
  	| startTime |
  	<var: #startTime type: #usqLong>
  	cogCompiledCodeCompactionCalledFor := false.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceCodeCompaction thing: TraceCodeCompaction source: 0].
  	startTime := self ioUTCMicrosecondsNow.
  
  	"This can be called in a number of circumstances.  The instructionPointer
  	 may contain a native pc that must be relocated.  There may already be a
  	 pushed instructionPointer on stack.  Clients ensure that instructionPointer
  	 is 0 if it should not be pushed and/or relocated.  Pushing twice is a mistake
  	 because only the top one will be relocated."
  	instructionPointer ~= 0 ifTrue:
  		[self push: instructionPointer.
  		 self externalWriteBackHeadStackPointer].
  	self assertValidStackedInstructionPointers: #'__LINE__'.
  	cogit compactCogCompiledCode.
- 	self assertValidStackedInstructionPointers: #'__LINE__'.
  	instructionPointer ~= 0 ifTrue:
  		[instructionPointer := self popStack.
  		 self externalWriteBackHeadStackPointer].
+ 	self assertValidStackedInstructionPointers: #'__LINE__'.
  
  	statCodeCompactionCount := statCodeCompactionCount + 1.
  	statCodeCompactionUsecs := statCodeCompactionUsecs + (self ioUTCMicrosecondsNow - startTime).
  
  	objectMemory checkForLeaks ~= 0 ifTrue:
  		[objectMemory clearLeakMapAndMapAccessibleObjects.
  		 self assert: (self checkCodeIntegrity: false)]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveTerminateTo (in category 'control primitives') -----
  primitiveTerminateTo
  	"Primitive. Terminate up the context stack from the receiver up to but not including
  	 the argument, if previousContext is on my Context stack. Make previousContext my
  	 sender. This prim has to shadow the code in ContextPart>terminateTo: to be correct.
  
  	 Override to ensure the caller's saved ip is correct, i.e. if an interpreter frame it may
  	 have to move to iframeSavedIP."
  	| thisCtx currentCtx aContextOrNil contextsFP contextsSP contextsIP nextCntx stackedReceiverOffset 
  	  theFP newFP newSP pageToStopOn thePage frameAbove |
  	<var: #contextsFP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #newFP type: #'char *'>
  	<var: #newSP type: #'char *'>
  	<var: #contextsIP type: #usqInt>
  	<var: #frameAbove type: #'char *'>
  	<var: #contextsSP type: #'char *'>
  	<var: #source type: #'char *'>
  	<var: #pageToStopOn type: #'StackPage *'>
  	<var: #thePage type: #'StackPage *'>
  
  	aContextOrNil := self stackTop.
  	(aContextOrNil = objectMemory nilObject or: [objectMemory isContext: aContextOrNil]) ifFalse:
  		[^self primitiveFail].
  	thisCtx := self stackValue: 1.
  	thisCtx = aContextOrNil ifTrue:
  		[^self primitiveFail].		
  
  	"All stackPages need to have current head pointers to avoid confusion."
  	self externalWriteBackHeadFramePointers.
  
  	"If we're searching for aContextOrNil it might be on a stack page.  Helps to know
  	 if we can free a whole page or not, or if we can short-cut the termination."
  	(aContextOrNil ~= objectMemory nilObject and: [self isStillMarriedContext: aContextOrNil])
  		ifTrue: [contextsFP := self frameOfMarriedContext: aContextOrNil.
  				pageToStopOn := stackPages stackPageFor: contextsFP]
  		ifFalse: [pageToStopOn := 0].
  
  	"if thisCtx is married ensure it is a base frame.  Then we can assign its sender."
  	(self isStillMarriedContext: thisCtx)
  		ifTrue:
  			[theFP := self frameOfMarriedContext: thisCtx.
  			 "Optimize terminating thisContext.  Move its frame down to be next to
  			  aContextOrNil's frame. Common in the exception system and so helps to be fast."
  			 (theFP = framePointer
  			  and: [pageToStopOn = stackPage]) ifTrue:
+ 				[self assertValidStackedInstructionPointersIn: stackPage line: #'__LINE__'.
+ 				 (self frameCallerFP: theFP) ~= contextsFP ifTrue:
- 				[(self frameCallerFP: theFP) ~= contextsFP ifTrue:
  					[stackedReceiverOffset := self frameStackedReceiverOffset: theFP.
  					 frameAbove := self findFrameAbove: contextsFP inPage: pageToStopOn.
  					 contextsIP := (self frameCallerSavedIP: frameAbove) asUnsignedInteger.
  					 self assert: ((contextsIP asUnsignedInteger >= objectMemory startOfMemory)
  								or: [contextsIP = cogit ceReturnToInterpreterPC]) == (self isMachineCodeFrame: contextsFP) not.
  					 newSP := self frameCallerSP: frameAbove.
  					 newFP := newSP - stackedReceiverOffset - BytesPerWord.
  					 theFP + stackedReceiverOffset
  						to: stackPointer
  						by: BytesPerWord negated
  						do: [:source|
  							newSP := newSP - BytesPerWord.
  							stackPages longAt: newSP put: (stackPages longAt: source)].
  					 stackPages longAt: newFP + FoxSavedFP put: contextsFP.
  					"Ensure contract between machine-code callee and interpreter caller frames is preserved.
  					 Return pc needs to be ceReturnToInterpreterPC."
  					 ((self isMachineCodeFrame: newFP)
  					  and: [contextsIP >= objectMemory startOfMemory]) ifTrue:
  						[self iframeSavedIP: contextsFP put: contextsIP.
  						 contextsIP := cogit ceReturnToInterpreterPC].
  					 stackPages longAt: newFP + FoxCallerSavedIP put: contextsIP.
  					 self assert: (objectMemory isContext: thisCtx).
  					 objectMemory storePointerUnchecked: SenderIndex
  						ofObject: thisCtx
  						withValue: (self withSmallIntegerTags: newFP).
  					 objectMemory storePointerUnchecked: InstructionPointerIndex
  						ofObject: thisCtx
  						withValue: (self withSmallIntegerTags: contextsFP).
  					 framePointer := newFP.
  					 stackPointer := newSP].
+ 				 self pop: 1.
+ 				 self assertValidStackedInstructionPointersIn: stackPage line: #'__LINE__'.
+ 				 self assert: stackPage = stackPages mostRecentlyUsedPage.
+ 				 ^nil].
- 				self pop: 1.
- 				self assert: stackPage = stackPages mostRecentlyUsedPage.
- 				^nil].
  			 theFP := self externalEnsureIsBaseFrame: theFP. "May cause a GC!!!!"
  			 currentCtx := self frameCallerContext: theFP.
  			 "May also reclaim aContextOrNil's page, hence..."
  			 (aContextOrNil ~= objectMemory nilObject and: [self isStillMarriedContext: aContextOrNil])
  				ifTrue: [contextsFP := self frameOfMarriedContext: aContextOrNil.
  						pageToStopOn := stackPages stackPageFor: contextsFP]
  				ifFalse: [pageToStopOn := 0]]
  		ifFalse:
  			[currentCtx := objectMemory fetchPointer: SenderIndex ofObject: thisCtx].
  
+ 	self assertValidStackedInstructionPointers: #'__LINE__'.
  	(self context: thisCtx hasSender: aContextOrNil) ifTrue:
  		["Need to walk the stack freeing stack pages and nilling contexts."
  		[currentCtx = aContextOrNil
  		 or: [currentCtx = objectMemory nilObject]] whileFalse:
  			[self assert: (objectMemory isContext: currentCtx).
  			 (self isMarriedOrWidowedContext: currentCtx)
  				ifTrue:
  					[theFP := self frameOfMarriedContext: currentCtx.
  					thePage := stackPages stackPageFor: theFP.
  					"If externalEnsureIsBaseFrame: above has moved thisContext to its own stack
  					 then we will always terminate to a frame on a different page.  But if we are
  					 terminating some other context to a context somewhere on the current page
  					 we must save the active frames above that context.  Things will look e.g. like this:
  		thisCtx			499383332 s MethodContext(ContextPart)>resume:
  						499380484 s BlockClosure>ensure:
  						499377320 s MethodContext(ContextPart)>handleSignal:
  						499373760 s MethodContext(ContextPart)>handleSignal:
  						499372772 s MessageNotUnderstood(Exception)>signal
  						499369068 s CodeSimulationTests(Object)>doesNotUnderstand: absentMethod
  						499368708 s [] in CodeSimulationTests>testDNU
  							(sender is 0xbffc2480 I CodeSimulationTests>runSimulated:)
  						------------
  		framePointer	0xbffc234c M MethodContext(ContextPart)>doPrimitive:method:receiver:args:
  						0xbffc2378 M MethodContext(ContextPart)>tryPrimitiveFor:receiver:args:
  						0xbffc23ac M MethodContext(ContextPart)>send:to:with:super:
  						0xbffc23e4 M MethodContext(ContextPart)>send:super:numArgs:
  						0xbffc2418 M MethodContext(InstructionStream)>interpretNextInstructionFor:
  						0xbffc2434 M MethodContext(ContextPart)>step
  						0xbffc2458 I MethodContext(ContextPart)>runSimulated:contextAtEachStep:
  						------------
  (499368708's sender)	0xbffc2480 I CodeSimulationTests>runSimulated:
  						0xbffc249c M CodeSimulationTests>testDNU
  						0xbffc24bc I CodeSimulationTests(TestCase)>performTest
  						0xbffc24dc I [] in CodeSimulationTests(TestCase)>runCase
  		aContextOrNil	0xbffc24fc M BlockClosure>ensure:
  						0xbffc2520 I CodeSimulationTests(TestCase)>runCase
  						0xbffc253c M [] in TestResult>runCase:
  					When we find this case we move the frames above to a new page by making the
  					frame above currentCtx a base frame, i.e. making 0xbffc2458 in the above example
  					a base frame.  But in this iteration of the loop we don't move down a frame i.e. currentCtx
  					doesn't change on this iteration."
  					thePage = stackPage
  						ifTrue:
  							[frameAbove := self findFrameAbove: theFP inPage: thePage.
  							self assert: frameAbove ~= 0.
  							frameAbove := self externalEnsureIsBaseFrame: frameAbove. "May cause a GC!!!! May also reclaim aContextOrNil's page, hence..."
  							(aContextOrNil ~= objectMemory nilObject and: [self isStillMarriedContext: aContextOrNil])
  								ifTrue: [contextsFP := self frameOfMarriedContext: aContextOrNil.
  										pageToStopOn := stackPages stackPageFor: contextsFP]
  								ifFalse: [pageToStopOn := 0]]
  						ifFalse:
  							[thePage = pageToStopOn
  								ifTrue:
  									["We're here.  Cut back the stack to aContextOrNil's frame,
  									  push its instructionPointer if it's not already a head frame,
  									  and we're done."
  									 frameAbove := self findFrameAbove: contextsFP inPage: thePage.
  									 frameAbove ~= 0 ifTrue:
  										[contextsSP := (self frameCallerSP: frameAbove) - BytesPerWord.
  										 stackPages longAt: contextsSP put: (self frameCallerSavedIP: frameAbove).
  										 self setHeadFP: contextsFP andSP: contextsSP inPage: thePage].
  									 currentCtx := aContextOrNil]
  								ifFalse:
  									["We can free the entire page without further ado."
  									 currentCtx := self frameCallerContext: thePage baseFP.
  									 "for a short time invariant is violated; assert follows"
  									 stackPages freeStackPageNoAssert: thePage]]]
  				ifFalse:
  					[nextCntx := objectMemory fetchPointer: SenderIndex ofObject: currentCtx.
  					 self markContextAsDead: currentCtx.
  					 currentCtx := nextCntx]]].
  	self assert: stackPages pageListIsWellFormed.
  	(self isMarriedOrWidowedContext: thisCtx)
  		ifTrue:
  			[self assert: (self checkIsStillMarriedContext: thisCtx currentFP: framePointer).
  			 self assert: (self isBaseFrame: (self frameOfMarriedContext: thisCtx)).
  			 theFP := self frameOfMarriedContext: thisCtx.
  			 self frameCallerContext: theFP put: aContextOrNil]
+ 		ifFalse:
+ 			[objectMemory storePointer: SenderIndex ofObject: thisCtx withValue: aContextOrNil].
- 		ifFalse: [objectMemory storePointer: SenderIndex ofObject: thisCtx withValue: aContextOrNil].
  	self pop: 1.
+ 	self assertValidStackedInstructionPointers: #'__LINE__'.
  	self assert: stackPage = stackPages mostRecentlyUsedPage!

Item was changed:
  ----- Method: CogIA32Compiler>>relocateCallBeforeReturnPC:by: (in category 'inline cacheing') -----
  relocateCallBeforeReturnPC: retpc by: delta
  	| distance |
  	delta ~= 0 ifTrue:
  		[distance :=    ((objectMemory byteAt: retpc - 1) << 24)
  					+  ((objectMemory byteAt: retpc - 2) << 16)
  					+  ((objectMemory byteAt: retpc - 3) << 8)
  					+   (objectMemory byteAt: retpc - 4).
  		 distance := distance + delta.
  		 objectMemory
  			byteAt: retpc - 1 put: (distance >> 24 bitAnd: 16rFF);
  			byteAt: retpc - 2 put: (distance >> 16 bitAnd: 16rFF);
  			byteAt: retpc - 3 put: (distance >>   8 bitAnd: 16rFF);
  			byteAt: retpc - 4 put: (distance            bitAnd: 16rFF).
+ 		(self asserta: (self callTargetFromReturnAddress: retpc) >= cogit minCallAddress) ifFalse:
+ 			[self error: 'relocating call to invalid address']]!
- 		false
- 			ifTrue: [self assert: (self callTargetFromReturnAddress: retpc) signedIntToLong >= cogit minCallAddress]
- 			ifFalse: [(self callTargetFromReturnAddress: retpc) signedIntToLong >= cogit minCallAddress ifFalse:
- 						[self error: 'relocating call to invalid address']]]!

Item was changed:
  ----- Method: StackInterpreter>>findClassOfMethod:forReceiver: (in category 'debug support') -----
  findClassOfMethod: meth forReceiver: rcvr
  	| rclass |
  	(objectMemory addressCouldBeOop: rcvr) ifTrue:
  		[rclass := objectMemory fetchClassOf: rcvr.
  		 (self addressCouldBeClassObj: rclass) ifTrue:
  			[rclass := self findClassContainingMethod: meth startingAt: rclass.
  			rclass ~= objectMemory nilObject ifTrue:
  				[^rclass]]].
+ 	((objectMemory addressCouldBeObj: meth)
+ 	 and: [self isCompiledMethod: meth]) ifFalse:
- 	(objectMemory addressCouldBeObj: meth) ifFalse:
  		[^objectMemory nilObject].
  	^self findClassContainingMethod: meth startingAt: (self methodClassOf: meth)!



More information about the Vm-dev mailing list