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

commits at source.squeak.org commits at source.squeak.org
Wed Jul 9 18:51:56 UTC 2014


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

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

Name: VMMaker.oscog-eem.811
Author: eem
Time: 9 July 2014, 11:49:23.981 am
UUID: 96eb7a61-d68a-4114-8c1a-c0a7fad3232e
Ancestors: VMMaker.oscog-eem.810

Spur:
Fix bug in old space GC processing of weaklings.  Old code
failed to trace strong references in weaklings to weaklings
in markWeaklingsAndMarkAndFireEphemerons.  Make sure
nilUnmarkedWeaklingSlotsIn: can be inlined.  Bug shows up
as crashes in Pharo Spur, Pharo making much more use of
weakness than Squeak or Newspeak.  Make

Move the scanning for young references in scavenger
processing of weaklings into processWeakSurvivor:.

Fix minor slips in allObjects & allInstancesOf: which should
only empty weaklingStack if marking.

Fix a couple of storePointer:ofObject:'s being applied to
objStacks.

Rename isReallyForwarded: to isUnambiguouslyForwarder:
and add an assert to isForwarded: to catch accidental
applications to free objects.

Fix longPrintOop: for free referents.

Slang:
Assign complex expressions to loop variables in value:
expansions.  Old code would replace variable with actual
parameter.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateValue:on:indent: (in category 'C translation') -----
  generateValue: aTSendNode on: aStream indent: level
  	"Reduce [:formal ... :formalN| body ] value: actual ... value: actualN
  	 to body with formals substituted for by actuals."
  	| substitution substitutionDict newLabels |
  	self assert: aTSendNode receiver isStmtList.
  	self assert: aTSendNode receiver args size = aTSendNode args size.
  	substitution := aTSendNode receiver copy.
  	substitution renameLabelsForInliningInto: currentMethod.
  	substitutionDict := Dictionary new: aTSendNode args size * 2.
  	aTSendNode receiver args with: aTSendNode args do:
  		[ :argName :exprNode |
+ 		exprNode isLeaf
+ 			ifTrue: [substitutionDict at: argName put: exprNode]
+ 			ifFalse:
+ 				[aStream nextPutAll: argName; nextPutAll: ' = '.
+ 				 exprNode emitCCodeAsExpressionOn: aStream level: level generator: self.
+ 				 aStream nextPut: $; ; crtab: level]].
- 		substitutionDict at: argName put: exprNode].
  	substitution
  		bindVariablesIn: substitutionDict;
  		emitCCodeOn: aStream level: level generator: self.
  	newLabels := Set withAll: currentMethod labels.
  	substitution nodesDo:
  		[:node| node isLabel ifTrue: [node label ifNotNil: [:label| newLabels add: label]]].
  	"now add the new labels so that a subsequent inline of
  	 the same block will be renamed with different labels."
  	currentMethod labels: newLabels!

Item was added:
+ ----- Method: SpurGenerationScavenger>>isMaybeOldScavengeSurvivor: (in category 'weakness and ephemerality') -----
+ isMaybeOldScavengeSurvivor: oop
+ 	"Answer whether the oop has survived a scavenge.  This version is
+ 	 for processing weak survivors and must cope with the scavenge in
+ 	 freeUnmarkedObjectsAndSortAndCoalesceFreeSpaceForPigCompact."
+ 	| target |
+ 	(manager isImmediate: oop) ifTrue:
+ 		[^true].
+ 	(manager isForwarded: oop)
+ 		ifTrue:
+ 			[target := manager followForwarded: oop.
+ 			 (manager isImmediate: oop) ifTrue:
+ 				[^true]]
+ 		ifFalse: [target := oop].
+ 	^(manager isOldObject: target)
+ 		ifTrue:
+ 			[tenureCriterion ~= MarkOnTenure
+ 			 or: [manager isMarked: target]]
+ 		ifFalse:
+ 			[manager isInFutureSpace: target]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>processWeakSurvivor: (in category 'weakness and ephemerality') -----
  processWeakSurvivor: weakObj
  	"Process a weak survivor on the weakList.  Those of its fields
  	 which have not survived the scavenge should be nilled, and if any
