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

commits at source.squeak.org commits at source.squeak.org
Thu May 26 19:11:55 UTC 2016


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

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

Name: VMMaker.oscog-eem.1870
Author: eem
Time: 26 May 2016, 12:10:14.605733 pm
UUID: c5578dcb-22a8-4798-8aa0-097f5adbb95e
Ancestors: VMMaker.oscog-eem.1868

Fix slang regression in VMMaker.oscog-eem.1868.  See MessageNode>>asTranslatorNodeIn:.

Fix ephemerons (at least for Gule's test case).  The mournQueue is of course a root for teh scavenger and so must be visited at the start of a scavenge.  Fix receiver in fireEphemeron:.

Simulator:  Make Spur clone the heap and do a lemming scavenge if leakCheckNewSpaceGC is set, just as ObjectMemory does.  Update Spur's leak checker to scan the mournQueue.

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

Item was removed:
- ----- Method: Interpreter>>primitiveAtEnd (in category 'deprecated - array and stream primitives') -----
- primitiveAtEnd
- 	"nb: This primitive was previously installed as primitive 67, but is no
- 	longer in use."
- 	| stream index limit |
- 	stream := self popStack.
- 	((objectMemory isPointers: stream)
- 			and: [(objectMemory lengthOf: stream) >= (StreamReadLimitIndex+1)])
- 		ifTrue: [index := self fetchInteger: StreamIndexIndex ofObject: stream.
- 			limit := self fetchInteger: StreamReadLimitIndex ofObject: stream]
- 		ifFalse: [self primitiveFail].
-  	self successful
- 		ifTrue: [self pushBool: (index >= limit)]
- 		ifFalse: [self unPop: 1].!

Item was changed:
  ----- Method: MessageNode>>asTranslatorNodeIn: (in category '*VMMaker-C translation') -----
  asTranslatorNodeIn: aTMethod
  	"make a CCodeGenerator equivalent of me"
  	"selector is sometimes a Symbol, sometimes a SelectorNode!!
  	On top of this, numArgs is needed due to the (truly grody) use of
  	arguments as a place to store the extra expressions needed to generate
  	code for in-line to:by:do:, etc.  see below, where it is used."
  	| rcvrOrNil sel args ifNotNilBlock |
  	rcvrOrNil := receiver ifNotNil: [receiver asTranslatorNodeIn: aTMethod].
  	(rcvrOrNil notNil
  	and: [rcvrOrNil isVariable
  	and: [rcvrOrNil name = 'super']]) ifTrue:
  		[^aTMethod superExpansionNodeFor: selector key args: arguments].
  	sel := selector isSymbol ifTrue: [selector] ifFalse: [selector key].
  	(sel == #cCode:inSmalltalk: "extracting here rather than in translation allows inlining in the block."
  	  or: [sel == #cCode:]) ifTrue:
  		[arguments first isBlockNode ifTrue:
  			[| block |
  			 ^(block := arguments first asTranslatorNodeIn: aTMethod) statements size = 1
  				ifTrue: [block statements first]
  				ifFalse: [block]].
  		 (arguments first isLiteralNode
+ 		 and: [arguments first key isString
+ 		 and: [arguments first key isEmpty]]) ifTrue:
- 		 and: [arguments first key isString]) ifTrue:
  			[^arguments first asTranslatorNodeIn: aTMethod]].
  	args := arguments
  				select: [:arg| arg notNil]
  				thenCollect: [:arg| arg asTranslatorNodeIn: aTMethod].
  	(sel = #to:by:do: and: [arguments size = 7 and: [(arguments at: 7) notNil]]) ifTrue:
  		["Restore limit expr that got moved by transformToDo:"
  		 args := {(arguments at: 7) value asTranslatorNodeIn: aTMethod. 
  				  args second.
  				  args third. "add the limit var as a hidden extra argument; we may need it later"
  				  TVariableNode new setName: arguments first key}].
  	(sel == #ifTrue:ifFalse: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifFalse:. args := {args last}].
  	(sel == #ifTrue:ifFalse: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	(sel == #ifFalse:ifTrue: and: [arguments first isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args last}].
  	(sel == #ifFalse:ifTrue: and: [arguments last isJust: NodeNil]) ifTrue:
  		[sel := #ifTrue:. args := {args first}].
  	((sel == #ifFalse: or: [sel == #or:])
  	 and: [arguments size = 2 and: [(arguments at: 2) notNil]]) ifTrue:
  		["Restore argument block that got moved by transformOr: or transformIfFalse:"
  		 args := {(arguments at: 2) asTranslatorNodeIn: aTMethod}].
  	(args size > sel numArgs and: [sel ~~ #to:by:do:]) ifTrue: "to:by:do: has iLimiT hidden in last arg"
  		["prune the extra blocks left by ifTrue:, ifFalse:, and: & or:"
  		 self assert: args size - sel numArgs = 1.
  		 self assert: (args last isStmtList
  					  and: [args last statements size = 1
  					  and: [(args last statements first isVariable
  							or: [args last statements first isConstant])
  					  and: [#('nil' true false) includes: args last statements first nameOrValue]]]).
  		 args := args first: sel numArgs].
  	"For the benefit of later passes, e.g. value: inlining,
  	 transform e ifNotNil: [:v| ...] into  v := e. v ifNotNil: [...],
  	 which in fact means transforming (v := e) ifTrue: [:v|...] into v := e. v ifTrue: [...]."
  	((sel == #ifTrue: or: [sel == #ifFalse: or: [sel == #ifTrue:ifFalse: or: [sel == #ifFalse:ifTrue:]]])
  	 and: [receiver notNil
  	 and: [receiver isAssignmentEqualsEqualsNil
  	 and: [(ifNotNilBlock := args detect: [:arg| arg isStmtList and: [arg args size = 1]] ifNone: []) notNil]]]) ifTrue:
  		[ifNotNilBlock setArguments: #().
  		 ^TStmtListNode new
  			setArguments: #()
  			statements:
  				{	receiver receiver asTranslatorNodeIn: aTMethod.
  					TSendNode new
  						setSelector: sel
  						receiver: (TSendNode new
  									setSelector: #==
  									receiver: (receiver receiver variable asTranslatorNodeIn: aTMethod)
  									arguments: {receiver arguments first asTranslatorNodeIn: aTMethod})
  						arguments: args }].
  	^TSendNode new
  		setSelector: sel
  		receiver: rcvrOrNil
  		arguments: args!

Item was changed:
+ ----- Method: Spur32BitMMLECoSimulator>>scavengingGCTenuringIf: (in category 'gc - global') -----
- ----- Method: Spur32BitMMLECoSimulator>>scavengingGCTenuringIf: (in category 'generation scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	(self leakCheckNewSpaceGC
+ 	 and: [parent isNil]) ifTrue:
+ 		[coInterpreter cr; print: 'scavenge '; print: statScavenges; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory scavengingGCTenuringIf: tenuringCriterion.
+ 		 Smalltalk garbageCollect].
- 	"Run the scavenger."
- 	"self halt: (statScavenges + 1) printString, ((statScavenges between: 9 and: 19)
- 													ifTrue: ['th']
- 													ifFalse: [#('st' 'nd' 'rd') at: (statScavenges + 1) \\ 10 ifAbsent: 'th']), ' scavenge'."
  	^super scavengingGCTenuringIf: tenuringCriterion!

Item was changed:
+ ----- Method: Spur32BitMMLESimulator>>scavengingGCTenuringIf: (in category 'gc - global') -----
- ----- Method: Spur32BitMMLESimulator>>scavengingGCTenuringIf: (in category 'generation scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	(self leakCheckNewSpaceGC
+ 	 and: [parent isNil]) ifTrue:
+ 		[coInterpreter cr; print: 'scavenge '; print: statScavenges; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory scavengingGCTenuringIf: tenuringCriterion.
+ 		 Smalltalk garbageCollect].
- 	"Run the scavenger."
- 	"self halt: (statScavenges + 1) printString, ((statScavenges between: 9 and: 19)
- 													ifTrue: ['th']
- 													ifFalse: [#('st' 'nd' 'rd') at: (statScavenges + 1) \\ 10 ifAbsent: 'th']), ' scavenge'."
- 													
- 	"statFullGCs > 0 ifTrue:
- 		[self halt]."
  	^super scavengingGCTenuringIf: tenuringCriterion!

Item was changed:
+ ----- Method: Spur64BitMMLECoSimulator>>scavengingGCTenuringIf: (in category 'gc - global') -----
- ----- Method: Spur64BitMMLECoSimulator>>scavengingGCTenuringIf: (in category 'generation scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	(self leakCheckNewSpaceGC
+ 	 and: [parent isNil]) ifTrue:
+ 		[coInterpreter cr; print: 'scavenge '; print: statScavenges; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory scavengingGCTenuringIf: tenuringCriterion.
+ 		 Smalltalk garbageCollect].
- 	"Run the scavenger."
- 	"self halt: (statScavenges + 1) printString, ((statScavenges between: 9 and: 19)
- 													ifTrue: ['th']
- 													ifFalse: [#('st' 'nd' 'rd') at: (statScavenges + 1) \\ 10 ifAbsent: 'th']), ' scavenge'."
  	^super scavengingGCTenuringIf: tenuringCriterion!

Item was changed:
+ ----- Method: Spur64BitMMLESimulator>>scavengingGCTenuringIf: (in category 'gc - global') -----
- ----- Method: Spur64BitMMLESimulator>>scavengingGCTenuringIf: (in category 'generation scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
+ 	"If we're /not/ a clone, clone the VM and push it over the cliff.
+ 	 If it survives, destroy the clone and continue.  We should be OK until next time."
+ 	(self leakCheckNewSpaceGC
+ 	 and: [parent isNil]) ifTrue:
+ 		[coInterpreter cr; print: 'scavenge '; print: statScavenges; tab; flush.
+ 		 coInterpreter cloneSimulation objectMemory scavengingGCTenuringIf: tenuringCriterion.
+ 		 Smalltalk garbageCollect].
- 	"Run the scavenger."
- 	"self halt: (statScavenges + 1) printString, ((statScavenges between: 9 and: 19)
- 													ifTrue: ['th']
- 													ifFalse: [#('st' 'nd' 'rd') at: (statScavenges + 1) \\ 10 ifAbsent: 'th']), ' scavenge'."
- 													
- 	"statFullGCs > 0 ifTrue:
- 		[self halt]."
  	^super scavengingGCTenuringIf: tenuringCriterion!

Item was added:
+ ----- Method: SpurGenerationScavenger>>copyAndForwardMourner: (in category 'scavenger') -----
+ copyAndForwardMourner: mourner
+ 	"A special version of copyAndForward: for objects in the mournQueue.  If we're
+ 	 in the good times tenuring regime then copy to futureSpace, otherwise tenure.
+ 	 Also, don't repeat any of the ephemeron processing."
+ 	<inline: false>
+ 	| bytesInObj format tenure newLocation |
+ 	self assert: ((manager isInEden: mourner) "cog methods should be excluded."
+ 				or: [manager isInPastSpace: mourner]).
+ 	bytesInObj := manager bytesInObject: mourner.
+ 	format := manager formatOf: mourner.
+ 	tenure := self shouldMournerBeTenured: mourner. "Allow Slang to inline."
+ 	newLocation := (tenure or: [futureSurvivorStart + bytesInObj > futureSpace limit])
+ 						ifTrue: [self copyToOldSpace: mourner bytes: bytesInObj format: format]
+ 						ifFalse: [self copyToFutureSpace: mourner bytes: bytesInObj].
+ 	manager forwardSurvivor: mourner to: newLocation.
+ 	"if weak or ephemeron add to the relevant list for subsequent scanning."
+ 	(manager isWeakFormat: format) ifTrue:
+ 		[self addToWeakList: mourner].
+ 	^newLocation!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavengeLoop (in category 'scavenger') -----
  scavengeLoop
  	"This is the inner loop of the main routine, scavenge.  It first scavenges the new objects immediately
  	 reachable from old ones. Then it scavenges those that are transitively reachable.  If this results in a
  	 promotion, the promotee gets remembered, and it first scavenges objects adjacent to the promotee,
  	 then scavenges the ones reachable from the promoted.  This loop continues until no more reachable
  	 objects are left.  At that point, pastSurvivorSpace is exchanged with futureSurvivorSpace.
  
  	 Notice that each pointer in a live object is inspected once and only once.  The previousRememberedSetSize
  	 and previousFutureSurvivorSpaceLimit variables ensure that no object is scanned twice, as well as
  	 detecting closure.  If this were not true, some pointers might get forwarded twice.
  
  	 An extension of the algorithm presented in David's original paper is to handle weak arrays and ephemerons.
  	 Weak arrays should not have their weak referents scavenged unless there are strong references to them.
  	 Ephemerons should fire if their key is not reachable other than from ephemerons and weak arrays.
  	 Handle this by maintaining a list for weak arrays and a list for ephemerons, which allow scavenging these
  	 objects once all other objects in new space have been scavenged, hence allowing the scavenger to
  	 detect which referents in new space of weak arrays are dead and of ephemeron keys are only live due to
  	 ephemerons.  Read the class comment for a more in-depth description of the algorithm."
  	<inline: false>
  	| previousFutureSurvivorStart firstTime |
  	self assert: futureSurvivorStart = futureSpace start. "future space should be empty at the start"
  
  	weakList := ephemeronList := nil.
  	numRememberedEphemerons := 0.
  	firstTime := true.
  	previousRememberedSetSize := 0.
  	previousFutureSurvivorStart := futureSurvivorStart.
  
  	coInterpreter initStackPageGC.
  
  	[self scavengeRememberedSetStartingAt: previousRememberedSetSize.
  	 previousRememberedSetSize := rememberedSetSize.
  	 firstTime ifTrue:
  		[coInterpreter mapInterpreterOops.
+ 		 manager mapMournQueue.
  		 manager mapExtraRoots.
  		 firstTime := false].
  	 "if nothing more copied and forwarded (or remembered by mapInterpreterOops)
  	  to scavenge, and no ephemerons to process, scavenge is done."
  	 (previousRememberedSetSize = rememberedSetSize
  	  and: [previousFutureSurvivorStart = futureSurvivorStart
  	  and: [numRememberedEphemerons = 0
  	  and: [ephemeronList isNil]]]) ifTrue:
  		[^self].
  
  	 self scavengeFutureSurvivorSpaceStartingAt: previousFutureSurvivorStart.
  	 previousFutureSurvivorStart := futureSurvivorStart.
  
  	 "no more roots created to scavenge..."
  	 previousRememberedSetSize = rememberedSetSize ifTrue:
  		[(numRememberedEphemerons = 0
  		  and: [ephemeronList isNil]) ifTrue:
  			[^self]. "no ephemerons to process, scavenge is done."
  
  		 "all reachable objects in this cycle have been promoted to futureSpace.
  		  ephemerons can now be processed."
  		 self processEphemerons]] repeat!

Item was added:
+ ----- Method: SpurGenerationScavenger>>shouldMournerBeTenured: (in category 'scavenger') -----
+ shouldMournerBeTenured: survivor
+ 	"Answer if an object in the mourn queue should be tenured.  If we're
+ 	 in the good times tenuring regime then copy to futureSpace, otherwise tenure."
+ 	^(tenureCriterion = TenureByAge and: [tenureThreshold = 0]) not!

Item was changed:
  ----- Method: SpurMemoryManager class>>initialize (in category 'class initialization') -----
  initialize
  	"SpurMemoryManager initialize"
  	BitsPerByte := 8.
  
  	"Initialize at least the become constants for the Spur bootstrap where the
  	 old ObjectMemory simulator is used before a Spur simulator is created.."
  	self initializeSpurObjectRepresentationConstants.
  
  	"Pig compact can be repeated to compact better.  Experience shows that 3 times
  	 compacts very well, desirable for snapshots.  But this is overkill for normal GCs."
  	CompactionPassesForGC := 2.
  	CompactionPassesForSnapshot := 3.
  
  	"An obj stack is a stack of objects stored in a hidden root slot, such as
  	 the markStack or the ephemeronQueue.  It is a linked list of segments,
  	 with the hot end at the head of the list.  It is a word object.  The stack
  	 pointer is in ObjStackTopx and 0 means empty.  The list goes through
  	 ObjStackNextx. We don't want to shrink objStacks, since they're used
+ 	 in GC and it's good to keep their memory around.  So unused pages
+ 	 created by popping emptied pages are kept on the ObjStackFreex list.
- 	 in GC and its good to keep their memory around.  So unused pages
- 	 created by popping emptying pages are kept on the ObjStackFreex list.
  	 ObjStackNextx must be the last field for swizzleObjStackAt:."
  	ObjStackPageSlots := 4092. "+ double header = 16k bytes per page in 32-bits"
  	ObjStackTopx := 0.
  	ObjStackMyx := 1.
  	ObjStackFreex := 2.
  	ObjStackNextx := 3.
  	ObjStackFixedSlots := 4.
  	ObjStackLimit := ObjStackPageSlots - ObjStackFixedSlots.
  	"The hiddenHootsObject contains the classTable pages and up to 8 additional objects.
  	 Currently we use four; the three objStacks, the mark stack, the weaklings and the
  	 mourn queue, and the rememberedSet."
  	MarkStackRootIndex := self basicNew classTableRootSlots.
  	WeaklingStackRootIndex := MarkStackRootIndex + 1.
  	MournQueueRootIndex := MarkStackRootIndex + 2.
  	RememberedSetRootIndex := MarkStackRootIndex + 3.
  
  	MarkObjectsForEnumerationPrimitives := false.
  
  	"The remap buffer support is for compatibility; Spur doesn't GC during allocation.
  	 Eventually this should die."
  	RemapBufferSize := 25.
  
  	"Extra roots are for plugin support."
  	ExtraRootsSize := 2048 "max. # of external roots"!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedNewSpaceObjs classIndicesShouldBeValid: classIndicesShouldBeValid
  	"Perform an integrity/leak check using the heapMap.  Assume clearLeakMapAndMapAccessibleObjects
  	 has set a bit at each (non-free) object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rememberedSet, remapBuffer and extraRootTable checking
  	 that every entry is a pointer to a header. Check that the number of roots is correct and that all
  	 rememberedSet entries have their isRemembered: flag set.  Answer if all checks pass."
  	| ok numRememberedObjectsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedObjectsInHeap := 0.
  	0 to: self numFreeLists - 1 do:
  		[:i|
  		(freeLists at: i) ~= 0 ifTrue:
  			[(heapMap heapMapAtWord: (self pointerForOop: (freeLists at: i))) ~= 0 ifTrue:
  				[coInterpreter print: 'leak in free list '; printNum: i; print: ' to non-free '; printHex: (freeLists at: i); cr.
  				 self eek.
  				 ok := false]]].
  
  	"Excuse the duplication but performance is at a premium and we avoid
  	 some tests by splitting the newSpace and oldSpace enumerations."
  	self allNewSpaceEntitiesDo:
  		[:obj| | fieldOop classIndex classOop |
  		(self isFreeObject: obj)
  			ifTrue:
  				[coInterpreter print: 'young object '; printHex: obj; print: ' is free'; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[((self isMarked: obj) not and: [excludeUnmarkedNewSpaceObjs]) ifFalse:
  					[(self isRemembered: obj) ifTrue:
  						[coInterpreter print: 'young object '; printHex: obj; print: ' is remembered'; cr.
  						 self eek.
  						 ok := false]].
  					 (self isForwarded: obj)
  						ifTrue:
  							[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  							 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  								[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  								 self eek.
  								 ok := false]]
  						ifFalse:
  							[classOop := self classOrNilAtIndex: (classIndex := self classIndexOf: obj).
  							 (classIndicesShouldBeValid
  							  and: [classOop = nilObj
  							  and: [(self isHiddenObj: obj) not]]) ifTrue:
  								[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  								 self eek.
  								 ok := false].
  							 0 to: (self numPointerSlotsOf: obj) - 1 do:
  								[:fi|
  								 fieldOop := self fetchPointer: fi ofObject: obj.
  								 (self isNonImmediate: fieldOop) ifTrue:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  										[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  										 self eek.
  										 ok := false]]]]]].
  	self allOldSpaceEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		(self isFreeObject: obj)
  			ifTrue:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0 ifTrue:
  					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' is mapped?!! '; cr.
  					 self eek.
  					 ok := false].
  				 fieldOop := self fetchPointer: self freeChunkNextIndex ofFreeChunk: obj.
  				 (fieldOop ~= 0
  				 and: [(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0]) ifTrue:
  					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ 0 = '; printHex: fieldOop; print: ' is mapped'; cr.
  					 self eek.
  					 ok := false].
  				(self isLargeFreeObject: obj) ifTrue:
  					[self freeChunkParentIndex to: self freeChunkLargerIndex do:
  						[:fi|
  						 fieldOop := self fetchPointer: fi ofFreeChunk: obj.
  						 (fieldOop ~= 0
  						 and: [(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0]) ifTrue:
  							[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is mapped'; cr.
  							 self eek.
  							 ok := false].]]]
  			ifFalse:
  				[containsYoung := false.
  				 (self isRemembered: obj) ifTrue:
  					[numRememberedObjectsInHeap := numRememberedObjectsInHeap + 1.
  					 (scavenger isInRememberedSet: obj) ifFalse:
  						[coInterpreter print: 'remembered object '; printHex: obj; print: ' is not in remembered table'; cr.
  						 self eek.
  						 ok := false]].
  				 (self isForwarded: obj)
  					ifTrue:
  						[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  						 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  							[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  							 self eek.
  							 ok := false].
  						 (self isReallyYoung: fieldOop) ifTrue:
  							[containsYoung := true]]
  					ifFalse:
  						[classOop := self classOrNilAtIndex: (classIndex := self classIndexOf: obj).
  						 (classIndicesShouldBeValid
  						  and: [classOop = nilObj
  						  and: [classIndex > self lastClassIndexPun]]) ifTrue:
  							[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  							 self eek.
  							 ok := false].
  						 0 to: (self numPointerSlotsOf: obj) - 1 do:
  							[:fi|
  							 fieldOop := self fetchPointer: fi ofObject: obj.
  							 (self isNonImmediate: fieldOop) ifTrue:
  								[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  									[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  									 self eek.
  									 ok := false].
  								 "don't be misled by CogMethods; they appear to be young, but they're not"
  								 (self isReallyYoung: fieldOop) ifTrue:
  									[containsYoung := true]]]].
  				 containsYoung ifTrue:
  					[(self isRemembered: obj) ifFalse:
  						[coInterpreter print: 'unremembered object '; printHex: obj; print: ' contains young oop(s)'; cr.
  						 self eek.
  						 ok := false]]]].
  	numRememberedObjectsInHeap ~= scavenger rememberedSetSize ifTrue:
  		[coInterpreter
  			print: 'root count mismatch. #heap roots ';
  			printNum: numRememberedObjectsInHeap;
  			print: '; #roots ';
  			printNum: scavenger rememberedSetSize;
  			cr.
  		self eek.
  		"But the system copes with overflow..."
  		self flag: 'no support for remembered set overflow yet'.
  		"ok := rootTableOverflowed and: [needGCFlag]"].
  	scavenger rememberedSetWithIndexDo:
  		[:obj :i|
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned oop in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]
  					ifFalse:
  						[(self isYoung: obj) ifTrue:
  							[coInterpreter print: 'non-root in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  							 self eek.
  							 ok := false]]]].
+ 	self objStack: mournQueue do:
+ 		[:i :page| | obj |
+ 		obj := self fetchPointer: i ofObject: page.
+ 		(obj bitAnd: self wordSize - 1) ~= 0
+ 			ifTrue:
+ 				[coInterpreter print: 'misaligned oop in mournQueue @ '; printNum: i; print: ' in '; printHex: page; print: ' = '; printHex: obj; cr.
+ 				 self eek.
+ 				 ok := false]
+ 			ifFalse:
+ 				[(excludeUnmarkedNewSpaceObjs and: [(self isYoung: obj) and: [(self isMarked: obj) not]]) ifFalse:
+ 					[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
+ 						[coInterpreter print: 'object leak in mournQueue @ '; printNum: i; print: ' in '; printHex: page; print: ' = '; printHex: obj; cr.
+ 						 self eek.
+ 						 ok := false]]]].
  	1 to: remapBufferCount do:
  		[:ri| | obj |
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	1 to: extraRootCount do:
  		[:ri| | obj |
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	^ok!

Item was added:
+ ----- Method: SpurMemoryManager>>mapMournQueue (in category 'weakness and ephemerality') -----
+ mapMournQueue
+ 	<inline: #never>
+ 	self objStack: mournQueue do:
+ 		[:i :page| | mourner |
+ 		mourner := self fetchPointer: i ofObject: page.
+ 		(self isNonImmediate: mourner) ifTrue: "someone could try and become weaklings into immediates..."
+ 			[(self isForwarded: mourner) ifTrue:
+ 				[mourner := self followForwarded: mourner].
+ 			 (scavenger isScavengeSurvivor: mourner) ifFalse:
+ 				[mourner := scavenger copyAndForwardMourner: mourner].
+ 			 "we could check for change but writes are cheasp with write buffers..."
+ 			 self storePointerUnchecked: i ofObject: page withValue: mourner]]!

Item was added:
+ ----- Method: SpurMemoryManager>>objStack:do: (in category 'obj stacks') -----
+ objStack: objStack do: aBlock
+ 	"Evaluate aBinaryBlock with all indices and pages of elements in objStack"
+ 	<inline: true>
+ 	| objStackPage |
+ 	objStack = nilObj ifTrue:
+ 		[^self].
+ 	self eassert: [self isValidObjStack: objStack].
+ 	objStackPage := objStack.
+ 	[objStackPage ~= 0] whileTrue:
+ 		[| numOnThisPage |
+ 		 numOnThisPage := self fetchPointer: ObjStackTopx ofObject: objStackPage.
+ 		 numOnThisPage + ObjStackFixedSlots - 1 to: ObjStackFixedSlots by: -1 do:
+ 			[:i| aBlock value: i value: objStackPage].
+ 		 objStackPage := self fetchPointer: ObjStackNextx ofObject: objStackPage]!

Item was changed:
  ----- Method: SpurMemoryManager>>queueMourner: (in category 'weakness and ephemerality') -----
  queueMourner: anEphemeronOrWeakArray
  	"Add the ephemeron to the queue and make it non-ephemeral, to avoid subsequent firing.
  	 Alas this means that other ephemerons on the same object not identified in this sccavenge
  	 or GC will not fire until later.  But that's life."
  	self assert: ((self isNonImmediate: anEphemeronOrWeakArray)
  				and: [(self formatOf: anEphemeronOrWeakArray) = self ephemeronFormat
  				   or: [(self formatOf: anEphemeronOrWeakArray) = self weakArrayFormat]]).
+ 	self deny: ((self formatOf: anEphemeronOrWeakArray) = self ephemeronFormat
+ 				and: [self is: anEphemeronOrWeakArray onObjStack: mournQueue]).
- 	self deny: (self is: anEphemeronOrWeakArray onObjStack: mournQueue).
  	self ensureRoomOnObjStackAt: MournQueueRootIndex.
  	self push: anEphemeronOrWeakArray onObjStack: mournQueue!

Item was changed:
  ----- Method: StackInterpreter>>fireEphemeron: (in category 'finalization') -----
  fireEphemeron: ephemeron
  	<option: #SpurObjectMemory>
+ 	objectMemory
+ 		queueMourner: ephemeron;
+ 		setFormatOf: ephemeron to: objectMemory nonIndexablePointerFormat.
- 	objectMemory queueMourner: ephemeron..
- 	self setFormatOf: ephemeron to: self nonIndexablePointerFormat.
  	self signalFinalization: ephemeron!



More information about the Vm-dev mailing list