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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 2 18:03:21 UTC 2015


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

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

Name: VMMaker.oscog-eem.1153
Author: eem
Time: 2 April 2015, 11:01:15.816 am
UUID: 078f2fbd-0bb3-4773-a8b7-73a06a398a24
Ancestors: VMMaker.oscog-eem.1152

Rename the inconsistently-named and hence confusing
frameReceiverOffset: to frameReceiverLocation:.
Fix the slip in followForwardingPointersInStackZone:
that was due to this confusion.

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

Item was changed:
  ----- Method: CoInterpreter>>checkStackIntegrity (in category 'object memory support') -----
  checkStackIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccesibleObjects has set a bit at each
  	 object's header.  Scan all objects accessible from the stack
  	 checking that every pointer points to a header.  Answer if no
  	 dangling pointers were detected."
  	| ok |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	ok := true.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP frameRcvrOffset callerFP oop |
  		thePage := stackPages stackPageAt: i.
  		(stackPages isFree: thePage) ifFalse:
  			[thePage = stackPage
  				ifTrue:
  					[theSP := stackPointer.
  					 theFP := framePointer]
  				ifFalse:
  					[theSP := thePage headSP.
  					 theFP := thePage  headFP].
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage ifFalse:
  				[theSP := theSP + objectMemory wordSize].
+ 			 [frameRcvrOffset := self frameReceiverLocation: theFP.
- 			 [frameRcvrOffset := self frameReceiverOffset: theFP.
  			  [theSP <= frameRcvrOffset] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 ((objectMemory isNonImmediate: oop) 
  				   and: [(objectMemory heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  					[self printFrameThing: 'object leak in frame temp' andFrame: theFP at: theSP.
  					 ok := false].
  				 theSP := theSP + objectMemory wordSize].
  			 (self frameHasContext: theFP) ifTrue:
  				[oop := self frameContext: theFP.
  				 ((objectMemory isImmediate: oop) 
  				   or: [(objectMemory heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  					[self printFrameThing: 'object leak in frame ctxt' andFrame: theFP at: theFP + FoxThisContext.
  					 ok := false].
  				 (objectMemory isContext: oop) ifFalse:
  					[self printFrameThing: 'frame ctxt should be context' andFrame: theFP at: theFP + FoxThisContext.
  					 ok := false].
  				 ((objectMemory isContext: oop) and: [self isMarriedOrWidowedContext: oop]) ifFalse:
  					[self printFrameThing: 'frame ctxt should be married' andFrame: theFP at: theFP + FoxThisContext.
  					 ok := false].
  				 ((objectMemory isContext: oop) and: [(self frameOfMarriedContext: oop) = theFP]) ifFalse:
  					[self printFrameThing: 'frame ctxt should be married to this frame ' andFrame: theFP at: theFP + FoxThisContext.
  					 ok := false]].
  			 (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[| cogMethod |
  					 cogMethod := self mframeHomeMethod: theFP.
  					 (objectMemory heapMapAtWord: (self pointerForOop: cogMethod)) = 0 ifTrue:
  						[self printFrameThing: 'object leak in mframe mthd' andFrame: theFP at: theFP + FoxMethod.
  						 ok := false]]
  				ifFalse:
  					[oop := self iframeMethod: theFP.
  					 ((objectMemory isImmediate: oop) 
  					   or: [(objectMemory heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  						[self printFrameThing: 'object leak in iframe mthd' andFrame: theFP at: theFP + FoxMethod.
  						 ok := false]].
  			 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  				 theFP := callerFP].
  			 theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 ((objectMemory isNonImmediate: oop) 
  				   and: [(objectMemory heapMapAtWord: (self pointerForOop: oop)) = 0]) ifTrue:
  					[self printFrameThing: 'object leak in frame arg' andFrame: theFP at: theSP.
  					 ok := false].
  				 theSP := theSP + objectMemory wordSize]]].
  	^ok!

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: theBecomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache
  	 probe, since notionally objects' internals are accessed only via sending messages to them,
  	 the exception is primitives that access the internals of the non-receiver argument(s).
  	 To avoid a read barrier on inst var fetch we scan the receivers in the stack zone and follow
  	 any forwarded ones.  This is way cheaper than scanning all of memory as in the old become.
  
  	 Override to handle machine code frames, and to handle the lack of an explicit read barrier on super sends.
  	 With most super send implementations (not Newspeak's absent super bytecodes) self, the receiver of the
  	 super send, is pushed before any arguments.  So if self is becommed during argument marshalling, e.g.
  		super doSomethingWith: (self become: self somethingElse)
  	 then a stale forwarded reference to self could be left on the stack.  In the StackInterpreter we deal with this
  	 with an explicit read barrier on supersend.  In the CoInterpreter we deal with it by following all non-argument
  	 stack contents."
  	| theIPPtr |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #offset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  
  	self externalWriteBackHeadFramePointers.
  
  	(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isOopForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := 0]
  				ifFalse:
  					[theIPPtr := theSP asUnsignedInteger.
  					 theSP := theSP + objectMemory wordSize].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
+ 			  offset := self frameReceiverLocation: theFP.
- 			  offset := theFP + (self frameStackedReceiverOffset: theFP).
  	 		  [theSP <= offset] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isOopForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			 (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxMFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxMFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := (self mframeHomeMethod: theFP) methodObject.
  					 self assert: (objectMemory isForwarded: oop) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 (objectMemory isOopForwarded: oop) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self iframeMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| newOop delta |
  						 newOop := objectMemory followForwarded: oop.
  						 delta := newOop - oop.
  						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > oop]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + delta].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + delta.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (oop := newOop)]].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theSP := theIPPtr + objectMemory wordSize.
  				 theFP := callerFP].
  			 "And finally follow the saved context and the caller context."
  			 theSP := thePage baseAddress - objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory isForwarded: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory followForwarded: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was added:
+ ----- Method: CoInterpreter>>frameReceiverLocation: (in category 'frame access') -----
+ frameReceiverLocation: theFP
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	^(self isMachineCodeFrame: theFP)
+ 		ifTrue: [theFP + FoxMFReceiver]
+ 		ifFalse: [theFP + FoxIFReceiver]!

Item was removed:
- ----- Method: CoInterpreter>>frameReceiverOffset: (in category 'frame access') -----
- frameReceiverOffset: theFP
- 	<inline: true>
- 	<var: #theFP type: #'char *'>
- 	^(self isMachineCodeFrame: theFP)
- 		ifTrue: [theFP + FoxMFReceiver]
- 		ifFalse: [theFP + FoxIFReceiver]!

Item was changed:
  ----- Method: CoInterpreter>>mapStackPages (in category 'object memory support') -----
  mapStackPages
  	<inline: #never>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #'char *'>
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP frameRcvrOffset callerFP theIPPtr theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := ((self isMachineCodeFrame: theFP)
  									or: [(self iframeSavedIP: theFP) = 0])
  										ifTrue: [0]
  										ifFalse: [theFP + FoxIFSavedIP]]
  				ifFalse:
  					[theIPPtr := theSP.
  					 theSP := theSP + objectMemory wordSize].
  			[self assert: (thePage addressIsInPage: theFP).
  			 self assert: (thePage addressIsInPage: theSP).
  			 self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
+ 			 frameRcvrOffset := self frameReceiverLocation: theFP.
- 			 frameRcvrOffset := self frameReceiverOffset: theFP.
  	 		  [theSP <= frameRcvrOffset] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory shouldRemapOop: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory remapObj: oop)].
  				 theSP := theSP + objectMemory wordSize].
  			 (self frameHasContext: theFP) ifTrue:
  				[(objectMemory shouldRemapObj: (self frameContext: theFP)) ifTrue:
  					[stackPages
  						longAt: theFP + FoxThisContext
  						put: (objectMemory remapObj: (self frameContext: theFP))].
  				 "forwarding scheme in SqueakV3 obj rep makes this hard to check."
  				 objectMemory hasSpurMemoryManagerAPI ifTrue:
  					[self assert: ((self isMarriedOrWidowedContext: (self frameContext: theFP))
  								and: [(self frameOfMarriedContext: (self frameContext: theFP)) = theFP])]].
  			(self isMachineCodeFrame: theFP) ifFalse:
  				[(objectMemory shouldRemapObj: (self iframeMethod: theFP)) ifTrue:
  					[theIPPtr ~= 0 ifTrue:
  						[theIP := stackPages longAt: theIPPtr.
  						 theIP = cogit ceReturnToInterpreterPC
  							ifTrue:
  								[self assert: (self iframeSavedIP: theFP) > (self iframeMethod: theFP).
  								 theIPPtr := theFP + FoxIFSavedIP.
  								 theIP := stackPages longAt: theIPPtr]
  							ifFalse:
  								[self assert: theIP > (self iframeMethod: theFP)].
  						 theIP := theIP - (self iframeMethod: theFP)].
  					 stackPages
  						longAt: theFP + FoxMethod
  						put: (objectMemory remapObj: (self iframeMethod: theFP)).
  					 theIPPtr ~= 0 ifTrue:
  						[stackPages longAt: theIPPtr put: theIP + (self iframeMethod: theFP)]]].
  			 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theSP := (theIPPtr := theFP + FoxCallerSavedIP) + objectMemory wordSize.
  				 theFP := callerFP].
  			 theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop := stackPages longAt: theSP.
  				 (objectMemory shouldRemapOop: oop) ifTrue:
  					[stackPages longAt: theSP put: (objectMemory remapObj: oop)].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: CoInterpreter>>markAndTraceStackPage: (in category 'object memory support') -----
  markAndTraceStackPage: thePage
  	| theSP theFP frameRcvrOffset callerFP oop |
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<inline: false>
  
  	self assert: (stackPages isFree: thePage) not.
  	self assert: thePage trace ~= StackPageTraced.
  	thePage trace: StackPageTraced.
  
  	theSP := thePage headSP.
  	theFP := thePage  headFP.
  	"Skip the instruction pointer on top of stack of inactive pages."
  	thePage = stackPage ifFalse:
  		[theSP := theSP + objectMemory wordSize].
+ 	[frameRcvrOffset := self frameReceiverLocation: theFP.
- 	[frameRcvrOffset := self frameReceiverOffset: theFP.
  	 [theSP <= frameRcvrOffset] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize].
  	(self frameHasContext: theFP) ifTrue:
  		[self assert: (objectMemory isContext: (self frameContext: theFP)).
  		 objectMemory markAndTrace: (self frameContext: theFP)].
  	(self isMachineCodeFrame: theFP)
  		ifTrue: [self markAndTraceMachineCodeMethod: (self mframeCogMethod: theFP)]
  		ifFalse: [objectMemory markAndTrace: (self iframeMethod: theFP)].
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  		 theFP := callerFP].
  	theSP := theFP + FoxCallerSavedIP + objectMemory wordSize. "caller ip is ceBaseReturnPC"
  	[theSP <= thePage baseAddress] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize]!