+ 	 are, the coInterpreter should be informed via signalFinalization:..
+ 	 Answer if the weakObj has any young referents."
+ 	| weakObjShouldMourn hasYoungReferents |
+ 	weakObjShouldMourn := hasYoungReferents := false.
+ 	"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
- 	 are, the coInterpreter should be informed via signalFinalization:."
- 	| weakObjShouldMourn |
- 	weakObjShouldMourn := false.
  	(manager numFixedSlotsOf: weakObj)
  		to: (manager numSlotsOf: weakObj) - 1
  		do: [:i| | referent |
  			referent := manager fetchPointer: i ofObject: weakObj.
  			"Referent could be forwarded due to scavenging or a become:, don't assume."
+ 			(manager isNonImmediate: referent) ifTrue:
+ 				[(manager isForwarded: referent) ifTrue:
+ 					[referent := manager followForwarded: referent.
+ 					 "weakObj is either young or already in remembered table; no need to check"
+ 					 self assert: ((manager isReallyYoungObject: weakObj)
+ 								or: [manager isRemembered: weakObj])..
+ 					 manager storePointerUnchecked: i ofObject: weakObj withValue: referent].
+ 				(self isMaybeOldScavengeSurvivor: referent)
+ 					ifTrue:
+ 						[(manager isYoungObject: referent) ifTrue:
+ 							[hasYoungReferents := true]]
+ 					ifFalse:
+ 						[weakObjShouldMourn := true.
+ 						 manager
+ 							storePointerUnchecked: i
+ 							ofObject: weakObj
+ 							withValue: manager nilObject]]].
- 			((manager isNonImmediate: referent)
- 			and: [manager isForwarded: referent]) ifTrue:
- 				[referent := manager followForwarded: referent.
- 				 (self isScavengeSurvivor: referent) ifTrue:
- 					[manager storePointer: i ofObject: weakObj withValue: referent]].
- 			(self isScavengeSurvivor: referent)
- 				ifFalse:
- 					[weakObjShouldMourn := true.
- 					 manager
- 						storePointerUnchecked: i
- 						ofObject: weakObj
- 						withValue: manager nilObject]
- 				ifTrue:
- 					[self assert: referent = (manager fetchPointer: i ofObject: weakObj)]].
  	weakObjShouldMourn ifTrue:
+ 		[coInterpreter signalFinalization: weakObj].
+ 	^hasYoungReferents!
- 		[coInterpreter signalFinalization: weakObj]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>processWeaklings (in category 'weakness and ephemerality') -----
  processWeaklings
  	"Go through the remembered set and the weak list, nilling references to
  	 any objects that didn't survive the scavenge. Read the class comment
  	 for a more in-depth description of the algorithm."
  	<inline: false>
  	| i rootObj weakCorpse weakObj |
  	self assert: self allWeakSurvivorsOnWeakList.
  	i := 0.
  	[i < rememberedSetSize] whileTrue:
  		[rootObj := rememberedSet at: i.
  		(manager isWeakNonImm: rootObj)
  			ifTrue:
+ 				["If no more referents, remove by overwriting with the last element in the set."
+ 				 (self processWeakSurvivor: rootObj)
- 				[self processWeakSurvivor: rootObj.
- 				 "If no more referents, remove by overwriting with the last element in the set."
- 				 (manager hasYoungReferents: rootObj)
  					ifFalse:
  						[manager setIsRememberedOf: rootObj to: false.
  						 i + 1 < rememberedSetSize ifTrue:
  							[rememberedSet at: i put: (rememberedSet at: rememberedSetSize - 1)].
  						 rememberedSetSize := rememberedSetSize - 1]
  					ifTrue: [i := i + 1]]
  			ifFalse: [i := i + 1]].
  	weakList ifNotNil:
  		[weakCorpse := self firstCorpse: weakList.
  		 [weakCorpse notNil] whileTrue:
  			[self assert: (manager isForwarded: weakCorpse).
  			 weakObj := manager followForwarded: weakCorpse.
+ 			 "weakObj may have been tenured..."
+ 			 ((self processWeakSurvivor: weakObj)
+ 			  and: [manager isOldObject: weakObj]) ifTrue:
+ 				[self remember: weakObj.
+ 				 manager setIsRememberedOf: weakObj to: true].
- 			 self processWeakSurvivor: weakObj.
  			 weakCorpse := self nextCorpseOrNil: weakCorpse].
  		weakList := nil]!

Item was changed:
  ----- Method: SpurMemoryManager>>allInstancesOf: (in category 'primitive support') -----
  allInstancesOf: aClass
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of instances as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| classIndex freeChunk ptr start limit count bytes |
  	classIndex := self rawHashBitsOf: aClass.
  	(classIndex = 0
  	 or: [aClass ~~ (self classOrNilAtIndex: classIndex)]) ifTrue:
  		[freeChunk := self allocateSlots: 0 format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 ^freeChunk].
  	MarkObjectsForEnumerationPrimitives ifTrue:
  		[self markObjects]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk.
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  	self allHeapEntitiesDo:
  		[:obj| "continue enumerating even if no room so as to unmark all objects."
  		 (MarkObjectsForEnumerationPrimitives
  				ifTrue: [self isMarked: obj]
  				ifFalse: [true]) ifTrue:
  			[(self isNormalObject: obj)
  				ifTrue:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[self setIsMarkedOf: obj to: false].
  					 (self classIndexOf: obj) = classIndex ifTrue:
  					 	[count := count + 1.
  						 ptr < limit ifTrue:
  							[self longAt: ptr put: obj.
  							 ptr := ptr + self bytesPerSlot]]]
  				ifFalse:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[(self isSegmentBridge: obj) ifFalse:
  							[self setIsMarkedOf: obj to: false]]]]].
  	self assert: self allObjectsUnmarked.
  	self assert: (self isEmptyObjStack: markStack).
