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

commits at source.squeak.org commits at source.squeak.org
Mon Nov 16 07:12:03 UTC 2020


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

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

Name: VMMaker.oscog-eem.2885
Author: eem
Time: 15 November 2020, 11:11:53.385644 pm
UUID: 23635dc5-2413-4ea8-bc4a-29927206bb3b
Ancestors: VMMaker.oscog-eem.2884

Fix the regression in VMMaker.oscog-eem.2876.  Since pinning is potentially a become operation followForwardingPointersInStackZone: is invoked, and that crashes when stackPage is 0, is it is when snapshotting.  So the fix is to return to not pinning in postGCUpdateDisplayBits if snapshotting.

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

Item was changed:
  ----- Method: CoInterpreter>>markCogMethodsAndReferentsOnPage: (in category 'frame access') -----
  markCogMethodsAndReferentsOnPage: thePage
  	<var: #thePage type: #'StackPage *'>
+ 	| theFP callerFP cogMethod theIP |
- 	| theFP callerFP |
- 	<var: #theFP type: #'char *'>
- 	<var: #callerFP type: #'char *'>
  	<inline: false>
  	self assert: (stackPages isFree: thePage) not.
  	self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  	theFP := thePage headFP.
+ 
+ 	"If a machine code primitive is in progress then there will be a return address on top of stack
+ 	 which does not refer to the current frame's method (which is the caller of the primitive), since
+ 	 the primitive has not built a frame. It is vital that that method not be reclaimed!!!!"
+ 	theIP := (stackPages longAt: thePage headSP) asUnsignedInteger.
+ 	(theIP < objectMemory startOfMemory
+ 	 and: [theIP ~= cogit ceReturnToInterpreterPC]) ifTrue:
+ 		[self assert: (self isMachineCodeFrame: theFP).
+ 		 cogMethod := self mframeHomeMethod: theFP.
+ 		 (theIP >= cogMethod asUnsignedInteger
+ 		  and: [theIP < (cogMethod asUnsignedInteger + cogMethod blockSize)]) ifFalse:
+ 			[(cogit cogMethodContaining: theIP) ifNotNil:
+ 				[:primCogMethod| cogit markMethodAndReferents: primCogMethod]]].
+ 
- 	"Skip the instruction pointer on top of stack of inactive pages."
  	[(self isMachineCodeFrame: theFP) ifTrue:
  		[cogit markMethodAndReferents: (self mframeCogMethod: theFP)].
  	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theFP := callerFP]!

Item was changed:
  ----- Method: StackInterpreter>>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 bytecode, literal and inst var fetch and non-local return, we scan
  	 the receivers (including the stacked receiver for non-local return) and method references
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than
  	 scanning all of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #theFP type: #'char *'>
  	<var: #theIPPtr type: #usqInt>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	stackPage = 0 ifTrue: "the system must be snapshotting; nothing to do..."
+ 		[self assert: (stackPages mostRecentlyUsedPage isNil or: [stackPages mostRecentlyUsedPage isFree]).
- 		[self assert: stackPages mostRecentlyUsedPage isFree.
  		 self cCode: [] inSmalltalk: [self assert: stackPages allPagesFree].
  		 ^self].
  
  	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 theFP callerFP offset oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr asVoidPointer]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| newOop delta |
  				 newOop := objectMemory followForwarded: oop.
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := newOop - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (oop := newOop)].
  			  offset := self frameStackedReceiverOffset: theFP.
  			  oop := stackPages longAt: theFP + offset.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: theFP + offset
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asUnsignedInteger.
  				 theFP := callerFP].
  			 "And finally follow the caller context."
  			 self assert: theFP = thePage baseFP.
  			 oop := self frameCallerContext: theFP.
  			 (objectMemory isForwarded: oop) ifTrue:
  				[self frameCallerContext: theFP put: (objectMemory followForwarded: oop)]]]!

Item was changed:
  ----- Method: StackInterpreter>>postGCUpdateDisplayBits (in category 'object memory support') -----
  postGCUpdateDisplayBits
  	"Update the displayBits after a GC may have moved it.
  	 Answer if the displayBits appear valid.  The wrinkle here is that the displayBits could be a surface handle."
  	<inline: false>
  	| displayObj bitsOop bitsNow |
  	displayObj := objectMemory splObj: TheDisplay.
  	((objectMemory isPointers: displayObj)
  	 and: [(objectMemory lengthOf: displayObj) >= 4]) ifFalse:
  		[^false].
  	
  	bitsOop := objectMemory fetchPointer: 0 ofObject: displayObj.
  	(objectMemory isIntegerObject: bitsOop) ifTrue: "It's a surface; our work here is done..."
  		[^true].
  
  	self assert: ((objectMemory addressCouldBeObj: bitsOop)
  				 and: [objectMemory isWordsOrBytes: bitsOop]).
  
  	(objectMemory hasSpurMemoryManagerAPI
  	 and: [objectMemory isPinned: bitsOop]) ifFalse:
  		[bitsNow := self cCode: [objectMemory firstIndexableField: bitsOop]
  					inSmalltalk: [(objectMemory firstIndexableField: bitsOop) asInteger].
  		 displayBits ~= bitsNow ifTrue:
  			[displayBits := bitsNow.
  			 self ioNoteDisplayChanged: displayBits width: displayWidth height: displayHeight depth: displayDepth].
+ 		 (objectMemory hasSpurMemoryManagerAPI
+ 		  and: [stackPage ~= 0]) ifTrue: "If stackPage is zero we're snapshotting and now is not the time to pin."
- 		 objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[objectMemory pinObject: bitsOop]].
  	^true!



More information about the Vm-dev mailing list