Item was changed:
  ----- Method: StackInterpreter>>checkOkayStackPage: (in category 'debug support') -----
  checkOkayStackPage: thePage
  	| theSP theFP ok frameRcvrOffset callerFP oop |
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<inline: false>
  	theSP := thePage headSP.
  	theFP := thePage  headFP.
  	ok := true.
  	"Skip the instruction pointer on top of stack of inactive pages."
  	thePage = stackPage ifFalse:
  		[theSP := theSP + objectMemory wordSize].
+ 	[frameRcvrOffset := self frameReceiverLocation: theFP.
- 	[frameRcvrOffset := self frameReceiverOffset: theFP.
  	 [theSP <= frameRcvrOffset] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isIntegerObject: oop) ifFalse:
  			[ok := ok & (self checkOkayFields: oop)].
  		 theSP := theSP + objectMemory wordSize].
  	(self frameHasContext: theFP) ifTrue:
  		[self assert: (objectMemory isContext: (self frameContext: theFP)).
  		 ok := ok & (self checkOkayFields: (self frameContext: theFP))].
  	ok := ok & (self checkOkayFields: (self frameMethodObject: theFP)).
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  		 theFP := callerFP].
  	theSP := self isCog
  				ifTrue: [theFP + FoxCallerSavedIP + objectMemory wordSize] "caller ip is ceBaseReturnPC"
  				ifFalse: [theFP + FoxCallerSavedIP]. "caller ip is frameCallerContext in a base frame"
  	[theSP <= thePage baseAddress] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isIntegerObject: oop) ifFalse:
  			[ok := ok & (self checkOkayFields: oop)].
  		 theSP := theSP + objectMemory wordSize].
  	^ok!