+ 	MarkObjectsForEnumerationPrimitives
+ 		ifTrue: [self emptyObjStack: weaklingStack]
+ 		ifFalse: [self assert: (self isEmptyObjStack: weaklingStack)].
- 	self emptyObjStack: weaklingStack.
  	(count > (ptr - start / self bytesPerSlot) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeObject: freeChunk.
  		 ^self integerObjectOf: count].
  	count < self numSlotsMask ifTrue:
  		[| smallObj |
  		 smallObj := self allocateSlots: count format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 0 to: count - 1 do:
  			[:i|
  			self storePointerUnchecked: i ofObject: smallObj withValue: (self fetchPointer: i ofFreeChunk: freeChunk)].
  		 self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  		 self beRootIfOld: smallObj.
  		 self checkFreeSpace.
  		 ^smallObj].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self setOverflowNumSlotsOf: freeChunk to: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace.
  	self runLeakCheckerForFullGC: false.
  	^freeChunk
  	
  	!

Item was changed:
  ----- Method: SpurMemoryManager>>allObjects (in category 'primitive support') -----
  allObjects
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of objects as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| freeChunk ptr start limit count bytes |
  	MarkObjectsForEnumerationPrimitives ifTrue:
  		[self markObjects]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk.
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  	self allHeapEntitiesDo:
  		[:obj| "continue enumerating even if no room so as to unmark all objects."
  		 (MarkObjectsForEnumerationPrimitives
  				ifTrue: [self isMarked: obj]
  				ifFalse: [true]) ifTrue:
  			[(self isNormalObject: obj)
  				ifTrue:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[self setIsMarkedOf: obj to: false].
  					 count := count + 1.
  					 ptr < limit ifTrue:
  						[self longAt: ptr put: obj.
  						 ptr := ptr + self bytesPerSlot]]
  				ifFalse:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[(self isSegmentBridge: obj) ifFalse:
  							[self setIsMarkedOf: obj to: false]]]]].
  	self assert: self allObjectsUnmarked.
  	self assert: (self isEmptyObjStack: markStack).
+ 	MarkObjectsForEnumerationPrimitives
+ 		ifTrue: [self emptyObjStack: weaklingStack]
+ 		ifFalse: [self assert: (self isEmptyObjStack: weaklingStack)].
- 	self emptyObjStack: weaklingStack.
  	self assert: count >= self numSlotsMask.
  	(count > (ptr - start / self bytesPerSlot) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeChunkWithBytes: (self bytesInObject: freeChunk) at: (self startOfObject: freeChunk).
  		 self checkFreeSpace.
  		 ^self integerObjectOf: count].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self setOverflowNumSlotsOf: freeChunk to: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace.
  	self runLeakCheckerForFullGC: false.
  	^freeChunk
  	
  	!

