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

commits at source.squeak.org commits at source.squeak.org
Fri Oct 18 00:35:28 UTC 2013


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

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

Name: VMMaker.oscog-eem.466
Author: eem
Time: 17 October 2013, 5:32:24.704 pm
UUID: dc4753dd-5258-42e3-9e41-35f8f037cd01
Ancestors: VMMaker.oscog-eem.465

Commit a barely functional markAndTrace: using a mark stack.

Introduce an obj stack datatype, a stack composed of pages that
grows but does not release memory back on shrink (when should it
do that?).  Use this for the mark stack and the ephemeron queue.

Add SpurContiguousObjStack and use it for the unscanned
ephemerons during global and/or incremental  gc.

Re-categorize the GC methods to group global, scavenging and
incremental GC together.

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

Item was changed:
  ----- Method: Spur32BitMemoryManager>>setIsMarkedOf:to: (in category 'header access') -----
  setIsMarkedOf: objOop to: aBoolean
  	self flag: #endianness.
  	self longAt: objOop + 4
  		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop + 4) bitOr: 1 << self markedBitHalfShift]
+ 				ifFalse: [(self longAt: objOop + 4) bitAnd: (1 << self markedBitHalfShift) bitInvert32])!
- 				ifTrue: [(self longAt: objOop) bitOr: 1 << self markedBitHalfShift]
- 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self markedBitHalfShift) bitInvert32])!

Item was added:
+ SpurNewSpaceSpace subclass: #SpurContiguousObjStack
+ 	instanceVariableNames: 'top'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!

Item was added:
+ ----- Method: SpurContiguousObjStack>>top (in category 'accessing') -----
+ top
+ 	"Answer the value of top"
+ 
+ 	^ top!

Item was added:
+ ----- Method: SpurContiguousObjStack>>top: (in category 'accessing') -----
+ top: anObject
+ 	"Set the value of top"
+ 
+ 	^top := anObject!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	^{	SpurGenerationScavenger. SpurNewSpaceSpace.
+ 		SpurSegmentManager. SpurSegmentInfo.
+ 		SpurContiguousObjStack }!
- 		SpurSegmentManager. SpurSegmentInfo }!

Item was changed:
  ----- Method: SpurMemoryManager class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	self declareCAsOop: #(	memory freeStart scavengeThreshold newSpaceLimit pastSpaceStart
  							lowSpaceThreshold freeOldSpaceStart endOfMemory sortedFreeChunks)
  		in: aCCodeGenerator.
  	self declareCAsUSqLong: (self allInstVarNames select: [:ivn| ivn endsWith: 'Usecs'])
  		in: aCCodeGenerator.
  	aCCodeGenerator
  		var: #freeLists type: #'sqInt *';
+ 		var: #classTableBitmap type: #'unsigned char *';
+ 		var: #unscannedEphemerons type: #SpurContiguousObjStack.
- 		var: #classTableBitmap type: #'unsigned char *'.
  	aCCodeGenerator
  		var: #remapBuffer
  		declareC: 'sqInt remapBuffer[RemapBufferSize + 1 /* ', (RemapBufferSize + 1) printString, ' */]'.
  	aCCodeGenerator
  		var: #extraRoots
  		declareC: 'sqInt *extraRoots[ExtraRootsSize + 1 /* ', (ExtraRootsSize + 1) printString, ' */]'.!

Item was changed:
  ----- Method: SpurMemoryManager class>>initialize (in category 'class initialization') -----
  initialize
+ 	"SpurMemoryManager initialize"
  	BitsPerByte := 8.
  
+ 	"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 its good to keep their memory around.  So unused pages
+ 	 created by popping emptying pages are kept on the ObjStackFreex list."
+ 	ObjStackPageSlots := 4092. "+ double header = 16k bytes per page in 32-bits"
+ 	ObjStackFixedSlots := 3.
+ 	ObjStackTopx := 0.
+ 	ObjStackFreex := 1.
+ 	ObjStackNextx := 2.
+ 	ObjStackLimit := ObjStackPageSlots - ObjStackFixedSlots.
+ 	"There are currently two obj stacks, the mark stack and the ephemeron queue."
+ 	MarkStackRootIndex := self basicNew classTableRootSlots.
+ 	EphemeronQueueRootIndex := MarkStackRootIndex + 1.
+ 
- 	"SpurMemoryManager initialize"
  	CheckObjectOverwrite := true.
  
  	"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 added:
+ ----- Method: SpurMemoryManager>>ensureAllMarkBitsAreZero (in category 'gc - incremental') -----
+ ensureAllMarkBitsAreZero
+ 	"If the incremental collector is running mark bits may be set; stop it and clear them if necessary."
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SpurMemoryManager>>ensureRoomOnObjStackAtIndex: (in category 'obj stacks') -----
+ ensureRoomOnObjStackAtIndex: objStackRootIndex
+ 	"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 its good to keep their memory around.  So unused pages
+ 	 created by popping emptying pages are kept on the ObjStackFreex list."
+ 	| stackOrNil freeOrNewPage |
+ 	stackOrNil := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
+ 	(stackOrNil = nilObj
+ 	 or: [(self fetchPointer: ObjStackTopx ofObject: stackOrNil) >= ObjStackLimit]) ifTrue:
+ 		[freeOrNewPage := self fetchPointer: ObjStackFreex ofObject: stackOrNil.
+ 		 freeOrNewPage ~= 0
+ 			ifTrue: "the free page list is always on the new page."
+ 				[self storePointerUnchecked: ObjStackFreex ofObject: stackOrNil withValue: 0]
+ 			ifFalse:
+ 				[freeOrNewPage := self allocateSlotsInOldSpace: ObjStackPageSlots
+ 										format: self wordIndexableFormat
+ 										classIndex: self wordSizeClassIndexPun.
+ 				 freeOrNewPage ifNil: [self error: 'no memory to allocate or extend obj stack'].
+ 				 self storePointerUnchecked: ObjStackFreex ofObject: freeOrNewPage withValue: 0].
+ 		marking ifTrue: [self setIsMarkedOf: freeOrNewPage to: true].
+ 		self storePointerUnchecked: ObjStackNextx ofObject: freeOrNewPage withValue: stackOrNil;
+ 			storePointerUnchecked: ObjStackTopx ofObject: freeOrNewPage withValue: 0;
+ 			storePointerUnchecked: objStackRootIndex ofObject: hiddenRootsObj withValue: freeOrNewPage.
+ 		self assert: (self isValidObjStackAt: objStackRootIndex).
+ 		^freeOrNewPage].
+ 	self assert: (self isValidObjStackAt: objStackRootIndex).
+ 	^stackOrNil!

Item was changed:
+ ----- Method: SpurMemoryManager>>ephemeronQueue (in category 'gc - global') -----
- ----- Method: SpurMemoryManager>>ephemeronQueue (in category 'garbage collection') -----
  ephemeronQueue
+ 	^self fetchPointer: EphemeronQueueRootIndex ofObject: hiddenRootsObj!
- 	"The ephemeron queue is the first hidden root after the class table pages."
- 	^self fetchPointer: self numClassTablePages ofObject: hiddenRootsObj!

Item was changed:
+ ----- Method: SpurMemoryManager>>ephemeronQueue: (in category 'gc - global') -----
- ----- Method: SpurMemoryManager>>ephemeronQueue: (in category 'garbage collection') -----
  ephemeronQueue: anObject
+ 	self storePointer: EphemeronQueueRootIndex ofObject: hiddenRootsObj withValue: anObject!
- 	"The ephemeron queue is the first hidden root after the class table pages."
- 	self storePointer: self numClassTablePages ofObject: hiddenRootsObj withValue: anObject!

Item was added:
+ ----- Method: SpurMemoryManager>>findLargestFreeChunk (in category 'free space') -----
+ findLargestFreeChunk
+ 	"Answer, but do not remove, the largest free chunk in the free lists."
+ 	| treeNode childNode |
+ 	treeNode := freeLists at: 0.
+ 	treeNode = 0 ifTrue:
+ 		[^nil].
+ 	[self assert: (self isValidFreeObject: treeNode).
+ 	 childNode := self fetchPointer: self freeChunkLargerIndex ofFreeChunk: treeNode.
+ 	 childNode ~= 0] whileTrue:
+ 		[treeNode := childNode].
+ 	^treeNode!