Item was changed:
  ----- Method: StackInterpreter>>findSPOrNilOf:on:startingFrom: (in category 'frame access') -----
  findSPOrNilOf: theFP on: thePage startingFrom: startFrame
  	"Search for the stack pointer for theFP.  This points to the hottest item on the frame's stack.
  	 DO NOT CALL THIS WITH theFP == localFP OR theFP == framePointer!!"
  	<var: #theFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #startFrame type: #'char *'>
  	<returnTypeC: #'char *'>
  	| aFrame prevFrame |
  	<inline: true>
  	<var: #aFrame type: #'char *'>
  	<var: #prevFrame type: #'char *'>
  	self assert: (stackPages isFree: thePage) not.
  	startFrame = theFP ifTrue:
  		[thePage headSP >= startFrame ifTrue:
  			["If the SP is invalid return the pointer to the receiver field."
+ 			 ^self frameReceiverLocation: theFP].
- 			 ^self frameReceiverOffset: aFrame].
  		 "Skip the instruction pointer on top of stack of inactive pages."
  		^thePage = stackPage
  			ifTrue: [thePage headSP]
  			ifFalse: [thePage headSP + objectMemory wordSize]].
  	aFrame := startFrame.
  	[prevFrame := aFrame.
  	 aFrame := self frameCallerFP: aFrame.
  	 aFrame ~= 0] whileTrue:
  		[theFP = aFrame ifTrue:
  			[^self frameCallerSP: prevFrame]].
  	^nil!