Item was added:
+ ----- Method: SpurMemoryManager>>allStrongSlotsOfWeaklingAreMarked: (in category 'weakness and ephemerality') -----
+ allStrongSlotsOfWeaklingAreMarked: aWeakling
+ 	"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
+ 	0 to: (self numStrongSlotsOfWeakling: aWeakling) - 1 do:
+ 		[:i| | referent |
+ 		referent := self fetchPointer: i ofObject: aWeakling.
+ 		(self isNonImmediate: referent) ifTrue:
+ 			[(self isMarked: referent) ifFalse:
+ 				[^false]]].
+ 	^true!

Item was changed:
  ----- Method: SpurMemoryManager>>emptyObjStack: (in category 'obj stacks') -----
  emptyObjStack: objStack
  	"Remove all the entries on the stack.  Do so by setting Topx to 0
  	 on the first page, and adding all subsequent pages to the free list."
  	| nextPage nextNextPage |
  	objStack = nilObj ifTrue:
  		[^self].
  	self assert: (self isValidObjStack: objStack).
+ 	self storePointer: ObjStackTopx ofObjStack: objStack withValue: 0.
- 	self storePointer: ObjStackTopx ofObject: objStack withValue: 0.
  	nextPage := self fetchPointer: ObjStackNextx ofObject: objStack.
  	[nextPage ~= 0] whileTrue:
  		[nextNextPage := self fetchPointer: ObjStackNextx ofObject: nextPage.
  		 self storePointer: ObjStackFreex
  			ofObjStack: nextPage
  			withValue: (self fetchPointer: ObjStackFreex ofObject: objStack).
  		 self storePointer: ObjStackNextx ofObjStack: nextPage withValue: 0.
  		 self storePointer: ObjStackFreex ofObjStack: objStack withValue: nextPage.
  		 nextPage := nextNextPage].
  	self storePointer: ObjStackNextx ofObjStack: objStack withValue: 0.
  	self assert: (self isValidObjStack: objStack)!

Item was changed:
  ----- Method: SpurMemoryManager>>followForwarded: (in category 'forwarding') -----
  followForwarded: objOop
  	"Follow a forwarding pointer.  THis must be a loop because we cannot prevent forwarders to
  	 forwarders being created by lazy become.  Consider the following example by Igor Stasenko:
  		array := { a. b. c }.
  		- array at: 1 points to &a. array at: 2 points to &b. array at: 3 points to &c
  		a becomeForward: b
  		- array at: 1 still points to &a. array at: 2 still points to &b. array at: 3 still points to &c
  		b becomeForward: c.
  		- array at: 1 still points to &a. array at: 2 still points to &b. array at: 3 still points to &c
  		- when accessing array first one has to follow a forwarding chain:
  		&a -> &b -> c"
  	<api>
  	| referent |
+ 	self assert: (self isUnambiguouslyForwarder: objOop).
- 	self assert: (self isReallyForwarded: objOop).
  	referent := self fetchPointer: 0 ofMaybeForwardedObject: objOop.
  	[(self isOopForwarded: referent)] whileTrue:
  		[referent := self fetchPointer: 0 ofMaybeForwardedObject: referent].
  	^referent!

Item was changed:
  ----- Method: SpurMemoryManager>>isForwarded: (in category 'object testing') -----
  isForwarded: objOop
  	"Answer if objOop is that if a forwarder.  Take advantage of isForwardedObjectClassIndexPun
  	 being a power of two to generate a more efficient test than the straight-forward
  		(self classIndexOf: objOop) = self isForwardedObjectClassIndexPun
  	 at the cost of this being ambiguous with free chunks.  So either never apply this to free chunks
  	 or guard with (self isFreeObject: foo) not.  So far the idiom has been to guard with isFreeObject:"
  	<api>
