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

commits at source.squeak.org commits at source.squeak.org
Tue Feb 16 00:07:29 UTC 2016


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

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

Name: VMMaker.oscog-eem.1680
Author: eem
Time: 16 February 2016, 4:05:15.580798 pm
UUID: 6fe34e1e-a5e0-4966-a2cd-3f21ccb0bde9
Ancestors: VMMaker.oscog-eem.1679

Spur.

Fix https://pharo.fogbugz.com/f/cases/17536/VM-Crash-when-adding-an-iVar-to-a-subclass-of-SystemAnnouncement.

When weaklings (and when ephemerons) are scan-marked forwarders must be coped with.

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

Item was changed:
  ----- Method: SpurMemoryManager>>fixFollowedField:ofObject:withInitialValue: (in category 'forwarding') -----
  fixFollowedField: fieldIndex ofObject: anObject withInitialValue: initialValue
  	"Private helper for followField:ofObject: to avoid code duplication for rare case."
  	<inline: #never>
  	| objOop |
  	self assert: (self isOopForwarded: initialValue).
+ 	"inlined followForwarded: for speed (one less test)"
+ 	objOop := initialValue.
+ 	[objOop := self fetchPointer: 0 ofMaybeForwardedObject: objOop.
+ 	 self isOopForwarded: objOop] whileTrue.
- 	objOop := self followForwarded: initialValue.
  	self storePointer: fieldIndex ofObject: anObject withValue: objOop.
  	^objOop!

Item was added:
+ ----- Method: SpurMemoryManager>>followOopField:ofObject: (in category 'forwarding') -----
+ followOopField: fieldIndex ofObject: anObject
+ 	"Make sure the oop at fieldIndex in anObject is not forwarded (follow the
+ 	 forwarder there-in if so).  Answer the (possibly followed) oop at fieldIndex."
+ 	| oop |
+ 	oop := self fetchPointer: fieldIndex ofObject: anObject.
+ 	(self isOopForwarded: oop) ifTrue:
+ 		[oop := self fixFollowedField: fieldIndex ofObject: anObject withInitialValue: oop].
+ 	^oop!

Item was added:
+ ----- Method: SpurMemoryManager>>followedKeyOfEphemeron: (in category 'object access') -----
+ followedKeyOfEphemeron: objOop
+ 	"Answer the object the ephemeron guards.  This is its first element."
+ 	self assert: ((self isNonImmediate: objOop) and: [self isEphemeron: objOop]).
+ 	^self followOopField: 0 ofObject: objOop!

Item was changed:
  ----- Method: SpurMemoryManager>>markAllUnscannedEphemerons (in category 'weakness and ephemerality') -----
  markAllUnscannedEphemerons
  	"After firing the unscanned ephemerons we must scan-mark them.
  	 The wrinkle is that doing so may add more ephemerons to the set."
  	| ptr |
  	self assert: (self noUnscannedEphemerons) not.
  	self assert: self allUnscannedEphemeronsAreActive.
  	ptr := unscannedEphemerons top - self wordSize.
  	[ptr >= unscannedEphemerons start] whileTrue:
  		[| ephemeron key |
+ 		 key := self followedKeyOfEphemeron: (ephemeron := self longAt: ptr).
+ 		 self
+ 			markAndTrace: key;
- 		 key := self keyOfEphemeron: (ephemeron := self longAt: ptr).
- 		 self markAndTrace: key;
  			markAndTrace: ephemeron.
  		 unscannedEphemerons top: unscannedEphemerons top - self wordSize.
  		 ptr < unscannedEphemerons top ifTrue:
  			["not the last entry; remove it by overwriting it with the last
  			  ephemeron (which must have been newly added by markAndTrace:)."
  			 self longAt: ptr put: (self longAt: unscannedEphemerons top)].
  		ptr := ptr - self wordSize]!

Item was changed:
  ----- Method: SpurMemoryManager>>markAndTraceWeaklingsFrom: (in category 'weakness and ephemerality') -----
  markAndTraceWeaklingsFrom: startIndex
  	"Mark weaklings on the weaklingStack, ignoring startIndex
  	 number of elements on the bottom of the stack.  Answer
  	 the size of the stack *before* the enumeration began."
  	^self objStack: weaklingStack from: startIndex do:
  		[:weakling|
+ 		 self deny: (self isForwarded: weakling).
  		 self markAndTraceClassOf: weakling.
  		"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
  		 0 to: (self numStrongSlotsOfWeakling: weakling) - 1 do:
  			[:i| | field |
+ 			field := self followObjField: i ofObject: weakling.
- 			field := self fetchPointer: i ofObject: weakling.
  			((self isImmediate: field) or: [self isMarked: field]) ifFalse:
  				[self markAndTrace: field]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>markInactiveEphemerons (in category 'weakness and ephemerality') -----
  markInactiveEphemerons
  	"Go through the unscanned ephemerons, marking the inactive ones, and
  	 removing them from the unscanned ephemerons. Answer if any inactive
  	 ones were found. We cannot fire the ephemerons until all are found to
  	 be active since scan-marking an inactive ephemeron later in the set may
  	 render a previously-observed active ephemeron as inactive."
  	| foundInactive ptr |
  	foundInactive := false.
  	ptr := unscannedEphemerons start.
  	[ptr < unscannedEphemerons top] whileTrue:
  		[| ephemeron key |
+ 		 key := self followedKeyOfEphemeron: (ephemeron := self longAt: ptr).
+ 		 ((self isImmediate: key) or: [self isMarked: key])
- 		key := self keyOfEphemeron: (ephemeron := self longAt: ptr).
- 		((self isImmediate: key) or: [self isMarked: key])
  			ifTrue:
  				[foundInactive := true.
  				 "Now remove the inactive ephemeron from the set, and scan-mark it.
  				  Scan-marking it may add more ephemerons to the set."
  				 unscannedEphemerons top: unscannedEphemerons top - self wordSize.
  				 unscannedEphemerons top > ptr ifTrue:
  					[self longAt: ptr put: (self longAt: unscannedEphemerons top)].
  				 self markAndTrace: ephemeron]
  			ifFalse:
  				[ptr := ptr + self wordSize]].
  	^foundInactive!

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: #'char *'>
- 	<var: #theIPPtr type: #usqInt>
  	<var: #callerFP type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  
  	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 ptr 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].
- 			 theIPPtr := thePage = stackPage ifTrue: [0] ifFalse: [thePage headSP asUnsignedInteger].
  			 [self assert: (thePage addressIsInPage: theFP).
+ 			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
- 			  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)].
  			  ptr := (theFP + (self frameStackedReceiverOffset: theFP)) asInteger.
  			  oop := stackPages longAt: ptr.
  			  (objectMemory isOopForwarded: oop) ifTrue:
  				[stackPages
  					longAt: ptr
  					put: (objectMemory followForwarded: oop)].
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := (theFP + FoxCallerSavedIP) asInteger.
  				 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)]]]!



More information about the Vm-dev mailing list