Item was changed:
  ----- Method: StackInterpreter>>followForwardedFrameContents:stackPointer: (in category 'lazy become') -----
  followForwardedFrameContents: theFP stackPointer: theSP
  	"follow pointers in the current stack frame up to theSP."
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	<inline: false>
  	<var: #ptr type: #'char *'>
  	theFP + (self frameStackedReceiverOffset: theFP)
  		to: theFP + FoxCallerSavedIP + objectMemory wordSize
  		by: objectMemory wordSize
  		do: [:ptr| | oop |
  			oop := stackPages longAt: ptr.
  			((objectMemory isNonImmediate: oop)
  			 and: [objectMemory isForwarded: oop]) ifTrue:
  				[stackPages longAt: ptr put: (objectMemory followForwarded: oop)]].
  	theSP
+ 		to: (self frameReceiverLocation: theFP)
- 		to: (self frameReceiverOffset: theFP)
  		by: objectMemory wordSize
  		do: [:ptr| | oop |
  			oop := stackPages longAt: ptr.
  			((objectMemory isNonImmediate: oop)
  			 and: [objectMemory isForwarded: oop]) ifTrue:
  				[stackPages longAt: ptr put: (objectMemory followForwarded: oop)]].
  	self assert: (objectMemory isForwarded: (self frameMethodObject: theFP)) not.
  	(self frameHasContext: theFP) ifTrue:
  		[self assert: (objectMemory isForwarded: (self frameContext: theFP)) not]!

Item was added:
+ ----- Method: StackInterpreter>>frameReceiverLocation: (in category 'frame access') -----
+ frameReceiverLocation: theFP
+ 	<inline: true>
+ 	<var: #theFP type: #'char *'>
+ 	^theFP + FoxReceiver!

Item was removed:
- ----- Method: StackInterpreter>>frameReceiverOffset: (in category 'frame access') -----
- frameReceiverOffset: theFP
- 	<inline: true>
- 	<var: #theFP type: #'char *'>
- 	^theFP + FoxReceiver!