+ 	self assert: (self isFreeObject: objOop) not.
  	^(self longAt: objOop) noMask: self classIndexMask - self isForwardedObjectClassIndexPun!

Item was removed:
- ----- Method: SpurMemoryManager>>isReallyForwarded: (in category 'object testing') -----
- isReallyForwarded: objOop
- 	"This version is for asserts.  It does not take advantage of the power-of0two optimization
- 	 in isForwarded:."
- 	<api>
- 	^(self classIndexOf: objOop) = self isForwardedObjectClassIndexPun!

Item was added:
+ ----- Method: SpurMemoryManager>>isUnambiguouslyForwarder: (in category 'object testing') -----
+ isUnambiguouslyForwarder: objOop
+ 	"This version is private to SpurMemoryManager (for asserts, etc).  It does not
+ 	 take advantage of the power-of0two optimization in isForwarded:."
+ 	<api>
+ 	^(self classIndexOf: objOop) = self isForwardedObjectClassIndexPun!

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 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 fetchPointer: i ofObject: weakling.
  			((self isImmediate: field) or: [self isMarked: field]) ifFalse:
  				[self markAndTrace: field]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>markWeaklingsAndMarkAndFireEphemerons (in category 'gc - global') -----
  markWeaklingsAndMarkAndFireEphemerons
  	"After the initial scan-mark is complete ephemerons can be processed.
  	 Weaklings have accumulated on the weaklingStack, but more may be
  	 uncovered during ephemeron processing.  So trace the strong slots
  	 of the weaklings, and as ephemerons are processed ensure any newly
  	 reached weaklings are also traced."
  	| numTracedWeaklings |
  	<inline: false>
  	numTracedWeaklings := 0.
  	[coInterpreter markAndTraceUntracedReachableStackPages.
  	 coInterpreter markAndTraceMachineCodeOfMarkedMethods.
+ 	 "Make sure all reached weaklings have their string slots traced before firing ephemerons..."
+ 	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
+ 	  (self sizeOfObjStack: weaklingStack) > numTracedWeaklings] whileTrue.
- 	 numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
  	 self noUnscannedEphemerons ifTrue:
  		[coInterpreter
  			markAndTraceUntracedReachableStackPages;
  	 		markAndTraceMachineCodeOfMarkedMethods;
  			freeUntracedStackPages;
  			freeUnmarkedMachineCode.
  		 ^self].
  	 self markInactiveEphemerons ifFalse:
  		[self fireAllUnscannedEphemerons].
  	 self markAllUnscannedEphemerons]
  		repeat!

Item was changed:
  ----- Method: SpurMemoryManager>>nilUnmarkedWeaklingSlots (in category 'weakness and ephemerality') -----
  nilUnmarkedWeaklingSlots
  	"Nil the unmarked slots in the weaklings on the
  	 weakling stack, finalizing those that lost references.
  	 Finally, empty the weaklingStack."
  	<inline: false>
  	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'nilling...'; flush].
  	self assert: self allOldMarkedWeakObjectsOnWeaklingStack.
  	weaklingStack = nilObj ifTrue:
  		[^self].
  	self objStack: weaklingStack from: 0 do:
+ 		[:weakling| | anyUnmarked |
+ 		anyUnmarked := self nilUnmarkedWeaklingSlotsIn: weakling.
+ 		anyUnmarked ifTrue:
- 		[:weakling|
- 		(self nilUnmarkedWeaklingSlotsIn: weakling) ifTrue:
  			[coInterpreter signalFinalization: weakling]].
  	self emptyObjStack: weaklingStack!

Item was changed:
  ----- Method: SpurMemoryManager>>nilUnmarkedWeaklingSlotsIn: (in category 'weakness and ephemerality') -----
  nilUnmarkedWeaklingSlotsIn: aWeakling
  	"Nil the unmarked slots in aWeakling and
  	 answer if any unmarked slots were found."
+ 	<inline: true>
  	| anyUnmarked |
  	anyUnmarked := false.
+ 	self assert: (self allStrongSlotsOfWeaklingAreMarked: aWeakling).
+ 	"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
  	(self numStrongSlotsOfWeakling: aWeakling) to: (self numSlotsOf: aWeakling) - 1 do:
  		[:i| | referent |
  		referent := self fetchPointer: i ofObject: aWeakling.
+ 		(self isNonImmediate: referent) ifTrue:
+ 			[(self isUnambiguouslyForwarder: referent) ifTrue:
+ 				[referent := self fixFollowedField: i ofObject: aWeakling withInitialValue: referent].
+ 			 ((self isImmediate: referent) or: [self isMarked: referent]) ifFalse:
+ 				[self storePointerUnchecked: i ofObject: aWeakling withValue: nilObj.
+ 				 anyUnmarked := true]]].
- 		((self isNonImmediate: referent)
- 		 and: [(self isFreeObject: referent) not
- 		 and: [self isForwarded: referent]]) ifTrue:
- 			[referent := self fixFollowedField: i ofObject: aWeakling withInitialValue: referent].
- 		((self isImmediate: referent) or: [self isMarked: referent]) ifFalse:
- 			[self storePointerUnchecked: i ofObject: aWeakling withValue: nilObj.
- 			 anyUnmarked := true]].
  	^anyUnmarked!

Item was changed:
  ----- Method: SpurMemoryManager>>numberOfForwarders (in category 'debug support') -----
  numberOfForwarders
  	| n |
  	n := 0.
  	self allHeapEntitiesDo:
  		[:o|
+ 		(self isUnambiguouslyForwarder: o) ifTrue:
- 		((self isForwarded: o) and: [(self isFreeObject: o) not]) ifTrue:
  			[n := n + 1]].
  	^n!