Item was changed:
+ ----- Method: SpurMemoryManager>>flushNewSpace (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>flushNewSpace (in category 'generation scavenging') -----
  flushNewSpace
  	| savedTenuringThreshold |
  	savedTenuringThreshold := scavenger getRawTenuringThreshold.
  	scavenger setRawTenuringThreshold: newSpaceLimit.
  	self scavengingGCTenuringIf: TenureByAge.
  	scavenger setRawTenuringThreshold: savedTenuringThreshold.
  	self assert: scavenger rememberedSetSize = 0.
  	self assert: pastSpaceStart = scavenger pastSpace start.
  	self assert: freeStart = scavenger eden start!

Item was changed:
+ ----- Method: SpurMemoryManager>>flushNewSpaceInstancesOf: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>flushNewSpaceInstancesOf: (in category 'generation scavenging') -----
  flushNewSpaceInstancesOf: aClass
  	| classIndex |
  	classIndex := self rawHashBitsOf: aClass.
  	classIndex = 0 ifTrue: "no instances; nothing to do"
  		[^self].
  	scavenger tenuringClassIndex: classIndex.
  	self scavengingGCTenuringIf: TenureByClass.
  	self assert: (self existInstancesInNewSpaceOf: aClass) not!

Item was added:
+ ----- Method: SpurMemoryManager>>fullGC (in category 'gc - global') -----
+ fullGC
+ 	^self globalGarbageCollect!

Item was changed:
+ ----- Method: SpurMemoryManager>>fullGCLock (in category 'gc - global') -----
- ----- Method: SpurMemoryManager>>fullGCLock (in category 'garbage collection') -----
  fullGCLock
  	"Spur never has a need to lock GC because it does not move pinned objects."
  	^0!

Item was added:
+ ----- Method: SpurMemoryManager>>globalGarbageCollect (in category 'gc - global') -----
+ globalGarbageCollect
+ 	self markObjects.
+ 	self freeUnmarkedObjects.
+ 	self exactFitCompact!

Item was changed:
  ----- Method: SpurMemoryManager>>hiddenRootsObj: (in category 'class table') -----
  hiddenRootsObj: anOop
  	hiddenRootsObj := anOop.
- 	classTableFirstPage := self fetchPointer: 0 ofObject: hiddenRootsObj.
- 	self assert: (self numSlotsOf: hiddenRootsObj) = (self classTableRootSlots + self hiddenRootSlots).
- 	self assert: (self numSlotsOf: classTableFirstPage) - 1 = self classTableMinorIndexMask.
  	self cCode: [self assert: self validClassTableRootPages]
  		inSmalltalk: [numClassTablePages ifNotNil:
  						[self assert: self validClassTableRootPages]]..
+ 	classTableFirstPage := self fetchPointer: 0 ofObject: hiddenRootsObj.
+ 	self assert: (self numSlotsOf: classTableFirstPage) - 1 = self classTableMinorIndexMask.
  	"Set classTableIndex to the start of the last used page (excepting first page).
  	 Set numClassTablePages to the number of used pages."
  	numClassTablePages := self classTableRootSlots.
  	2 to: numClassTablePages - 1 do:
  		[:i|
  		(self fetchPointer: i ofObject: hiddenRootsObj) = nilObj ifTrue:
  			[numClassTablePages := i.
  			 classTableIndex := (numClassTablePages - 1 max: 1) << self classTableMajorIndexShift.
  			 ^self]].
  	"no unused pages; set it to the start of the second page."
  	classTableIndex := 1 << self classTableMajorIndexShift!

Item was changed:
+ ----- Method: SpurMemoryManager>>incrementalGC (in category 'gc - global') -----
- ----- Method: SpurMemoryManager>>incrementalGC (in category 'garbage collection') -----
  incrementalGC
  	self shouldNotImplement!

Item was changed:
  ----- Method: SpurMemoryManager>>initialize (in category 'initialization') -----
  initialize
  	"We can put all initializations that set something to 0 or to false here.
  	 In C all global variables are initialized to 0, and 0 is false."
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := extraRootCount := 0. "see below"
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
+ 	needGCFlag := signalLowSpace := scavengeInProgress := marking := false.
- 	needGCFlag := signalLowSpace := scavengeInProgress := false.
  	becomeEffectsFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statGCEndUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  	statGrowMemory := statShrinkMemory := statRootTableCount := statTenures := statSurvivorCount := 0.
  	statRootTableOverflows := statSweepCount := statMarkCount := statSpecialMarkCount := statMkFwdCount := 0.
  
+ 	"We can initialize things that are allocated but are lazily initialized."
+ 	unscannedEphemerons := SpurContiguousObjStack new.
+ 
  	"we can initialize things that are virtual in C."
  	scavenger := SpurGenerationScavengerSimulator new manager: self; yourself.
  	segmentManager := SpurSegmentManager new manager: self; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := self wordSize = 4 ifTrue: [CogCheck32BitHeapMap new].
  
  	"N.B. We *don't* initialize extraRoots because we don't simulate it."!

Item was added:
+ ----- Method: SpurMemoryManager>>initializeMarkStack (in category 'gc - global') -----
+ initializeMarkStack
+ 	self ensureRoomOnObjStackAtIndex: MarkStackRootIndex!

Item was changed:
+ ----- Method: SpurMemoryManager>>initializeNewSpaceVariables (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>initializeNewSpaceVariables (in category 'generation scavenging') -----
  initializeNewSpaceVariables
  	startOfMemory ifNotNil: "true in bootstrap"
  		[^self].
  	freeStart := scavenger eden start.
  	pastSpaceStart := scavenger pastSpace start.
  	scavengeThreshold := scavenger eden limit
  							- (scavenger edenBytes / 64)
  							- coInterpreter interpreterAllocationReserveBytes.
  	startOfMemory := scavenger pastSpace start min: scavenger futureSpace start.
  	self assert: startOfMemory < scavenger eden start.
  	self initSpaceForAllocationCheck: (self addressOf: scavenger eden)!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory is initially set (by the image-reading code) to the end of the last object in the image. Initialization redefines endOfMemory to be the end of the object allocation area based on the total available memory, but reserving some space for forwarding blocks."
  	"Assume: image reader initializes the following variables:
  		memory
  		memoryLimit
  		specialObjectsOop
  		lastHash
  	"
  	<inline: false>
  	| freeListObj |
  	"Catch mis-initializations leading to bad translations to C"
  	self assert: BaseHeaderSize = self baseHeaderSize.
  
  	segmentManager adjustSegmentSwizzlesBy: bytesToShift.
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
  
  	segmentManager numSegments > 0 "false if Spur image bootstrap"
  		ifTrue: [specialObjectsOop := segmentManager swizzleObj: specialObjectsOop]
  		ifFalse: [self assert: bytesToShift = 0].
  
  	"heavily used special objects"
  	nilObj		:= self splObj: NilObject.
  	falseObj	:= self splObj: FalseObject.
  	trueObj		:= self splObj: TrueObject.
  
  	"In Cog we insist that nil, true & false are next to each other (Cogit generates tighter
  	 conditional branch code as a result).  In addition, Spur places the free lists and
  	 class table root page immediately following them."
  	self assert: nilObj = newSpaceLimit.
  	self assert: falseObj = (self objectAfter: nilObj).
  	self assert: trueObj = (self objectAfter: falseObj).
  	freeListObj := self objectAfter: trueObj.
  	self reInitializeClassTablePostLoad: (self objectAfter: freeListObj).
  	self initializeFreeSpacePostLoad: freeListObj.
+ 	self swizzleObjStack: MarkStackRootIndex.
+ 	self swizzleObjStack: EphemeronQueueRootIndex.
  
  	segmentManager collapseSegmentsPostSwizzle.
  
  	self initializeNewSpaceVariables.
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart"
  
  	"These defaults should depend on machine size; e.g. too small on a powerful laptop, too big on a Pi."
  	growHeadroom := 8*1024*1024.		"headroom when growing"
  	shrinkThreshold := 16*1024*1024.		"free space before shrinking"!

Item was added:
+ ----- Method: SpurMemoryManager>>initializeUnscannedEphemerons (in category 'gc - global') -----
+ initializeUnscannedEphemerons
+ 	"Initialize unscannedEphemerons to use the largest free chunk
+ 	 or unused eden space, which ever is the larger."
+ 	
+ 	| largestFree sizeOfUnusedEden |
+ 	largestFree := self findLargestFreeChunk.
+ 	sizeOfUnusedEden := scavenger eden limit - freeStart.
+ 	(largestFree notNil
+ 	 and: [(self numSlotsOfAny: largestFree) > (sizeOfUnusedEden / self wordSize)])
+ 		ifTrue:
+ 			[unscannedEphemerons
+ 				start: largestFree + self baseHeaderSize;
+ 				limit: (self addressAfter: largestFree)]
+ 		ifFalse:
+ 			[unscannedEphemerons
+ 				start: freeStart;
+ 				limit: scavenger eden limit].
+ 	unscannedEphemerons top: unscannedEphemerons start!

Item was changed:
+ ----- Method: SpurMemoryManager>>isScavengeSurvivor: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>isScavengeSurvivor: (in category 'generation scavenging') -----
  isScavengeSurvivor: oop
  	<doNotGenerate>
  	^scavenger isScavengeSurvivor: oop!

Item was added:
+ ----- Method: SpurMemoryManager>>isValidObjStackAt: (in category 'obj stacks') -----
+ isValidObjStackAt: objStackRootIndex
+ 	"Answer if the obj stack at objStackRootIndex is valid."
+ 	| stackOrNil |
+ 	stackOrNil := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
+ 	^stackOrNil = nilObj
+ 	  or: [self isValidObjStackPage: stackOrNil firstPage: true]!

Item was added:
+ ----- Method: SpurMemoryManager>>isValidObjStackPage:firstPage: (in category 'obj stacks') -----
+ isValidObjStackPage: objStackPage firstPage: isFirstPage
+ 	"Answer if the obj stack at stackRootIndex is valid."
+ 	| freeOrNextPage index |
+ 	<inline: false>
+ 	(self numSlotsOfAny: objStackPage) ~= ObjStackPageSlots ifTrue: [^false].
+ 	freeOrNextPage := self fetchPointer: ObjStackFreex ofObject: objStackPage.
+ 	freeOrNextPage ~= 0 ifTrue:
+ 		[isFirstPage ifFalse: [^false].
+ 		 (self isValidObjStackPage: freeOrNextPage firstPage: false) ifFalse:
+ 			[^false]].
+ 	index := self fetchPointer: ObjStackTopx ofObject: objStackPage.
+ 	(index between: 0 and: ObjStackLimit) ifFalse: [^false].
+ 	freeOrNextPage := self fetchPointer: ObjStackNextx ofObject: objStackPage.
+ 	^freeOrNextPage = 0
+ 	  or: [self isValidObjStackPage: objStackPage firstPage: false]!

Item was changed:
+ ----- Method: SpurMemoryManager>>mapExtraRoots (in category 'gc - global') -----
- ----- Method: SpurMemoryManager>>mapExtraRoots (in category 'garbage collection') -----
  mapExtraRoots
  	self assert: remapBufferCount = 0.
  	1 to: extraRootCount do:
  		[:i | | oop |
  		oop := (extraRoots at: i) at: 0.
  		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
  			[(self shouldRemapObj: oop) ifTrue:
  				[(extraRoots at: i) at: 0 put: (self remapObj: oop)]]]!

Item was added:
+ ----- Method: SpurMemoryManager>>markAccessibleObjects (in category 'gc - global') -----
+ markAccessibleObjects
+ 	self assert: self validClassTableRootPages.
+ 	marking := true.
+ 	self markAndTraceObjStack: self markStack andContents: false.
+ 	self assert: self validClassTableRootPages.
+ 	self markAndTraceObjStack: self ephemeronQueue andContents: true.
+ 	self assert: self validClassTableRootPages.
+ 	self markAndTrace: hiddenRootsObj.
+ 	self markAndTrace: self specialObjectsOop.
+ 	coInterpreter markAndTraceInterpreterOops: true.
+ 	self markAndFireEphemerons.
+ 	marking := false!

Item was added:
+ ----- Method: SpurMemoryManager>>markAndTrace: (in category 'gc - global') -----
+ markAndTrace: objOop
+ 	"Mark the argument, and all objects reachable from it, and any remaining objects on the mark stack."
+ 	<returnTypeC: #void>
+ 	| objToScan index key |
+ 	self assert: (self isNonImmediate: objOop).
+ 	(self isMarked: objOop) ifTrue:
+ 		[^nil].
+ 	"self setIsMarkedOf: objOop to: false" "for debugging"
+ 	self setIsMarkedOf: objOop to: true.
+ 	((self isEphemeron: objOop)
+ 	 and: [(self isNonImmediate: (key := self keyOfEphemeron: objOop))
+ 	 and: [(self isMarked: key) not
+ 	 and: [self pushOnUnscannedEphemeronStack: objOop]]]) ifTrue:
+ 		[^self].
+ 
+ 	"Now scan the object, and any remaining objects on the mark stack."
+ 	objToScan := objOop.
+ 	index := 0.
+ 	"It is a bad idea to scan big objects early in the mark phase; pushing all their
+ 	 referents onto the mark stack is inviting overflow.  Instead, defer until later."
+ 	[| numSlots |
+ 	 numSlots := self numStrongSlotsOf: objToScan ephemeronInactiveIf: nil.
+ 	 numSlots > self traceImmediatelySlotLimit ifTrue:
+ 		[(self swapLargeObject: objToScan
+ 			   ofSlots: numSlots
+ 			   withSmallerOnObjStackAt: MarkStackRootIndex) ifNotNil:
+ 			[:top|
+ 			 (self isImmediate: top)
+ 				ifTrue: "index,large object pair"
+ 					[index := self integerValueOf: top.
+ 					 objToScan := self popObjStackAt: MarkStackRootIndex]
+ 				ifFalse:
+ 					[objToScan := top]]].
+ 	 self assert: (index between: 0 and: (self numStrongSlotsOf: objToScan  ephemeronInactiveIf: nil) - 1).
+ 	 "The opportunity here is to scan a large object only so far, and push it back on the
+ 	  stack when the stack appears full.  But for the moment we don't code this; it's tricky."
+ 	 [index < numSlots] whileTrue:
+ 		[| field |
+ 		 field := self fetchPointer: index ofObject: objToScan.
+ 		 ((self isImmediate: field) or: [self isMarked: field]) ifFalse:
+ 			[self setIsMarkedOf: field to: true.
+ 			 ((self isEphemeron: field)
+ 			  and: [(self isNonImmediate: (key := self keyOfEphemeron: field))
+ 			  and: [(self isMarked: key) not
+ 			  and: [self pushOnUnscannedEphemeronStack: field]]]) ifFalse:
+ 				[self push: field onObjStackAt: MarkStackRootIndex]].
+ 		 index := index + 1].
+ 	 objToScan := self popObjStackAt: MarkStackRootIndex.
+ 	 objToScan ifNil: [^self].
+ 	 (self isImmediate: objToScan)
+ 		ifTrue:
+ 			[index := self integerValueOf: objToScan.
+ 			 objToScan := self popObjStackAt: MarkStackRootIndex]
+ 		ifFalse:
+ 			[index := 0]] repeat!

Item was added:
+ ----- Method: SpurMemoryManager>>markAndTraceObjStack:andContents: (in category 'obj stacks') -----
+ markAndTraceObjStack: stackOrNil andContents: markAndTraceContents
+ 	"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."
+ 	<returnTypeC: #void>
+ 	| index field |
+ 	stackOrNil = nilObj ifTrue:
+ 		[^self].
+ 	self assert: (self numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
+ 	field := self fetchPointer: ObjStackNextx ofObject: stackOrNil.
+ 	self markAndTraceObjStack: field andContents: markAndTraceContents.
+ 	markAndTraceContents ifFalse:
+ 		[^self].
+ 	"There are two fixed slots in an obj stack, and a Topx of 0 indicates empty, so
+ 	  if there were 4 slots in an oop stack, full would be 2, and the last 0-rel index is 3.
+ 	  Hence the last index is topx + fixed slots - 1, or topx + ObjStackNextx"
+ 	index := (self fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
+ 	[index > ObjStackNextx] whileTrue:
+ 		[field := self fetchPointer: index ofObject: stackOrNil.
+ 		 (self isImmediate: field) ifFalse:
+ 			[self markAndTrace: field].
+ 		 index := index - 1]!

Item was added:
+ ----- Method: SpurMemoryManager>>markObjects (in category 'gc - global') -----
+ markObjects
+ 	"Mark all accessible objects."
+ 	"If the incremental collector is running mark bits may be set; stop it and clear them if necessary."
+ 	self ensureAllMarkBitsAreZero.
+ 	self initializeUnscannedEphemerons.
+ 	self initializeMarkStack.
+ 	self markAccessibleObjects!

Item was added:
+ ----- Method: SpurMemoryManager>>markStack (in category 'gc - global') -----
+ markStack
+ 	^self fetchPointer: MarkStackRootIndex ofObject: hiddenRootsObj!

Item was added:
+ ----- Method: SpurMemoryManager>>markStack: (in category 'gc - global') -----
+ markStack: anObject
+ 	self storePointer: MarkStackRootIndex ofObject: hiddenRootsObj withValue: anObject!

Item was changed:
+ ----- Method: SpurMemoryManager>>newSpaceIsEmpty (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>newSpaceIsEmpty (in category 'generation scavenging') -----
  newSpaceIsEmpty
  	^freeStart = scavenger eden start
  	  and: [pastSpaceStart = scavenger pastSpace start]!

Item was changed:
+ ----- Method: SpurMemoryManager>>newSpaceRefCountMask (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>newSpaceRefCountMask (in category 'generation scavenging') -----
  newSpaceRefCountMask
  	"The three bit field { isGrey, isPinned, isRemembered } is for bits
  	 that are never set in young objects.  This allows the remembered
  	 table to be pruned when full by using these bits as a reference
  	 count of newSpace objects from the remembered table. Objects
  	 with a high count should be tenured to prune the remembered table."
  	^ (1 << self greyBitShift)
  	 | (1 << self pinnedBitShift)
  	 | (1 << self rememberedBitShift)!

Item was changed:
  ----- Method: SpurMemoryManager>>numStrongSlotsOf:ephemeronInactiveIf: (in category 'object access') -----
  numStrongSlotsOf: objOop ephemeronInactiveIf: criterion
  	"Answer the number of strong pointer fields in the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<api>
  	<var: 'criterion' declareC: 'int (*criterion)(sqInt key)'>
  	<inline: true>
  	<asmLabel: false>
  	| fmt numSlots  contextSize numLiterals |
  	fmt := self formatOf: objOop.
  	fmt <= self lastPointerFormat ifTrue:
  		[numSlots := self numSlotsOf: objOop.
  		 fmt <= self arrayFormat ifTrue:
  			[^numSlots].
  		 fmt = self indexablePointersFormat ifTrue:
  			[(self isContextNonImm: objOop) ifTrue:
  				["contexts end at the stack pointer"
  				contextSize := coInterpreter fetchStackPointerOf: objOop.
  				^CtxtTempFrameStart + contextSize].
  			 ^numSlots].
  		 fmt = self weakArrayFormat ifTrue:
  			[^self fixedFieldsOfClass: (self fetchClassOfNonImm: objOop)].
  		 self assert: fmt = self ephemeronFormat.
+ 		 ^(criterion isNil or: [self perform: criterion with: (self keyOfEphemeron: objOop)])
- 		 ^(self perform: criterion with: (self keyOfEphemeron: objOop))
  			ifTrue: [numSlots]
  			ifFalse: [0]].
  	fmt = self forwardedFormat ifTrue: [^1].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
  	numLiterals := coInterpreter literalCountOf: objOop.
  	^numLiterals + LiteralStart!

Item was added:
+ ----- Method: SpurMemoryManager>>popObjStackAt: (in category 'obj stacks') -----
+ popObjStackAt: objStackRootIndex 
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SpurMemoryManager>>push:onObjStackAt: (in category 'obj stacks') -----
+ push: objOop onObjStackAt: objStackRootIndex 
+ 	| page numEntries |
+ 	page := self ensureRoomOnObjStackAtIndex: objStackRootIndex.
+ 	numEntries := self fetchPointer: ObjStackTopx ofObject: page.
+ 	self assert: numEntries < ObjStackLimit.
+ 	numEntries := numEntries + 1.
+ 	self storePointerUnchecked: numEntries + ObjStackNextx ofObject: page withValue: objOop;
+ 		storePointerUnchecked: ObjStackTopx ofObject: page withValue: numEntries!

Item was added:
+ ----- Method: SpurMemoryManager>>pushOnUnscannedEphemeronStack: (in category 'weakness and ephemerality') -----
+ pushOnUnscannedEphemeronStack: anEphemeron
+ 	"Attempt to push anEphemeron on the unscanned ephemerons stack
+ 	 and answer if the attempt succeeded.  Note that the ephemeron
+ 	 stack overflowing isn't a disaster; it simply means treating the
+ 	 ephemeron as strong in this GC cycle."
+ 	self assert: (self isEphemeron: anEphemeron).
+ 	unscannedEphemerons top >= unscannedEphemerons limit ifTrue:
+ 		[^false].
+ 	self longAt: unscannedEphemerons top put: anEphemeron.
+ 	unscannedEphemerons top: unscannedEphemerons top + self wordSize.
+ 	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>queueEphemeron: (in category 'weakness and ephemerality') -----
+ queueEphemeron: anEphemeron
+ 	self assert: ((self isNonImmediate: anEphemeron)
+ 				and: [(self formatOf: anEphemeron) = self ephemeronFormat]).
+ 	self push: anEphemeron onObjStackAt: EphemeronQueueRootIndex!

Item was changed:
+ ----- Method: SpurMemoryManager>>remap: (in category 'gc - global') -----
- ----- Method: SpurMemoryManager>>remap: (in category 'garbage collection') -----
  remap: oop
  	self shouldNotImplement!

Item was changed:
+ ----- Method: SpurMemoryManager>>remapObj: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>remapObj: (in category 'generation scavenging') -----
  remapObj: objOop
  	"Scavenge or simply follow objOop.  Answer the new location of objOop.  The
  	 send should have been guarded by a send of shouldRemapOop: or shouldScavengeObj:.
  	 The method is called remapObj: for compatibility with ObjectMemory."
  	<inline: false>
  	| resolvedObj |
  	self assert: (self shouldRemapOop: objOop).
  	(self isForwarded: objOop)
  		ifTrue:
  			[resolvedObj := self followForwarded: objOop.
  			(self isYoung: resolvedObj) ifFalse: "a becommed object whose target is in old space"
  				[^resolvedObj].
  			(self isInFutureSpace: resolvedObj) ifTrue: "already scavenged"
  				[^resolvedObj]]
  		ifFalse:
  			[resolvedObj := objOop].
  	^scavenger copyAndForward: resolvedObj!

Item was changed:
+ ----- Method: SpurMemoryManager>>scavengingGC (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>scavengingGC (in category 'generation scavenging') -----
  scavengingGC
  	"Run the scavenger."
  
  	self scavengingGCTenuringIf: TenureByAge!

Item was changed:
+ ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'generation scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
  	"Run the scavenger."
  
  	self assert: remapBufferCount = 0.
  	self assert: (segmentManager numSegments = 0 "true in the spur image bootstrap"
  				or: [scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes]).
  	self checkFreeSpace.
  	"coInterpreter printCallStackFP: coInterpreter framePointer"
  
  	self runLeakCheckerForFullGC: false.
  	coInterpreter
  		preGCAction: GCModeIncr;
  		"would prefer this to be in mapInterpreterOops, but
  		 compatibility with ObjectMemory dictates it goes here."
  		flushMethodCacheFrom: startOfMemory to: newSpaceLimit.
  	needGCFlag := false.
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	scavengeInProgress := true.
  	pastSpaceStart := scavenger scavenge: tenuringCriterion.
  	self assert: (self
  					oop: pastSpaceStart
  					isGreaterThanOrEqualTo: scavenger pastSpace start
  					andLessThanOrEqualTo: scavenger pastSpace limit).
  	freeStart := scavenger eden start.
  	self initSpaceForAllocationCheck: (self addressOf: scavenger eden).
  	scavengeInProgress := false.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  	statRootTableCount := scavenger rememberedSetSize.
  
  	coInterpreter postGCAction.
  	self runLeakCheckerForFullGC: false.
  
  	self checkFreeSpace!

Item was changed:
+ ----- Method: SpurMemoryManager>>scheduleScavenge (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>scheduleScavenge (in category 'generation scavenging') -----
  scheduleScavenge
  	needGCFlag := true.
  	coInterpreter forceInterruptCheck!

Item was changed:
+ ----- Method: SpurMemoryManager>>shouldRemapObj: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>shouldRemapObj: (in category 'generation scavenging') -----
  shouldRemapObj: objOop
  	"Answer if the obj should be scavenged (or simply followed). The method is called
  	 shouldRemapObj: for compatibility with ObjectMemory."
  	^(self isForwarded: objOop)
  	  or: [self isYoung: objOop]!

Item was changed:
+ ----- Method: SpurMemoryManager>>shouldRemapOop: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>shouldRemapOop: (in category 'generation scavenging') -----
  shouldRemapOop: oop
  	<api>
  	"Answer if the oop should be scavenged.. The method is called
  	 shouldRemapOop: for compatibility with ObjectMemory."
  	<inline: true>
  	^(self isNonImmediate: oop)
  	   and: [self shouldRemapObj: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>stackValue:ofObjStack: (in category 'obj stacks') -----
+ stackValue: offset ofObjStack: objStackPage
+ 	| numEntries nextPage |
+ 	self assert: offset >= 0.
+ 	numEntries := self fetchPointer: ObjStackTopx ofObject: objStackPage.
+ 	offset < numEntries ifTrue:
+ 		[^self fetchPointer: ObjStackTopx + offset ofObject: objStackPage].
+ 	nextPage := self fetchPointer: ObjStackNextx ofObject: objStackPage.
+ 	nextPage = 0 ifTrue:
+ 		[^nil].
+ 	^self stackValue: offset - numEntries ofObjStack: nextPage!

Item was added:
+ ----- Method: SpurMemoryManager>>stackValue:ofObjStackAt: (in category 'obj stacks') -----
+ stackValue: offset ofObjStackAt: objStackRootIndex 
+ 	^self
+ 		stackValue: offset
+ 		ofObjStack: (self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj)!

Item was changed:
+ ----- Method: SpurMemoryManager>>sufficientSpaceAfterGC: (in category 'gc - scavenging') -----
- ----- Method: SpurMemoryManager>>sufficientSpaceAfterGC: (in category 'generation scavenging') -----
  sufficientSpaceAfterGC: numBytes
  	"This is ObjectMemory's funky entry-point into its incremental GC,
  	 which is a stop-the-world a young generation reclaimer.  In Spur
  	 we run the scavenger.  Answer if space is not low."
  
  	self assert: numBytes = 0.
  	self scavengingGCTenuringIf: TenureByAge.
  	lowSpaceThreshold > totalFreeOldSpace ifTrue: "space is low"
  		[lowSpaceThreshold := 0. "avoid signalling low space twice"
  		 ^false].
  	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>swapLargeObject:ofSlots:withSmallerOnObjStackAt: (in category 'obj stacks') -----
+ swapLargeObject: objOop ofSlots: numStrongSlots withSmallerOnObjStackAt: objStackRootIndex
+ 	"Assuming objOop is large, answer a smaller object, if it is available, otherwise answer nil."
+ 	| objStackPage top topObj |
+ 	objStackPage := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
+ 	top := self stackValue: 0 ofObjStack: objStackPage.
+ 	top ifNil: [^nil].
+ 	(self isImmediate: top) ifTrue: "index,large obj pair on top. is it smaller?"
+ 		[(self integerValueOf: top) >= numStrongSlots ifTrue:
+ 			[^nil]. "no. go with the one we've already got"
+ 		 "yes. push 0, objOop, answer index, leaving large obj on top to be popped."
+ 		 topObj := self stackValue: 1 ofObjStack: objStackPage.
+ 		 self stackValue: 0 ofObjStackAt: objStackRootIndex put: ConstZero.
+ 		 self stackValue: 1 ofObjStackAt: objStackRootIndex put: objOop.
+ 		 self push: topObj onObjStackAt: objStackRootIndex.
+ 		 ^top].
+ 	"push numStrongSlots, objOop and answer top"
+ 	self stackValue: 0 ofObjStackAt: objStackRootIndex put: objOop.
+ 	self push: ConstZero onObjStackAt: objStackRootIndex.
+ 	^top!

Item was added:
+ ----- Method: SpurMemoryManager>>swizzleObjStack: (in category 'obj stacks') -----
+ swizzleObjStack: objStackRootIndex
+ 	<returnTypeC: #void>
+ 	"On load, swizzle the pointers in an obj stack."
+ 	| firstPage stackOrNil index field |
+ 	firstPage := stackOrNil := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
+ 	stackOrNil = nilObj ifTrue:
+ 		[^self].
+ 	[self assert: (self numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
+ 	 "There are three fixed slots in an obj stack, and a Topx of 0 indicates empty, so
+ 	   if there were 5 slots in an oop stack, full would be 2, and the last 0-rel index is 4.
+ 	   Hence the last index is topx + fixed slots - 1, or topx + ObjStackNextx"
+ 	 index := (self fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
+ 	 [field := self fetchPointer: index ofObject: stackOrNil.
+ 	  (self isImmediate: field) ifFalse:
+ 		[field := segmentManager swizzleObj: field.
+ 		 self storePointerUnchecked: ObjStackNextx ofObject: stackOrNil withValue: field].
+ 	  (index := index - 1) > ObjStackTopx] whileTrue.
+ 	 (stackOrNil := field) ~= 0] whileTrue.
+ 	[stackOrNil := self fetchPointer: ObjStackFreex ofObject: firstPage.
+ 	 stackOrNil ~= 0] whileTrue:
+ 		[field := segmentManager swizzleObj: stackOrNil.
+ 		 self storePointerUnchecked: ObjStackFreex ofObject: firstPage withValue: field.
+ 		 firstPage := stackOrNil].
+ 	self assert: (self isValidObjStackAt: objStackRootIndex)
+ 	!

Item was added:
+ ----- Method: SpurMemoryManager>>traceImmediatelySlotLimit (in category 'gc - global') -----
+ traceImmediatelySlotLimit
+ 	"Arbitrary level at which to defer tracing large objects until later.
+ 	 The average slot size of Smalltalk objects is typically near 8."
+ 	^16!

Item was changed:
  ----- Method: SpurMemoryManager>>validClassTableRootPages (in category 'class table') -----
  validClassTableRootPages
+ 	"Answer if hiddenRootsObj is of the right size with the
+ 	 expected contents, and if numClassTablePages is correct."
- 	"Answer if numClassTablePages is correct."
  
+ 	(self numSlotsOf: hiddenRootsObj) = (self classTableRootSlots + self hiddenRootSlots) ifFalse:
+ 		[^false].
+ 
  	"is it in range?"
  	(numClassTablePages > 1 and: [numClassTablePages <= self classTableRootSlots]) ifFalse:
  		[^false].
  	"are all pages the right size?"
  	0 to: numClassTablePages - 1 do:
  		[:i| | obj |
  		 obj := self fetchPointer: i ofObject: hiddenRootsObj.
  		 ((self addressCouldBeObj: obj)
  		  and: [(self numSlotsOf: obj) = self classTablePageSize]) ifFalse:
  			[^false]].
  	"are all entries beyond numClassTablePages nil?"
  	numClassTablePages to: self classTableRootSlots - 1 do:
  		[:i|
  		(self fetchPointer: i ofObject: hiddenRootsObj) ~= nilObj ifTrue:
  			[^false]].
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>fireEphemeron: (in category 'finalization') -----
  fireEphemeron: ephemeron
+ 	<option: #SpurObjectMemory>
+ 	objectMemory queueEphemeron: ephemeron.
+ 	self forceInterruptCheck!
- 	self shouldBeImplemented!



More information about the Vm-dev mailing list