Item was changed:
  ----- Method: StackInterpreter>>markAndTraceStackPage: (in category 'object memory support') -----
  markAndTraceStackPage: thePage
  	| theSP theFP frameRcvrOffset callerFP oop |
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #frameRcvrOffset type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<inline: false>
  
  	self assert: (stackPages isFree: thePage) not.
  	self assert: thePage trace ~= StackPageTraced.
  	thePage trace: StackPageTraced.
  
  	theSP := thePage headSP.
  	theFP := thePage  headFP.
  	"Skip the instruction pointer on top of stack of inactive pages."
  	thePage = stackPage ifFalse:
  		[theSP := theSP + objectMemory wordSize].
+ 	[frameRcvrOffset := self frameReceiverLocation: theFP.
- 	[frameRcvrOffset := self frameReceiverOffset: theFP.
  	 [theSP <= frameRcvrOffset] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize].
  	(self frameHasContext: theFP) ifTrue:
  		[self assert: (objectMemory isContext: (self frameContext: theFP)).
  		 objectMemory markAndTrace: (self frameContext: theFP)].
  	objectMemory markAndTrace: (self iframeMethod: theFP).
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  		 theFP := callerFP].
  	theSP := theFP + FoxCallerSavedIP. "caller ip is frameCallerContext in a base frame"
  	[theSP <= thePage baseAddress] whileTrue:
  		[oop := stackPages longAt: theSP.
  		 (objectMemory isOopForwarded: oop) ifTrue:
  			[oop := objectMemory followForwarded: oop.
  			 stackPages longAt: theSP put: oop].
  		 (objectMemory isImmediate: oop) ifFalse:
  			[objectMemory markAndTrace: oop].
  		 theSP := theSP + objectMemory wordSize]!

Item was changed:
  ----- Method: StackInterpreter>>marriedContext:pointsTo:stackDeltaForCurrentFrame: (in category 'frame access') -----
  marriedContext: spouseContext pointsTo: anOop stackDeltaForCurrentFrame: stackDeltaForCurrentFrame
  	"This is a helper for primitiveObjectPointsTo so it *does not* check the frameContext field because that is an implicit self-reference not present in the state ."
  	| theFP thePage theSP rcvrOffset |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #rcvrOffset type: #'char *'>
  	theFP := self frameOfMarriedContext: spouseContext.
  	theFP = framePointer
  		ifTrue: [theSP := stackPointer + (stackDeltaForCurrentFrame * objectMemory wordSize)]
  		ifFalse:
  			[thePage := stackPages stackPageFor: theFP.
  			theSP := self findSPOf: theFP on: thePage].
  	(objectMemory isIntegerObject: anOop)
  		ifTrue: "Check stack and instruction pointer fields."
  			[(anOop = (objectMemory integerObjectOf: (self stackPointerIndexForFrame: theFP WithSP: theSP))
  			or: [anOop = (self externalInstVar: InstructionPointerIndex ofContext: spouseContext)]) ifTrue:
  				[^true]]
  		ifFalse: "Check method and sender fields, avoiding unnecessarily reifying sender context."
  			[anOop = (self frameMethodObject: theFP) ifTrue:
  				[^true].
  			 (self isBaseFrame: theFP)
  				ifTrue: [anOop = (self frameCallerContext: theFP) ifTrue:
  							[^true]]
  				ifFalse: [((self frameHasContext: (self frameCallerFP: theFP))
  						and: [anOop = (self frameContext: (self frameCallerFP: theFP))]) ifTrue:
  							[^true]]].
  	"Now check receiver, temps and stack contents"
+ 	rcvrOffset := self frameReceiverLocation: theFP.
- 	rcvrOffset := self frameReceiverOffset: theFP.
  	 [theSP <= rcvrOffset] whileTrue:
  		[anOop = (stackPages longAt: theSP) ifTrue:
  			[^true].
  		 theSP := theSP + objectMemory wordSize].
  	"Finally check stacked receiver (closure field or duplicate of receiver) and arguments"
  	theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
  	rcvrOffset := theFP + (self frameStackedReceiverOffset: theFP).
  	 [theSP <= rcvrOffset] whileTrue:
  		[anOop = (stackPages longAt: theSP) ifTrue:
  			[^true].
  		 theSP := theSP + objectMemory wordSize].
  	^false!