Item was changed:
  ----- Method: SpurMemoryManager>>popObjStack: (in category 'obj stacks') -----
  popObjStack: objStack
  	| topx top nextPage myx |
  	self assert: (self isValidObjStack: objStack).
  	topx := self fetchPointer: ObjStackTopx ofObject: objStack.
  	topx = 0 ifTrue:
  		[self assert: (self fetchPointer: ObjStackNextx ofObject: objStack) = 0.
  		 self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
  			inSmalltalk:
  				[(self fetchPointer: ObjStackMyx ofObject: objStack) = MarkStackRootIndex ifTrue:
  					[MarkStackRecord ifNotNil:
  						[MarkStackRecord addLast: {#EMPTY. nil}]]].
  		^nil].
  	topx := topx - 1.
  	top := self fetchPointer: topx + ObjStackFixedSlots ofObject: objStack.
  	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
  		inSmalltalk:
  			[(self fetchPointer: ObjStackMyx ofObject: objStack) = MarkStackRootIndex ifTrue:
  				[MarkStackRecord ifNotNil:
  					[(MarkStackRecord last first = #push and: [MarkStackRecord last last = top])
  						ifTrue: [MarkStackRecord removeLast]
  						ifFalse: [MarkStackRecord addLast: {#pop. top}]]]].
+ 	self storePointer: ObjStackTopx ofObjStack: objStack withValue: topx.
- 	self storePointer: ObjStackTopx ofObject: objStack withValue: topx.
  	(topx = 0
  	 and: [(nextPage := self fetchPointer: ObjStackNextx ofObject: objStack) ~= 0])
  		ifTrue:
  			[self storePointer: ObjStackFreex ofObjStack: nextPage withValue: objStack.
  			 self storePointer: ObjStackNextx ofObjStack: objStack withValue: 0.
  			 myx := self fetchPointer: ObjStackMyx ofObject: objStack.
  			 self updateRootOfObjStackAt: myx with: nextPage.
  			 self assert: (self isValidObjStack: nextPage)]
  		ifFalse:
  			[self assert: (self isValidObjStack: objStack)].
  	^top!

Item was added:
+ ----- Method: SpurMemoryManager>>sizeOfObjStack: (in category 'obj stacks') -----
+ sizeOfObjStack: objStack
+ 	| total objStackPage |
+ 	objStack = nilObj ifTrue: [^0].
+ 	total := self fetchPointer: ObjStackTopx ofObject: objStack.
+ 	objStackPage := objStack.
+ 	[objStackPage := self fetchPointer: ObjStackNextx ofObject: objStackPage.
+ 	 objStackPage ~= 0] whileTrue:
+ 		[total := total + ObjStackLimit.
+ 		 self assert: (self fetchPointer: ObjStackTopx ofObject: objStackPage) = ObjStackLimit].
+ 	^total!

Item was changed:
  ----- Method: StackInterpreter>>printOopShortInner: (in category 'debug printing') -----
  printOopShortInner: oop
  	| classOop name nameLen |
  	<var: #name type: #'char *'>
  	<inline: true>
  	(objectMemory isImmediate: oop) ifTrue:
  		[(objectMemory isImmediateCharacter: oop) ifTrue:
  			[^self
  				printChar: $$;
  				printChar: (objectMemory characterValueOf: oop);
  				printChar: $(;
  				printHex: (objectMemory integerValueOf: oop);
  				printChar: $)].
  		^self
  			printNum: (objectMemory integerValueOf: oop);
  			printChar: $(;
  			printHex: (objectMemory integerValueOf: oop);
  			printChar: $)].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^self print: ((oop bitAnd: objectMemory allocationUnit - 1) ~= 0
  						ifTrue: [' is misaligned']
  						ifFalse: [self whereIs: oop])].
+ 	(objectMemory isFreeObject: oop) ifTrue:
+ 		[^self print: ' is a free chunk'].
+ 	(objectMemory isForwarded: oop) ifTrue:
+ 		[^self print: ' is a forwarder to '; printHex: (objectMemory followForwarded: oop)].
- 	(objectMemory isOopForwarded: oop) ifTrue:
- 		[^self printHex: oop; print: ' is a forwarder to '; printHex: (objectMemory followForwarded: oop)].
  	(self isFloatObject: oop) ifTrue:
  		[^self printFloat: (self dbgFloatValueOf: oop)].
  	classOop := objectMemory fetchClassOfNonImm: oop.
  	(objectMemory addressCouldBeObj: classOop) ifFalse:
  		[^self print: 'a ??'].
  	(objectMemory numSlotsOf: classOop) = metaclassNumSlots ifTrue:
  		[^self printNameOfClass: oop count: 5].
  	oop = objectMemory nilObject ifTrue: [^self print: 'nil'].
  	oop = objectMemory trueObject ifTrue: [^self print: 'true'].
  	oop = objectMemory falseObject ifTrue: [^self print: 'false'].
  	nameLen := self lengthOfNameOfClass: classOop.
  	nameLen = 0 ifTrue: [^self print: 'a ??'].
  	name := self nameOfClass: classOop.
  	nameLen = 10 ifTrue:
  		[(self str: name n: 'ByteString' cmp: 10) = 0 "strncmp is weird" ifTrue:
  			[^self printChar: $'; printStringOf: oop; printChar: $'].
  		 (self str: name n: 'ByteSymbol' cmp: 10) = 0 "strncmp is weird" ifTrue:
  			[self printChar: $#; printStringOf: oop. ^self]].
  	(nameLen = 9 and: [(self str: name n: 'Character' cmp: 9) = 0]) ifTrue:
  		[^self printChar: $$; printChar: (objectMemory integerValueOf: (objectMemory fetchPointer: 0 ofObject: oop))].
  	self print: 'a(n) '.
  	self
  		cCode: [0 to: nameLen - 1 do: [:i| self printChar: (name at: i)]]
  		inSmalltalk:
  			[name isString
  				ifTrue: [self print: name]
  				ifFalse: [0 to: nameLen - 1 do: [:i| self printChar: (name at: i)]]].
  	"Try to spot association-like things; they're all subclasses of LookupKey"
  	((objectMemory instanceSizeOf: classOop) = (ValueIndex + 1)
  	 and: [(self superclassOf: classOop) = (self superclassOf: (objectMemory fetchClassOfNonImm: (objectMemory splObj: SchedulerAssociation)))
  	 and: [objectMemory isBytes: (objectMemory fetchPointer: KeyIndex ofObject: oop)]]) ifTrue:
  		[self space;
  			printOopShort: (objectMemory fetchPointer: KeyIndex ofObject: oop);
  			print: ' -> ';
  			printHex: (objectMemory fetchPointer: ValueIndex ofObject: oop)]!



More information about the Vm-dev mailing list