Item was changed:
  ----- Method: StackInterpreter>>printFrame: (in category 'debug printing') -----
  printFrame: theFP
  	| thePage frameAbove theSP |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	<var: #frameAbove type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	(stackPages couldBeFramePointer: theFP) ifFalse:
  		[self printHexPtr: theFP; print: ' is not in the stack zone?!!'; cr.
  		 ^nil].
  	frameAbove := nil.
  	theFP = framePointer
  		ifTrue: [theSP := stackPointer]
  		ifFalse:
  			[thePage := stackPages stackPageFor: theFP.
  			 (stackPages isFree: thePage) ifTrue:
  				[self printHexPtr: theFP; print: ' is on a free page?!!'; cr.
  				 ^nil].
  			 (thePage ~= stackPage
  			  and: [theFP = thePage headFP])
  				ifTrue: [theSP := thePage headSP]
  				ifFalse:
  					[frameAbove := self safeFindFrameAbove: theFP
  										on: thePage
  										startingFrom: ((thePage = stackPage
  														and: [framePointer
  																between: thePage realStackLimit
  																and: thePage baseAddress])
  														ifTrue: [framePointer]
  														ifFalse: [thePage headFP]).
  					 theSP := frameAbove ifNotNil:
  								[self frameCallerSP: frameAbove]]].
  	theSP ifNil:
  		[self print: 'could not find sp; using bogus value'; cr.
+ 		 theSP := self frameReceiverLocation: theFP].
- 		 theSP := self frameReceiverOffset: theFP].
  	self printFrame: theFP WithSP: theSP.
  	frameAbove ifNotNil:
  		[self printFrameThing: 'frame pc' at: frameAbove + FoxCallerSavedIP]!

Item was changed:
  ----- Method: StackInterpreter>>printStackReferencesTo: (in category 'object memory support') -----
  printStackReferencesTo: oop
  	<api>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage ifFalse:
  				[theSP := theSP + objectMemory wordSize].
+ 			 [[theSP <= (self frameReceiverLocation: theFP)] whileTrue:
- 			 [[theSP <= (self frameReceiverOffset: theFP)] whileTrue:
  				[oop = (stackPages longAt: theSP) ifTrue:
  					[self print: 'FP: '; printHexnp: theFP; print: ' @ '; printHexnp: theSP; cr].
  				 theSP := theSP + objectMemory wordSize].
  			  (self frameHasContext: theFP) ifTrue:
  				[oop = (self frameContext: theFP) ifTrue:
  					[self print: 'FP: '; printHexnp: theFP; print: ' CTXT'; cr]].
  			  oop = (self frameMethod: theFP) ifTrue:
  				[self print: 'FP: '; printHexnp: theFP; print: ' MTHD'; cr].
  			  (callerFP := self frameCallerFP: theFP) ~= 0]
  				whileTrue:
  					[theSP := (theFP + FoxCallerSavedIP) + objectMemory wordSize.
  					 theFP := callerFP].
  			 theSP := theFP + FoxCallerSavedIP. "a.k.a. FoxCallerContext"
  			 [theSP <= thePage baseAddress] whileTrue:
  				[oop = (stackPages longAt: theSP) ifTrue:
  					[self print: 'FP: '; printHexnp: theFP; print: ' @ '; printHexnp: theSP; cr].
  				 theSP := theSP + objectMemory wordSize]]]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveVoidReceiver (in category 'system control primitives') -----
  primitiveVoidReceiver
  	"Potentially crash the VM by voiding the receiver.  A subsequent inst var
  	 access in the caller's frame should indirect through a null pointer."
  	<export: true>
+ 	stackPages longAtPointer: (self frameReceiverLocation: framePointer) put: 0!
- 	stackPages longAtPointer: (self frameReceiverOffset: framePointer) put: 0!



More information about the Vm-dev mailing list