[Vm-dev] VM Maker: VMMaker.oscog.seperateMarking-WoC.3246.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Aug 9 16:47:55 UTC 2022


Tom Braun uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog.seperateMarking-WoC.3246.mcz

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

Name: VMMaker.oscog.seperateMarking-WoC.3246
Author: WoC
Time: 9 August 2022, 6:47:49.542723 pm
UUID: 50b19065-4384-48d9-96ce-91a1e12b8e33
Ancestors: VMMaker.oscog-eem.3245, VMMaker.oscog.seperateMarking-eem.3223

arate class for garbage collection
implemented first versions for: incremental marking, sweeping and compacting
added two error messages to code generationself flag: #Todo. ""

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

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-FFI'!
  SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-V3MemoryManager'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Utilities'!
+ SystemOrganization addCategory: #'VMMaker-SpurGarbageCollectorSimulation'!
+ SystemOrganization addCategory: #'VMMaker-SpurGarbageCollector'!

Item was changed:
  ----- Method: CCodeGenerator>>checkClassForNameConflicts: (in category 'error notification') -----
  checkClassForNameConflicts: aClass
  	"Verify that the given class does not have constant, variable, or method names that conflict with
  	 those of previously added classes. Raise an error if a conflict is found, otherwise just return."
  
  	"check for constant name collisions in class pools"
  	aClass classPool associationsDo:
  		[:assoc |
  		(constants includesKey: assoc key) ifTrue:
  			[self error: 'Constant ', assoc key, ' was defined in a previously added class']].
  
  	"and in shared pools"
  	(aClass sharedPools reject: [:pool| pools includes: pool]) do:
  		[:pool |
  		pool bindingsDo:
  			[:assoc |
  			(constants includesKey: assoc key) ifTrue:
  				[self error: 'Constant ', assoc key, ' was defined in a previously added class']]].
  
  	"check for instance variable name collisions"
  	(aClass inheritsFrom: VMStructType) ifFalse:
  		[(self instVarNamesForClass: aClass) do:
  			[:varName |
  			(variables includes: varName) ifTrue:
  				[self error: 'Instance variable ', varName, ' was defined in a previously added class']]].
  
  	"check for method name collisions"
  	aClass selectors do:
  		[:sel | | tmeth meth |
  		((self shouldIncludeMethodFor: aClass selector: sel)
  		and: [(tmeth := methods at: sel ifAbsent: nil) notNil
  		and: [(aClass isStructClass and: [(aClass isAccessor: sel)
  				and: [(methods at: sel) isStructAccessor]]) not
  		and: [(meth := aClass >> sel) isSubclassResponsibility not
  		and: [(aClass includesBehavior: tmeth definingClass) not]]]]) ifTrue:
  			[((aClass >>sel) pragmaAt: #option:)
+ 				ifNil: [self error: 'Method ', sel, ' was previously defined in: ' , tmeth definingClass , ' and now in: ', aClass]
- 				ifNil: [self error: 'Method ', sel, ' was defined in a previously added class.']
  				ifNotNil:
  					[logger
  						ensureCr;
  						show: 'warning, method ', aClass name, '>>', sel storeString,
  								' overrides ', tmeth definingClass, '>>', sel storeString;
  						cr]]]!

Item was added:
+ ----- Method: CoInterpreter>>incrementalMarkAndTracePrimTraceLog (in category 'debug support') -----
+ incrementalMarkAndTracePrimTraceLog
+ 	"The prim trace log is a circular buffer of objects. If there is
+ 	 an entry at primTraceLogIndex - 1 \\ PrimTraceBufferSize it has entries.
+ 	 If there is something at primTraceLogIndex it has wrapped."
+ 	<inline: false>
+ 	| entryOop |
+ 	(primTraceLog at: (self safe: primTraceLogIndex - 1 mod: PrimTraceLogSize)) = 0 ifTrue:
+ 		[^self].
+ 	(primTraceLog at: primTraceLogIndex) ~= 0 ifTrue:
+ 		[primTraceLogIndex to: PrimTraceLogSize - 1 do:
+ 			[:i|
+ 			 entryOop := primTraceLog at: i.
+ 			 (entryOop ~= 0
+ 			  and: [objectMemory isNonImmediate: entryOop]) ifTrue:
+ 				[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: entryOop]]].
+ 	0 to: primTraceLogIndex - 1 do:
+ 		[:i|
+ 		entryOop := primTraceLog at: i.
+ 		(entryOop ~= 0
+ 		  and: [objectMemory isNonImmediate: entryOop]) ifTrue:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: entryOop]]!

Item was added:
+ ----- Method: CoInterpreter>>incrementalMarkAndTraceStackPage: (in category 'object memory support') -----
+ incrementalMarkAndTraceStackPage: thePage
+ 	| theSP theFP frameRcvrOffset callerFP oop |
+ 	<var: #thePage type: #'StackPage *'>
+ 	<var: #theSP type: #'char *'>
+ 	<var: #theFP type: #'char *'>
+ 	<var: #frameRcvrOffset type: #'char *'>
+ 	<var: #callerFP type: #'char *'>
+ 	<inline: false>
+ 
+ 	self assert: (stackPages isFree: thePage) not.
+ 	self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 	self assert: thePage trace ~= StackPageTraced.
+ 	thePage trace: StackPageTraced.
+ 
+ 	theSP := thePage headSP.
+ 	theFP := thePage  headFP.
+ 	"Skip the instruction pointer on top of stack of inactive pages."
+ 	thePage = stackPage ifFalse:
+ 		[theSP := theSP + objectMemory wordSize].
+ 	[frameRcvrOffset := self frameReceiverLocation: theFP.
+ 	 [theSP <= frameRcvrOffset] whileTrue:
+ 		[oop := stackPages longAt: theSP.
+ 		 (objectMemory isOopForwarded: oop) ifTrue:
+ 			[oop := objectMemory followForwarded: oop.
+ 			 stackPages longAt: theSP put: oop].
+ 		 (objectMemory isImmediate: oop) ifFalse:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGrey: oop].
+ 		 theSP := theSP + objectMemory wordSize].
+ 	(self frameHasContext: theFP) ifTrue:
+ 		[self assert: (objectMemory isContext: (self frameContext: theFP)).
+ 		 objectMemory marker pushOnMarkingStackAndMakeGrey: (self frameContext: theFP)].
+ 	(self isMachineCodeFrame: theFP)
+ 		ifTrue: [self markAndTraceMachineCodeMethod: (self mframeCogMethod: theFP)]
+ 		ifFalse: [objectMemory marker pushOnMarkingStackAndMakeGrey: (self iframeMethod: theFP)].
+ 	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
+ 		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
+ 		 theFP := callerFP].
+ 	theSP := theFP + FoxCallerSavedIP + objectMemory wordSize. "caller ip is ceBaseReturnPC"
+ 	[theSP <= thePage baseAddress] whileTrue:
+ 		[oop := stackPages longAt: theSP.
+ 		 (objectMemory isOopForwarded: oop) ifTrue:
+ 			[oop := objectMemory followForwarded: oop.
+ 			 stackPages longAt: theSP put: oop].
+ 		 (objectMemory isImmediate: oop) ifFalse:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGrey: oop].
+ 		 theSP := theSP + objectMemory wordSize]!

Item was added:
+ ----- Method: CoInterpreter>>incrementalMarkAndTraceTraceLog (in category 'object memory support') -----
+ incrementalMarkAndTraceTraceLog
+ 	"The trace log is a circular buffer of pairs of entries. If there is an entry at
+ 	 traceLogIndex - 3 \\ TraceBufferSize it has entries.  If there is something at
+ 	 traceLogIndex it has wrapped."
+ 	<inline: false>
+ 	| limit |
+ 	limit := self safe: traceLogIndex - 3 mod: TraceBufferSize.
+ 	(traceLog at: limit) = 0 ifTrue: [^self].
+ 	(traceLog at: traceLogIndex) ~= 0 ifTrue:
+ 		[limit := TraceBufferSize - 3].
+ 	0 to: limit by: 3 do:
+ 		[:i| | oop |
+ 		oop := traceLog at: i.
+ 		(objectMemory isImmediate: oop) ifFalse:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: oop].
+ 		oop := traceLog at: i + 1.
+ 		(objectMemory isImmediate: oop) ifFalse:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: oop]]!

Item was added:
+ ----- Method: CoInterpreterMT>>incrementalMarkAndTraceInterpreterOops (in category 'object memory support') -----
+ incrementalMarkAndTraceInterpreterOops
+ 	"Override to mark the awolProcesses"
+ 	<var: #vmThread type: #'CogVMThread *'>
+ 
+ 	super incrementalMarkAndTraceInterpreterOops.
+ 
+ 	"Per-thread state; trace each thread's own newMethod and stack of awol processes."
+ 	1 to: cogThreadManager getNumThreads do:
+ 		[:i| | vmThread |
+ 		vmThread := cogThreadManager vmThreadAt: i.
+ 		vmThread state ifNotNil:
+ 			[vmThread newMethodOrNull ifNotNil:
+ 				[objectMemory marker pushOnMarkingStackAndMakeGrey: vmThread newMethodOrNull].
+ 			 0 to: vmThread awolProcIndex - 1 do:
+ 				[:j| objectMemory marker pushOnMarkingStackAndMakeGrey: (vmThread awolProcesses at: j)]]]!

Item was added:
+ ----- Method: CogVMSimulator>>incrementalMarkAndTraceInterpreterOops (in category 'multi-threading simulation switch') -----
+ incrementalMarkAndTraceInterpreterOops
+ 	"This method includes or excludes CoInterpreterMT methods as required.
+ 	 Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate"
+ 
+ 	^self perform: #incrementalMarkAndTraceInterpreterOops
+ 		withArguments: {}
+ 		inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])!

Item was added:
+ ----- Method: ImageLeakChecker>>incrementalMarkAndTraceInterpreterOops (in category 'no-op overrides') -----
+ incrementalMarkAndTraceInterpreterOops!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveClone (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveClone (in category 'object access primitives') -----
  primitiveClone
  	"Return a shallow copy of the receiver."
  
  	| rcvr newCopy |
  	rcvr := self stackTop.
  	(objectMemory isImmediate: rcvr)
  		ifTrue:
  			[newCopy := rcvr]
  		ifFalse:
  			[(argumentCount = 0
  			  or: [(objectMemory isForwarded: rcvr) not])
  				ifTrue: [newCopy := objectMemory cloneObject: rcvr]
  				ifFalse: [newCopy := 0].
  			 newCopy = 0 ifTrue: "not enough memory most likely"
  				[^self primitiveFail]].
  	self pop: argumentCount + 1 thenPush: newCopy!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveNew (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveNew (in category 'object access primitives') -----
  primitiveNew
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 1
  		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			["Allocate a new fixed-size instance.  Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
  			(objectMemory instantiateClass: self stackTop)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
  											ifTrue: [PrimErrNoMemory]
  											ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			["Allocate a new fixed-size instance. Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. May cause a GC."
  			| spaceOkay |
  			"The following may cause GC!! Use var for result to permit inlining."
  			spaceOkay := objectMemory
  								sufficientSpaceToInstantiate: self stackTop
  								indexableSize: 0.
  			spaceOkay
  				ifTrue:
  					[self
  						pop: argumentCount + 1
  						thenPush: (objectMemory
  									instantiateClass: self stackTop
  									indexableSize: 0)]
  				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveNewMethod (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveNewMethod (in category 'compiled methods') -----
  primitiveNewMethod
  	| header bytecodeCount class size theMethod literalCount |
  	header := self stackTop.
  	bytecodeCount := self stackValue: 1.
  	((objectMemory isIntegerObject: header)
  	 and: [(objectMemory isIntegerObject: bytecodeCount)
  	 and: [(bytecodeCount := objectMemory integerValueOf: bytecodeCount) >= 0]]) ifFalse:
  		[self primitiveFailFor: PrimErrBadArgument.
  		 ^self].
  	class := self stackValue: 2.
  	literalCount := objectMemory literalCountOfMethodHeader: header.
  	size := literalCount + LiteralStart * objectMemory bytesPerOop + bytecodeCount.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[theMethod := objectMemory instantiateCompiledMethodClass: class indexableSize: size.
  			 theMethod ifNil:
  				[self primitiveFailFor: ((objectMemory isCompiledMethodFormat: (objectMemory instSpecOfClass: class))
  										ifTrue: [PrimErrNoMemory]
  										ifFalse: [PrimErrBadReceiver]).
  				 ^self]]
  		ifFalse:
  			[theMethod := objectMemory instantiateClass: class indexableSize: size].
  	objectMemory storePointerUnchecked: HeaderIndex ofObject: theMethod withValue: header.
  	1 to: literalCount do:
  		[:i | objectMemory storePointerUnchecked: i ofObject: theMethod withValue: objectMemory nilObject].
  	self pop: 3 thenPush: theMethod!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveNewPinnedInOldSpace (in category 'object access primitives') -----
+ primitiveNewPinnedInOldSpace
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 1
+ 		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			["Allocate a new fixed-size instance.  Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
+ 			(objectMemory instantiateClass: self stackTop)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
+ 											ifTrue: [PrimErrNoMemory]
+ 											ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			["Allocate a new fixed-size instance. Fail if the allocation would leave
+ 			  less than lowSpaceThreshold bytes free. May cause a GC."
+ 			| spaceOkay |
+ 			"The following may cause GC!! Use var for result to permit inlining."
+ 			spaceOkay := objectMemory
+ 								sufficientSpaceToInstantiate: self stackTop
+ 								indexableSize: 0.
+ 			spaceOkay
+ 				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory
+ 									instantiateClass: self stackTop
+ 									indexableSize: 0)]
+ 				ifFalse: [self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveNewWithArg (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveNewWithArg (in category 'object access primitives') -----
  primitiveNewWithArg
  	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
  	| size spaceOkay instSpec |
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 2
  		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		[^self primitiveFailFor: PrimErrBadArgument].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
  					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
  											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
  												ifTrue: [PrimErrNoMemory]
  												ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
  			 spaceOkay
  				ifTrue:
  					[self
  						pop: argumentCount + 1
  						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
  				ifFalse:
  					[self primitiveFailFor: PrimErrNoMemory]]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveNewWithArgUninitialized (in category 'object access primitives') -----
+ primitiveNewWithArgUninitialized
+ 	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
+ 	| size spaceOkay instSpec |
+ 	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
+ 		[(argumentCount < 2
+ 		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
+ 			[^self primitiveFailFor: PrimErrBadArgument]].
+ 	size := self positiveMachineIntegerValueOf: self stackTop.
+ 	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
+ 		[^self primitiveFailFor: PrimErrBadArgument].
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
+ 				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 												ifTrue: [PrimErrNoMemory]
+ 												ifFalse: [PrimErrBadReceiver])]]
+ 		ifFalse:
+ 			[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
+ 			 spaceOkay
+ 				ifTrue:
+ 					[self
+ 						pop: argumentCount + 1
+ 						thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
+ 				ifFalse:
+ 					[self primitiveFailFor: PrimErrNoMemory]]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitivePinnedNew (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitivePinnedNew (in category 'object access primitives') -----
  primitivePinnedNew
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 1
  		  or: [self objCouldBeClassObj: self stackTop]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			["Allocate a new fixed-size instance.  Fail if the allocation would leave
  			  less than lowSpaceThreshold bytes free. This *will not* cause a GC :-)"
  			(objectMemory inOldSpaceInstantiatePinnedClass: self stackTop)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [self primitiveFailFor: ((objectMemory isFixedSizePointerFormat: (objectMemory instSpecOfClass: self stackTop))
  											ifTrue: [PrimErrNoMemory]
  											ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrUnsupported]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitivePinnedNewWithArg (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitivePinnedNewWithArg (in category 'object access primitives') -----
  primitivePinnedNewWithArg
  	"Allocate a new pinned indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free."
  	| size instSpec |
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 2
  		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		[^self primitiveFailFor: PrimErrBadArgument].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(objectMemory inOldSpaceInstantiatePinnedClass: (self stackValue: 1) indexableSize: size)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
  					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
  											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
  												ifTrue: [PrimErrNoMemory]
  												ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrUnsupported]!

Item was changed:
+ ----- Method: InterpreterPrimitives>>primitiveUninitializedNewWithArg (in category 'instantiation primitives') -----
- ----- Method: InterpreterPrimitives>>primitiveUninitializedNewWithArg (in category 'object access primitives') -----
  primitiveUninitializedNewWithArg
  	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
  	| size instSpec |
  	NewspeakVM ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  		[(argumentCount < 2
  		  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  			[^self primitiveFailFor: PrimErrBadArgument]].
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self successful ifFalse:"positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		[^self primitiveFailFor: PrimErrBadArgument].
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[(objectMemory instantiateUninitializedClass: (self stackValue: 1) indexableSize: size)
  				ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
  				ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
  					  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
  											and: [(objectMemory isCompiledMethodFormat: instSpec) not])
  												ifTrue: [PrimErrNoMemory]
  												ifFalse: [PrimErrBadReceiver])]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrUnsupported]!

Item was removed:
- ----- Method: Spur32BitMMLECoSimulator>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	"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."
- 	parent ifNil:
- 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
- 		 CloneOnGC ifTrue:
- 			[coInterpreter cloneSimulation objectMemory globalGarbageCollect.
- 			 Smalltalk garbageCollect]].
- 	^super globalGarbageCollect!

Item was added:
+ ----- Method: Spur32BitMMLECoSimulator>>preGlobalGCActions (in category 'gc - global') -----
+ preGlobalGCActions
+ 	"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."
+ 	parent ifNil:
+ 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
+ 		 CloneOnGC ifTrue:
+ 			[coInterpreter cloneSimulation objectMemory gc globalGarbageCollect.
+ 			 Smalltalk garbageCollect]]!

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	"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."
- 	parent ifNil:
- 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
- 		 CloneOnGC ifTrue:
- 			[coInterpreter cloneSimulation objectMemory globalGarbageCollect.
- 			 Smalltalk garbageCollect]].
- 	^super globalGarbageCollect!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>preGlobalGCActions (in category 'gc - global') -----
+ preGlobalGCActions
+ 	"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."
+ 	parent ifNil:
+ 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
+ 		 CloneOnGC ifTrue:
+ 			[coInterpreter cloneSimulation objectMemory gc globalGarbageCollect.
+ 			 Smalltalk garbageCollect]]!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlotsForPinningInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsForPinningInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  Try and
  	 allocate in a segment that already includes pinned objects.  The header of the
  	 result will have been filled-in but not the contents."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes
  				   suchThat: [:f| (segmentManager segmentContainingObj: f) containsPinned].
  	chunk ifNil:
  		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
  		 chunk ifNil:
  			[^nil].
  		 (segmentManager segmentContainingObj: chunk) containsPinned: true].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self flag: #endianness.
  		 self longAt: chunk put: numSlots.
  		 self longAt: chunk + 4 put: self numSlotsMask << self numSlotsHalfShift.
  		 self long64At: chunk + self baseHeaderSize
  			 put: ((self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)
  					bitOr: 1 << self pinnedBitShift).
+ 		
+ 		self flag: #Todo. "later on we probably want to do this in the call above"
+ 		gc maybeModifyGCFlagsOf: chunk.
  		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self long64At: chunk
  		put: ((self headerForSlots: numSlots format: formatField classIndex: classIndex)
  					bitOr: 1 << self pinnedBitShift).
+ 	
+ 	self flag: #Todo. "later on we probably want to do this in the call above"
+ 	gc maybeModifyGCFlagsOf: chunk.
  	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlotsInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  The header
  	 will have been filled-in but not the contents.  If no memory is available answer nil."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
  	chunk ifNil:
  		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self flag: #endianness.
  		 self longAt: chunk put: numSlots.
  		 self longAt: chunk + 4 put: self numSlotsMask << self numSlotsHalfShift.
  		 self long64At: chunk + self baseHeaderSize
  			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
+ 			
+ 		self flag: #Todo. "later on we probably want to do this in the call above"
+ 		gc maybeModifyGCFlagsOf: chunk.
  		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self long64At: chunk put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
+ 	
+ 	self flag: #Todo. "later on we probably want to do this in the call above"
+ 	gc maybeModifyGCFlagsOf: chunk.
  	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: Spur64BitMMLECoSimulator>>coInterpreter:cogit: (in category 'initialization') -----
  coInterpreter: aCoInterpreter cogit: aCogit
+ 
  	coInterpreter := aCoInterpreter.
  	cogit := aCogit.
+ 	marker coInterpreter: aCoInterpreter.
  	scavenger coInterpreter: aCoInterpreter.
+ 	compactor coInterpreter: aCoInterpreter.
+ 	gc coInterpreter: aCoInterpreter
+ 	!
- 	compactor coInterpreter: aCoInterpreter!

Item was removed:
- ----- Method: Spur64BitMMLECoSimulator>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	"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."
- 	parent ifNil:
- 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
- 		 CloneOnGC ifTrue:
- 			[coInterpreter cloneSimulation objectMemory globalGarbageCollect.
- 			 Smalltalk garbageCollect]].
- 	^super globalGarbageCollect!

Item was added:
+ ----- Method: Spur64BitMMLECoSimulator>>preGlobalGCActions (in category 'gc - global') -----
+ preGlobalGCActions
+ 	"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."
+ 	parent ifNil:
+ 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
+ 		 CloneOnGC ifTrue:
+ 			[coInterpreter cloneSimulation objectMemory gc globalGarbageCollect.
+ 			 Smalltalk garbageCollect]]!

Item was removed:
- ----- Method: Spur64BitMMLESimulator>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	"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."
- 	parent ifNil:
- 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
- 		 CloneOnGC ifTrue:
- 			[coInterpreter cloneSimulation objectMemory globalGarbageCollect.
- 			 Smalltalk garbageCollect]].
- 	^super globalGarbageCollect!

Item was added:
+ ----- Method: Spur64BitMMLESimulator>>preGlobalGCActions (in category 'gc - global') -----
+ preGlobalGCActions
+ 	"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."
+ 	parent ifNil:
+ 		[coInterpreter cr; print: 'GC number '; printNum: statFullGCs; tab; flush.
+ 		 CloneOnGC ifTrue:
+ 			[coInterpreter cloneSimulation objectMemory gc globalGarbageCollect.
+ 			 Smalltalk garbageCollect]]!

Item was added:
+ ----- Method: Spur64BitMMLESimulator>>setIsGreyOf:to: (in category 'header access') -----
+ setIsGreyOf: objOop to: aBoolean
+ 	"objOop = 16rB26020 ifTrue: [self halt]."
+ 	"(#(16r1971D0 16r196EE0 16r197048 16r197148) includes: objOop) ifTrue:
+ 		[self halt]."
+ 	GCEventLog register: ((aBoolean
+ 		ifTrue: [GCGreyEvent]
+ 		ifFalse: [GCUngreyEvent]) address: objOop).
+ 		
+ 	objOop = 16r448 ifTrue: [self halt].
+ 
+ 	super setIsGreyOf: objOop to: aBoolean.
+ 	"(aBoolean
+ 	 and: [(self isContextNonImm: objOop)
+ 	 and: [(coInterpreter
+ 			checkIsStillMarriedContext: objOop
+ 			currentFP: coInterpreter framePointer)
+ 	 and: [(coInterpreter stackPages stackPageFor: (coInterpreter frameOfMarriedContext: objOop)) trace = 0]]]) ifTrue:
+ 		[self halt]"!

Item was changed:
  ----- Method: Spur64BitMMLESimulator>>setIsMarkedOf:to: (in category 'header access') -----
  setIsMarkedOf: objOop to: aBoolean
  	"objOop = 16rB26020 ifTrue: [self halt]."
  	"(#(16r1971D0 16r196EE0 16r197048 16r197148) includes: objOop) ifTrue:
  		[self halt]."
+ 	GCEventLog register: ((aBoolean
+ 		ifTrue: [GCMarkEvent]
+ 		ifFalse: [GCUnmarkEvent]) address: objOop).
+ 
  	super setIsMarkedOf: objOop to: aBoolean.
  	"(aBoolean
  	 and: [(self isContextNonImm: objOop)
  	 and: [(coInterpreter
  			checkIsStillMarriedContext: objOop
  			currentFP: coInterpreter framePointer)
  	 and: [(coInterpreter stackPages stackPageFor: (coInterpreter frameOfMarriedContext: objOop)) trace = 0]]]) ifTrue:
  		[self halt]"!

Item was added:
+ ----- Method: Spur64BitMMLESimulator>>unlinkFreeChunk:chunkBytes: (in category 'as yet unclassified') -----
+ unlinkFreeChunk: freeChunk chunkBytes: chunkBytes
+ 
+ 	GCEventLog register: (GCUnlinkEvent address: freeChunk).
+ 	^ super unlinkFreeChunk: freeChunk chunkBytes: chunkBytes!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlotsForPinningInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsForPinningInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  Try and
  	 allocate in a segment that already includes pinned objects.  The header of the
  	 result will have been filled-in but not the contents."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes
  				   suchThat: [:f| (segmentManager segmentContainingObj: f) containsPinned].
  	chunk ifNil:
  		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
  		 chunk ifNil:
  			[^nil].
  		 (segmentManager segmentContainingObj: chunk) containsPinned: true].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self longAt: chunk
  			put: numSlots + (self numSlotsMask << self numSlotsFullShift).
  		 self longAt: chunk + self baseHeaderSize
  			put: ((self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)
  					bitOr: 1 << self pinnedBitShift).
+ 					
+ 		self flag: #Todo. "later on we probably want to do this in the call above"
+ 		gc maybeModifyGCFlagsOf: chunk.
  		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self longAt: chunk
  		put: ((self headerForSlots: numSlots format: formatField classIndex: classIndex)
  				bitOr: 1 << self pinnedBitShift).
+ 	
+ 	self flag: #Todo. "later on we probably want to do this in the call above"
+ 	gc maybeModifyGCFlagsOf: chunk.
  	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlotsInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  The header
  	 will have been filled-in but not the contents.  If no memory is available answer nil."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
  	chunk ifNil:
  		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self longAt: chunk
  			put: numSlots + (self numSlotsMask << self numSlotsFullShift).
  		 self longAt: chunk + self baseHeaderSize
  			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
+ 			
+ 		self flag: #Todo. "later on we probably want to do this in the call above"
+ 		gc maybeModifyGCFlagsOf: chunk.
  		 self checkFreeSpace: GCModeNewSpace ignoring: chunk + self baseHeaderSize.
  		 ^chunk + self baseHeaderSize].
  	self longAt: chunk
  		put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
+ 		
+ 	self flag: #Todo. "later on we probably want to do this in the call above"
+ 	gc maybeModifyGCFlagsOf: chunk.
  	self checkFreeSpace: GCModeNewSpace ignoring: chunk.
  	^chunk!

Item was added:
+ SpurMarker subclass: #SpurAllAtOnceMarker
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurAllAtOnceMarker class>>implicitReturnTypeFor: (in category 'translation') -----
+ implicitReturnTypeFor: aSelector
+ 	"Answer the return type for methods that don't have an explicit return."
+ 	^#void!

Item was added:
+ ----- Method: SpurAllAtOnceMarker class>>simulatorClass (in category 'simulation') -----
+ simulatorClass
+ 	^ SpurAllAtOnceMarkerSimulator!

Item was added:
+ ----- Method: SpurAllAtOnceMarker class>>sourceSortingKey (in category 'translation') -----
+ sourceSortingKey
+ 	"To keep methods in the same order while refactoring..."
+ 	^SpurMemoryManager name!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAccessibleObjectsAndFireEphemerons (in category 'marking') -----
+ markAccessibleObjectsAndFireEphemerons
+ 	self assert: marking.
+ 	self assert: manager validClassTableRootPages.
+ 	self assert: manager segmentManager allBridgesMarked.
+ 	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
+ 		inSmalltalk: [MarkStackRecord ifNotNil: [MarkStackRecord resetTo: 1]].
+ 
+ 	"This must come first to enable stack page reclamation.  It clears
+ 	  the trace flags on stack pages and so must precede any marking.
+ 	  Otherwise it will clear the trace flags of reached pages."
+ 	coInterpreter initStackPageGC.
+ 	self markAndTraceHiddenRoots.
+ 	self markAndTraceExtraRoots.
+ 	self assert: manager validClassTableRootPages.
+ 	coInterpreter markAndTraceInterpreterOops: true.
+ 	self assert: manager validObjStacks.
+ 	self markWeaklingsAndMarkAndFireEphemerons.
+ 	self assert: manager validObjStacks!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAllUnscannedEphemerons (in category 'weakness and ephemerality') -----
+ markAllUnscannedEphemerons
+ 	"After firing the unscanned ephemerons we must scan-mark them.
+ 	 The wrinkle is that doing so may add more ephemerons to the set.
+ 	 So we remove the first element, by overwriting it with the last element,
+ 	 and decrementing the top, and then markAndTrace its contents."
+ 	self assert: (manager noUnscannedEphemerons) not.
+ 	self assert: manager allUnscannedEphemeronsAreActive.
+ 	[manager unscannedEphemerons top > manager unscannedEphemerons start] whileTrue:
+ 		[| ephemeron key lastptr |
+ 		 ephemeron := manager longAt: manager unscannedEphemerons start.
+ 		 lastptr := manager unscannedEphemerons top - manager bytesPerOop.
+ 		 lastptr > manager unscannedEphemerons start ifTrue:
+ 			[manager longAt: manager unscannedEphemerons start put: (manager longAt: lastptr)].
+ 		 manager unscannedEphemerons top: lastptr.
+ 		 key := manager followedKeyOfMaybeFiredEphemeron: ephemeron.
+ 		 manager setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
+ 		 self
+ 			markAndTrace: key;
+ 			markAndTrace: ephemeron]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndShouldScan: (in category 'marking') -----
+ markAndShouldScan: objOop
+ 	"Helper for markAndTrace:.
+ 	 Mark the argument, and answer if its fields should be scanned now.
+ 	 Immediate objects don't need to be marked.
+ 	 Already marked objects have already been processed.
+ 	 Pure bits objects don't need scanning, although their class does.
+ 	 Weak objects should be pushed on the weakling stack.
+ 	 Anything else need scanning."
+ 	| format |
+ 	<inline: true>
+ 	(manager isImmediate: objOop) ifTrue:
+ 		[^false].
+ 	"if markAndTrace: is to follow and eliminate forwarding pointers
+ 	 in its scan it cannot be handed an r-value which is forwarded."
+ 	self assert: (manager isForwarded: objOop) not.
+ 	(manager isMarked: objOop) ifTrue:
+ 		[^false].
+ 	manager setIsMarkedOf: objOop to: true.
+ 	format := manager formatOf: objOop.
+ 	(manager isPureBitsFormat: format) ifTrue: "avoid pushing non-pointer objects on the markStack."
+ 		["Avoid tracing classes of non-objects on the heap, e.g. IRC caches, Sista counters."
+ 		 (manager classIndexOf: objOop) > manager lastClassIndexPun ifTrue:
+ 			[self markAndTraceClassOf: objOop].
+ 		 ^false].
+ 	(manager isWeakFormat: format) ifTrue: "push weaklings on the weakling stack to scan later"
+ 		[manager push: objOop onObjStack: manager weaklingStack.
+ 		 ^false].
+ 	((manager isEphemeronFormat: format)
+ 	 and: [manager activeAndDeferredScan: objOop]) ifTrue:
+ 		[^false].
+ 	^true!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTrace: (in category 'marking') -----
+ markAndTrace: objOop
+ 	"Mark the argument, and all objects reachable from it, and any remaining objects
+ 	 on the mark stack. Follow forwarding pointers in the scan."
+ 	<api>
+ 	<inline: #never>
+ 	"if markAndTrace: is to follow and eliminate forwarding pointers
+ 	 in its scan it cannot be handed an r-value which is forwarded.
+ 	 The assert for this is in markAndShouldScan:"
+ 	(self markAndShouldScan: objOop) ifFalse:
+ 		[^self].
+ 
+ 	"Now scan the object, and any remaining objects on the mark stack."
+ 	self markLoopFrom: objOop!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceClassOf: (in category 'marking') -----
+ markAndTraceClassOf: objOop
+ 	"Ensure the class of the argument is marked, pushing it on the markStack if not already marked.
+ 	 And for one-way become, which can create duplicate entries in the class table, make sure
+ 	 objOop's classIndex refers to the classObj's actual classIndex.
+ 	 Note that this is recursive, but the metaclass chain should terminate quickly."
+ 	<inline: false>
+ 	| classIndex classObj realClassIndex |
+ 	classIndex := manager classIndexOf: objOop.
+ 	classObj := manager classOrNilAtIndex: classIndex.
+ 	self assert: (coInterpreter objCouldBeClassObj: classObj).
+ 	realClassIndex := manager rawHashBitsOf: classObj.
+ 	(classIndex ~= realClassIndex
+ 	 and: [classIndex > manager lastClassIndexPun]) ifTrue:
+ 		[manager setClassIndexOf: objOop to: realClassIndex].
+ 	(manager isMarked: classObj) ifFalse:
+ 		[manager setIsMarkedOf: classObj to: true.
+ 		 self markAndTraceClassOf: classObj.
+ 		 manager push: classObj onObjStack: manager markStack]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceExtraRoots (in category 'marking') -----
+ markAndTraceExtraRoots
+ 	| oop |
+ 	self assert: manager remapBufferCount = 0.
+ 
+ 	1 to: manager extraRootCount do:
+ 		[:i|
+ 		oop := (manager extraRoots at: i) at: 0.
+ 		((manager isImmediate: oop) or: [manager isFreeObject: oop]) ifFalse:
+ 			[self markAndTrace: oop]]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceHiddenRoots (in category 'marking') -----
+ markAndTraceHiddenRoots
+ 	"The hidden roots hold both the class table pages and the obj stacks,
+ 	 and hence need special treatment.  The obj stacks must be marked
+ 	 specially; their pages must be marked, but only the contents of the
+ 	 mournQueue should be marked.
+ 
+ 	 If a class table page is weak we can mark and trace the hiddenRoots,
+ 	 which will not trace through class table pages because they are weak.
+ 	 But if class table pages are strong, we must mark the pages and *not*
+ 	 trace them so that only classes reachable from the true roots will be
+ 	 marked, and unreachable classes will be left unmarked."
+ 
+ 	self markAndTraceObjStack: manager markStack andContents: false.
+ 	self markAndTraceObjStack: manager weaklingStack andContents: false.
+ 	self markAndTraceObjStack: manager mournQueue andContents: true.
+ 
+ 	manager setIsMarkedOf: manager rememberedSetObj to: true.
+ 	manager setIsMarkedOf: manager freeListsObj to: true.
+ 
+ 	(manager isWeakNonImm: manager classTableFirstPage) ifTrue:
+ 		[^self markAndTrace: manager hiddenRootsObj].
+ 
+ 	manager setIsMarkedOf: manager hiddenRootsObj to: true.
+ 	self markAndTrace: manager classTableFirstPage.
+ 	1 to: manager numClassTablePages - 1 do:
+ 		[:i| manager setIsMarkedOf: (manager fetchPointer: i ofObject: manager hiddenRootsObj)
+ 				to: true]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markAndTraceObjStack:andContents: (in category 'marking') -----
+ 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."
+ 	<inline: false>
+ 	| index field |
+ 	stackOrNil = manager nilObj ifTrue:
+ 		[^self].
+ 	manager setIsMarkedOf: stackOrNil to: true.
+ 	self assert: (manager numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
+ 	field := manager fetchPointer: ObjStackNextx ofObject: stackOrNil.
+ 	field ~= 0 ifTrue:
+ 		[self markAndTraceObjStack: field andContents: markAndTraceContents].
+ 	field := stackOrNil.
+ 	[field := manager fetchPointer: ObjStackFreex ofObject: field.
+ 	 field ~= 0] whileTrue:
+ 		[manager setIsMarkedOf: field to: true].
+ 	markAndTraceContents ifFalse:
+ 		[^self].
+ 	"There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
+ 	  if there were 6 slots in an oop stack, full would be 2, and the last 0-rel index is 5."
+ 	index := (manager fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
+ 	[index >= ObjStackFixedSlots] whileTrue:
+ 		[field := manager followObjField: index ofObject: stackOrNil.
+ 		 (manager isImmediate: field) ifFalse:
+ 			[self markAndTrace: field].
+ 		 index := index - 1]!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>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."
+ 	^manager objStack: manager weaklingStack from: startIndex do:
+ 		[:weakling|
+ 		 self deny: (manager isForwarded: weakling).
+ 		 self markAndTraceClassOf: weakling.
+ 		"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
+ 		 0 to: (manager numStrongSlotsOfWeakling: weakling) - 1 do:
+ 			[:i| | field |
+ 			field := manager followOopField: i ofObject: weakling.
+ 			((manager isImmediate: field) or: [manager isMarked: field]) ifFalse:
+ 				[self markAndTrace: field]]]!

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

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markLoopFrom: (in category 'marking') -----
+ markLoopFrom: objOop
+ 	"Scan objOop and all objects on the mark stack, until the mark stack is empty.
+ 	 N.B. When the incremental GC is written this will probably be refactored as
+ 	 markLoopFrom: objOop while: aBlock"
+ 	<inline: true>
+ 	| objToScan field index numStrongSlots scanLargeObject |
+ 
+ 	"Now scan the object, and any remaining objects on the mark stack."
+ 	objToScan := objOop.
+ 	"To avoid overflowing the mark stack when we encounter large objects, we
+ 	 push the obj, then its numStrongSlots, and then index the object from the stack."
+ 	[(manager isImmediate: objToScan)
+ 		ifTrue: [scanLargeObject := true]
+ 		ifFalse:
+ 			[numStrongSlots := manager numStrongSlotsOfInephemeral: objToScan.
+ 			 scanLargeObject := numStrongSlots > self traceImmediatelySlotLimit].
+ 	 scanLargeObject
+ 		ifTrue: "scanning a large object. scan until hitting an unmarked object, then switch to it, if any."
+ 			[(manager isImmediate: objToScan)
+ 				ifTrue:
+ 					[index := manager integerValueOf: objToScan.
+ 					 objToScan := manager topOfObjStack: manager markStack]
+ 				ifFalse:
+ 					[index := numStrongSlots.
+ 					 self markAndTraceClassOf: objToScan].
+ 			 [index > 0] whileTrue:
+ 				[index := index - 1.
+ 				 field := manager fetchPointer: index ofObject: objToScan.
+ 				 (manager isNonImmediate: field) ifTrue:
+ 					[(manager isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
+ 						[field := manager fixFollowedField: index ofObject: objToScan withInitialValue: field].
+ 					 (self markAndShouldScan: field) ifTrue:
+ 						[index > 0 ifTrue:
+ 							[(manager topOfObjStack: manager markStack) ~= objToScan ifTrue: 
+ 								[manager push: objToScan onObjStack: manager markStack].
+ 							 manager push: (manager integerObjectOf: index) onObjStack: manager markStack].
+ 						 objToScan := field.
+ 						 index := -1]]].
+ 			 index >= 0 ifTrue: "if loop terminated without finding an unmarked referent, switch to top of stack."
+ 				[objToScan := manager popObjStack: manager markStack.
+ 				 objToScan = objOop ifTrue:
+ 					[objToScan := manager popObjStack: manager markStack]]]
+ 		ifFalse: "scanning a small object. scan, marking, pushing unmarked referents, then switch to the top of the stack."
+ 			[index := numStrongSlots.
+ 			 self markAndTraceClassOf: objToScan.
+ 			 [index > 0] whileTrue:
+ 				[index := index - 1.
+ 				 field := manager fetchPointer: index ofObject: objToScan.
+ 				 (manager isNonImmediate: field) ifTrue:
+ 					[(manager isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
+ 						[field := manager fixFollowedField: index ofObject: objToScan withInitialValue: field].
+ 					 (self markAndShouldScan: field) ifTrue:
+ 						[manager push: field onObjStack: manager markStack.
+ 						 ((manager rawNumSlotsOf: field) > self traceImmediatelySlotLimit
+ 						  and: [(numStrongSlots := manager numStrongSlotsOfInephemeral: field) > self traceImmediatelySlotLimit]) ifTrue:
+ 							[manager push: (manager integerObjectOf: numStrongSlots) onObjStack: manager markStack]]]].
+ 			 objToScan := manager popObjStack: manager markStack].
+ 	 objToScan notNil] whileTrue!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markObjects: (in category 'marking') -----
+ markObjects: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
+ 	<inline: #never> "for profiling"
+ 	"Mark all accessible objects.  objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
+ 	 is true if all objects are unmarked and/or if unmarked classes shoud be removed from the class table."
+ 	"If the incremental collector is running mark bits may be set; stop it and clear them if necessary."
+ 	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'marking...'; flush].
+ 	manager runLeakCheckerFor: GCModeFull.
+ 
+ 	manager shutDownGlobalIncrementalGC: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
+ 	manager initializeUnscannedEphemerons.
+ 	manager initializeMarkStack.
+ 	manager initializeWeaklingStack.
+ 	marking := true.
+ 	self markAccessibleObjectsAndFireEphemerons.
+ 	manager expungeDuplicateAndUnmarkedClasses: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
+ 	manager nilUnmarkedWeaklingSlots.
+ 	marking := false!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>markWeaklingsAndMarkAndFireEphemerons (in category 'weakness and ephemerality') -----
+ 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 strong slots traced before firing ephemerons..."
+ 	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
+ 	  (manager sizeOfObjStack: manager weaklingStack) > numTracedWeaklings] whileTrue.
+ 	 manager noUnscannedEphemerons ifTrue:
+ 		[coInterpreter
+ 			markAndTraceUntracedReachableStackPages;
+ 	 		markAndTraceMachineCodeOfMarkedMethods;
+ 			freeUntracedStackPages;
+ 			freeUnmarkedMachineCode.
+ 		 ^self].
+ 	 self markInactiveEphemerons ifFalse:
+ 		[manager fireAllUnscannedEphemerons].
+ 	 self markAllUnscannedEphemerons]
+ 		repeat!

Item was added:
+ ----- Method: SpurAllAtOnceMarker>>traceImmediatelySlotLimit (in category 'marking') -----
+ traceImmediatelySlotLimit
+ 	"Arbitrary level at which to defer tracing large objects until later.
+ 	 The average slot size of Smalltalk objects is typically near 8.
+ 	 We do require traceImmediatelySlotLimit to be < numSlotsMask."
+ 	^64!

Item was added:
+ SpurAllAtOnceMarker subclass: #SpurAllAtOnceMarkerSimulator
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was changed:
  CogClass subclass: #SpurCompactor
  	instanceVariableNames: 'coInterpreter manager scavenger'
  	classVariableNames: ''
  	poolDictionaries: 'SpurMemoryManagementConstants VMBasicConstants VMSpurObjectRepresentationConstants'
+ 	category: 'VMMaker-SpurGarbageCollector'!
- 	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurCompactor commentStamp: '' prior: 0!
- !SpurCompactor commentStamp: 'cb 4/27/2018 09:38' prior: 0!
  Abstract common superclass of all compactors to define apis and simulation variables.
  
  The full GC in Spur is split in two, the marking phase and the compactor phase. The subclasses of SpurCompactor are implementations of the second phase, so they are called once the marking phase is finished. SpurCompactor is reponsible for:
  - freeing unmarked objects
  - compacting the live old space objects (though each subclass define what it does, some spurCompactor may not compact)
  - unmarking all objects remaining live
  - updating oops directly referred by the VM when they are moved (remapObj:/shouldRemapObj: thingy)
  
  The main apis are the following:
  - biasForGC/biasForSnapshot: tells the compactor if the GC is performed for snapshots or not, in general we want to compact more aggressively for snapshots to avoid saving large files with many unused space.
  - compact: main API, should free the unmarked object, unmark the objects remaining live and potentially compact the heap
  - remapObj:/shouldRemapObj: => Not really sure what this does, it seems it has to do with updating oops directly referred by the VM when they are moved. 
  - postSwizzleAction: if you want to do something at start-up after swizzle phase (typically useful if your compaction algo uses segInfos)
  
  Instance Variables
  	coInterpreter:				<StackInterpreter>
  	scavenger:					<SpurGenerationScavenger>
  	manager:					<SpurMemoryManager>!

Item was added:
+ CogClass subclass: #SpurGarbageCollector
+ 	instanceVariableNames: 'marker scavenger compactor manager coInterpreter allocatorShouldAllocateBlack'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'SpurMemoryManagementConstants'
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurGarbageCollector class>>classesForTranslation (in category 'as yet unclassified') -----
+ classesForTranslation
+ 
+ 	^ self shouldBeImplemented!

Item was added:
+ ----- Method: SpurGarbageCollector class>>compactorClass (in category 'as yet unclassified') -----
+ compactorClass
+ 
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SpurGarbageCollector class>>declareCVarsIn: (in category 'as yet unclassified') -----
+ declareCVarsIn: aCCodeGenerator
+ 
+ 	super declareCVarsIn: aCCodeGenerator.
+ 	aCCodeGenerator
+ 		var: #allocatorShouldAllocateBlack type: #usqInt.!

Item was added:
+ ----- Method: SpurGarbageCollector class>>markerClass (in category 'as yet unclassified') -----
+ markerClass
+ 
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SpurGarbageCollector>>allocatorShouldAllocateBlack (in category 'accessing') -----
+ allocatorShouldAllocateBlack
+ 
+ 	<inline: true>
+ 	^ allocatorShouldAllocateBlack!

Item was added:
+ ----- Method: SpurGarbageCollector>>allocatorShouldAllocateBlack: (in category 'accessing') -----
+ allocatorShouldAllocateBlack: anObject
+ 
+ 	allocatorShouldAllocateBlack := anObject.!

Item was added:
+ ----- Method: SpurGarbageCollector>>coInterpreter (in category 'accessing') -----
+ coInterpreter
+ 
+ 	^ coInterpreter!

Item was added:
+ ----- Method: SpurGarbageCollector>>coInterpreter: (in category 'accessing') -----
+ coInterpreter: anObject
+ 
+ 	<doNotGenerate>
+ 	coInterpreter := anObject.!

Item was added:
+ ----- Method: SpurGarbageCollector>>compactor (in category 'accessing') -----
+ compactor
+ 
+ 	<doNotGenerate>
+ 	^ compactor!

Item was added:
+ ----- Method: SpurGarbageCollector>>compactor: (in category 'accessing') -----
+ compactor: anObject
+ 
+ 	compactor := anObject.!

Item was added:
+ ----- Method: SpurGarbageCollector>>doScavenge: (in category 'scavenge') -----
+ doScavenge: tenuringCriterion
+ 	"The inner shell for scavenge, abstrascted out so globalGarbageCollect can use it."
+ 	<inline: false>
+ 	manager doAllocationAccountingForScavenge.
+ 	manager gcPhaseInProgress: ScavengeInProgress.
+ 	manager pastSpaceStart: (scavenger scavenge: tenuringCriterion).
+ 	self assert: (self
+ 					oop: manager pastSpaceStart
+ 					isGreaterThanOrEqualTo: scavenger pastSpace start
+ 					andLessThanOrEqualTo: scavenger pastSpace limit).
+ 	manager freeStart: scavenger eden start.
+ 	manager gcPhaseInProgress: 0.
+ 	manager resetAllocationAccountingAfterGC.
+ 	
+ 	self incrementalCollect!

Item was added:
+ ----- Method: SpurGarbageCollector>>fullGC (in category 'global') -----
+ fullGC
+ 
+ 	^ self subclassResponsibility!

Item was added:
+ ----- Method: SpurGarbageCollector>>incrementalCollect (in category 'global') -----
+ incrementalCollect
+ 
+ 	^ self subclassResponsibility!

Item was added:
+ ----- Method: SpurGarbageCollector>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	allocatorShouldAllocateBlack := false!

Item was added:
+ ----- Method: SpurGarbageCollector>>manager (in category 'accessing') -----
+ manager
+ 
+ 	^ manager!

Item was added:
+ ----- Method: SpurGarbageCollector>>manager: (in category 'accessing') -----
+ manager: anObject
+ 
+ 	<doNotGenerate>
+ 	manager := anObject.!

Item was added:
+ ----- Method: SpurGarbageCollector>>marker (in category 'accessing') -----
+ marker
+ 	
+ 	<doNotGenerate>
+ 	^ marker!

Item was added:
+ ----- Method: SpurGarbageCollector>>marker: (in category 'accessing') -----
+ marker: anObject
+ 
+ 	<doNotGenerate>
+ 	marker := anObject.!

Item was added:
+ ----- Method: SpurGarbageCollector>>maybeModifyGCFlagsOf: (in category 'as yet unclassified') -----
+ maybeModifyGCFlagsOf: objOop
+ 
+ 	<doNotGenerate>!

Item was added:
+ ----- Method: SpurGarbageCollector>>scavenger (in category 'accessing') -----
+ scavenger
+ 
+ 	^ scavenger!

Item was added:
+ ----- Method: SpurGarbageCollector>>scavenger: (in category 'accessing') -----
+ scavenger: anObject
+ 
+ 	scavenger := anObject.!

Item was added:
+ ----- Method: SpurGarbageCollector>>scavengingGCTenuringIf: (in category 'scavenge') -----
+ scavengingGCTenuringIf: tenuringCriterion
+ 	"Run the scavenger."
+ 	<inline: false>
+ 	self assert: manager remapBufferCount = 0.
+ 	(self asserta: scavenger eden limit - manager freeStart > coInterpreter interpreterAllocationReserveBytes) ifFalse:
+ 		[coInterpreter tab;
+ 			printNum: scavenger eden limit - manager freeStart; space;
+ 			printNum: coInterpreter interpreterAllocationReserveBytes; space;
+ 			printNum: coInterpreter interpreterAllocationReserveBytes - (scavenger eden limit - manager freeStart); cr].
+ 	manager checkMemoryMap.
+ 	manager checkFreeSpace: GCModeNewSpace.
+ 	manager runLeakCheckerFor: GCModeNewSpace.
+ 
+ 	coInterpreter
+ 		preGCAction: GCModeNewSpace;
+ 		"would prefer this to be in mapInterpreterOops, but
+ 		 compatibility with ObjectMemory dictates it goes here."
+ 		flushMethodCacheFrom: manager newSpaceStart to: manager oldSpaceStart.
+ 	manager needGCFlag: false.
+ 
+ 	manager gcStartUsecs: coInterpreter ioUTCMicrosecondsNow.
+ 
+ 	self doScavenge: tenuringCriterion.
+ 
+ 	manager statScavenges: manager statScavenges + 1.
+ 	manager statGCEndUsecs: coInterpreter ioUTCMicrosecondsNow.
+ 	manager statSGCDeltaUsecs: manager statGCEndUsecs - manager gcStartUsecs.
+ 	manager statScavengeGCUsecs: manager statScavengeGCUsecs + manager statSGCDeltaUsecs.
+ 	manager statRootTableCount: scavenger rememberedSetSize.
+ 
+ 	scavenger logScavenge.
+ 
+ 	coInterpreter postGCAction: GCModeNewSpace.
+ 
+ 	manager runLeakCheckerFor: GCModeNewSpace.
+ 	manager checkFreeSpace: GCModeNewSpace!

Item was changed:
  CogClass subclass: #SpurGenerationScavenger
  	instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize previousRememberedSetSize rememberedSetRedZone rememberedSetLimit refCountToShrinkRT weakList ephemeronList tenureCriterion tenureThreshold tenuringClassIndex tenuringProportion numRememberedEphemerons scavengeLog scavengeLogRecord statSurvivorCount statTenures'
  	classVariableNames: ''
  	poolDictionaries: 'SpurMemoryManagementConstants'
+ 	category: 'VMMaker-SpurGarbageCollector'!
- 	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurGenerationScavenger commentStamp: '' prior: 0!
- !SpurGenerationScavenger commentStamp: 'eem 11/7/2017 17:26' prior: 0!
  SpurGenerationScavenger is an implementation of David Ungar's Generation Scavenging garbage collection algorithm.  See
  	Generation Scavenging, A Non-disruptive, High-Performance Storage Reclamation Algorithm
  	David Ungar
  	Proceeding
  	SDE 1 Proceedings of the first ACM SIGSOFT/SIGPLAN software engineering symposium on Practical software development environments
  	Pages 157 - 167 
  	ACM New York, NY, USA ©1984 
  
  Also relevant are
  	An adaptive tenuring policy for generation scavengers
  	David Ungar & Frank Jackson
  	ACM Transactions on Programming Languages and Systems (TOPLAS) TOPLAS Homepage archive
  	Volume 14 Issue 1, Jan. 1992 
  	Pages 1 - 27 
  	ACM New York, NY, USA ©1992
  and
  	Ephemerons: a new finalization mechanism
  	Barry Hayes
  	Proceedings of the 12th ACM SIGPLAN conference on Object-oriented programming, systems, languages, and applications
  	Pages 176-183 
  	ACM New York, NY, USA ©1997
  
  See text below the variable definitions and explanation below for a full explanation of weak and ephemeron processing.
  
  Instance Variables
  	coInterpreter:					<StackInterpreterSimulator|CogVMSimulator>
  	eden:							<SpurNewSpaceSpace>
  	ephemeronList:					<Integer|nil>
  	futureSpace:					<SpurNewSpaceSpace>
  	futureSurvivorStart:				<Integer address>
  	manager:						<SpurMemoryManager|Spur32BitMMLESimulator et al>
  	numRememberedEphemerons:	<Integer>
  	pastSpace:						<SpurNewSpaceSpace>
  	previousRememberedSetSize:	<Integer>
  	rememberedSet:				<CArrayAccessor on: Array>
  	rememberedSetSize:			<Integer>
  	tenuringProportion:				<Float>
  	tenuringThreshold:				<Integer address>
  	weakList:						<Integer|nil>
  
  coInterpreter
  	- the interpreter/vm, in this context, the mutator
  
  manager
  	- the Spur memory manager
  
  eden
  	- the space containing newly created objects
  
  futureSpace
  	- the space to which surviving objects are copied during a scavenge
  
  futureSurvivorStart
  	- the allocation pointer into futureSpace
  
  pastSpace
  	- the space surviving objects live in until the next scavenge
  
  rememberedSet
  	- the root old space objects that refer to objects in new space; a scavenge starts form these roots and the interpreter's stack
  
  rememberedSetSize
  	- the size of the remembered set, also the first unused index in the rememberedSet
  
  previousRememberedSetSize:
  	- the size of the remembered set before scavenging objects in future space.
  
  numRememberedEphemerons
  	- the number of unscavenged ephemerons at the front of the rememberedSet.
  
  ephemeronList
  	- the head of the list of corpses of unscavenged ephemerons reached in the current phase
  
  weakList
  	- the head of the list of corpses of weak arrays reached during the scavenge.
  
  tenuringProportion
  	- the amount of pastSpace below which the system will not tenure unless futureSpace fills up, and above which it will eagerly tenure
  
  tenuringThreshold
  	- the pointer into pastSpace below which objects will be tenured
  
  Weakness and Ephemerality in the Scavenger.
  Weak arrays should not hold onto their referents (except from their strong fileds, their named inst vars).  Ephemerons are objects that implement instance-based finalization; attaching an ephemeron to an object keeps that object alive and causes the ephemeron to "fire" when the object is only reachable from the ephemeron (or other ephemerons & weak arrays).  They are a special kind of Associations that detect when their keys are about to die, i.e. when an ephemeron's key is not reachable from the roots except from weak arrays and other ephemerons with about-to-die keys.  Note that if an ephemeron's key is not about to die then references from the rest of the ephemeron can indeed prevent ephemeron keys from dying.
  
  The scavenger is concerned with collecting objects in new space, therefore it ony deals with weak arrays and ephemerons that are either in the remembered set or in new space.  By deferring scanning these objects until other reachable objects have been scavenged, the scavenger can detect dead or dying references.
  
  Weak Array Processing
  In the case of weak arrays this is simple.  The scavenger refuses to scavenge the referents of weak arrays in scavengeReferentsOf: until the entire scavenge is over.  It then scans the weak arrays in the remembered set and in future space and nils all fields in them that are referring to unforwarded objects in eden and past space, because these objects have not survived the scavenge.  The root weak arrays remaining to be scavenged are in the remembered table.  Surviving weak arrays in future space are collected on a list.  The list is threaded through the corpses of weak arrays in eden and/or past space.  weakList holds the slot offset of the first weak array found in eden and/or past space.  The next offset is stored in the weak array corpse's identityHash and format fields (22 bits & 5 bits of allocationUnits, for a max new space size of 2^28 bytes, 256Mb).  The list is threaded throguh corpses, but the surviving arrays are pointed to by the corpses' forwarding pointers.
  
  Ephemeron Processing
  The case of ephemerons is a little more complicated because an ephemeron's key should survive.  The scavenger is cyclical.  It scavenges the remembered set, which may copy and forward surviving objects in past and/or eden spaces to future space.  It then scavenges those promoted objects in future space until no more are promoted, which may in turn remember more objects.  The cycles continue until no more objects get promoted to future space and no more objects get remembered.  At this point all surviving objecta are in futureSpace.
  
  So if the scavenger does not scan ephemerons in the remembered set or in future space until the scavenger finishes cycling, it can detect ephemerons whose keys are about to die because these will be unforwarded objects in eden and/or past space.  Ephemerons encountered in the remembered set are either processed like ordinary objects if their keys have been promoted to futureSpace, or are moved to the front of the rememberedSet (because, dear reader, it is a sequence) if their keys have not been promoted.  Ephemerons encountered in scavengeReferentsOf: are either scanned like normal objects if their keys have been promoted, or added to the ephemeronList, organized identically to the weakList, if their keys are yet to be promoted.  Since references from other ephemerons with surviving keys to ephemeron keys can and should prevent the ephemerons whose keys they are from firing the scavenger does not fire ephemerons unless all unscavenged ephemerons have unscavenged keys.  So the unsca
 venged ephemerons (they will be at the beginning of the remembered set and on the ephemeronList) are scanned and any that have promoted keys are scavenged.  But if no unscavenged ephemerons have surviving keys then all the unscavenged ephemerons are fired and then scavenged.  This in turn may remember more objects and promote more objects to future space, and encounter more unscavenged ephemerons.  So the scavenger continues until no more objects are remembered, no more objects are promoted to future space and no more unscavenged ephemerons exist.!

Item was removed:
- ----- Method: SpurGenerationScavenger class>>isNonArgumentImplicitReceiverVariableName: (in category 'translation') -----
- isNonArgumentImplicitReceiverVariableName: instVarName
- 	^#('self' 'coInterpreter' 'manager') includes: instVarName!

Item was changed:
  SpurCompactor subclass: #SpurHybridCompactor
  	instanceVariableNames: 'planningCompactor selectiveCompactor planNotSelect'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!
- 	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurHybridCompactor commentStamp: '' prior: 0!
- !SpurHybridCompactor commentStamp: 'eem 6/6/2018 19:25' prior: 0!
  A SpurHybridCompactor is a compactor that uses SpurSelectiveCompactor for normal GC compactions, but uses SpurPlanningCompactor for snapshot.
  
  Instance Variables
  	planNotSelect:			<Boolean>
  	planningCompactor:	<SpurPlanningCompactor>
  	selectiveCompactor:	<SpurSelectiveCompactor>
  
  planNotSelect
  	- the boolean that selects between the two compactors; if true it chooses SpurPlanningCompactor
  
  planningCompactor
  	- the SpurPlanningCompactor
  
  selectiveCompactor
  	- the SpurSelectiveCompactor
  !

Item was added:
+ SpurCompactor subclass: #SpurIncrementalCompactor
+ 	instanceVariableNames: 'isCompacting segmentToFill shouldCompact currentHeapPointer currentSegment'
+ 	classVariableNames: 'MaxOccupationForCompaction'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurIncrementalCompactor class>>declareCVarsIn: (in category 'as yet unclassified') -----
+ declareCVarsIn: aCCodeGenerator
+ 
+ 	super declareCVarsIn: aCCodeGenerator.
+ 	aCCodeGenerator var: #segmentToFill type: #'SpurSegmentInfo *'.!

Item was added:
+ ----- Method: SpurIncrementalCompactor class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	super initialize.
+ 	"If the segment is occupied by more than MaxOccupationForCompaction, 
+ 	 it's not worth compacting it, whatever the rest of the system looks like.
+ 	 MaxOccupationForCompaction is included in [0;16rFFFF]."
+ 	MaxOccupationForCompaction := 16rD000. "81%"!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>assertNoSegmentBeingCompacted (in category 'testing') -----
+ assertNoSegmentBeingCompacted
+ 	"Assertion only - no segment is being claimed at this point"
+ 	| segInfo |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	0 to: manager numSegments - 1 do:
+ 		[:i|
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		 self deny: (self isSegmentBeingCompacted: segInfo)].!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>compact (in category 'api') -----
+ compact
+ 
+ 	self incrementalCompact!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>compactSegment:freeStart:segIndex: (in category 'incremental compaction') -----
+ compactSegment: segInfo freeStart: initialFreeStart segIndex: segIndex
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	
+ 	| currentEntity fillStart bytesToCopy bridge copy |
+ 	fillStart := initialFreeStart.
+ 	bridge := manager segmentManager bridgeFor: segInfo.
+ 	currentEntity := manager objectStartingAt: segInfo segStart.
+ 	
+ 	self deny: segIndex = 0. "Cannot compact seg 0"
+ 	[self oop: currentEntity isLessThan: bridge] whileTrue:
+ 		[(manager isFreeObject: currentEntity)
+ 			ifTrue: 
+ 				[manager detachFreeObject: currentEntity.
+ 				 "To avoid confusing too much Spur (especially the leak/free checks), we mark the free chunk as a word object."
+ 				 manager set: currentEntity classIndexTo: manager wordSizeClassIndexPun formatTo: manager wordIndexableFormat]
+ 			ifFalse: 
+ 				["Copy the object in segmentToFill and replace it by a forwarder."
+ 				 self assert: (manager isPinned: currentEntity) not. 
+ 				 bytesToCopy := manager bytesInBody: currentEntity.
+ 				 manager memcpy: fillStart asVoidPointer _: (manager startOfObject: currentEntity) asVoidPointer _: bytesToCopy.
+ 				
+ 				 copy := manager objectStartingAt: fillStart.
+ 				 (manager isRemembered: copy) ifTrue: 
+ 					["copy has the remembered bit set, but is not in the remembered table."
+ 					 manager setIsRememberedOf: copy to: false.
+ 					 scavenger remember: copy].
+ 				
+ 				 manager forward: currentEntity to: (manager objectStartingAt: fillStart).
+ 				 fillStart := fillStart + bytesToCopy.
+ 				 self assert: (self oop: fillStart isLessThan: (segmentToFill segLimit - manager bridgeSize))].
+ 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
+ 	
+ 	self assert: currentEntity = bridge.
+ 	segmentToFill := segmentToFill + 1.
+ 	^ fillStart!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>computeSegmentsToCompact (in category 'compaction planning') -----
+ computeSegmentsToCompact
+ 	"Compute segments to compact: least occupied.
+ 	 Answers true if compaction should be done 
+ 	 (at least 1 segment is being compacted and
+ 	 there is a segment to compact into)."
+ 	| canStillClaim aboutToClaim aboutToClaimSegment atLeastOneSegmentToCompact |
+ 	<var: 'aboutToClaimSegment' type: #'SpurSegmentInfo *'>
+ 	atLeastOneSegmentToCompact := false.
+ 	aboutToClaimSegment := self findNextSegmentToCompact.
+ 	"Segment to fill is one of the segment compacted last GC. 
+ 	 If no segment were compacted last GC, and that there is 
+ 	 at least one segment to compact, allocate a new one."
+ 	aboutToClaimSegment ifNil: [^false].
+ 	segmentToFill ifNil:
+ 		[self findOrAllocateSegmentToFill.
+ 		 segmentToFill ifNil: ["Abort compaction"^false]].
+ 	canStillClaim := segmentToFill segSize - manager bridgeSize.
+ 	[aboutToClaimSegment ifNil: [^atLeastOneSegmentToCompact].
+ 	 aboutToClaim := self sizeClaimedIn: aboutToClaimSegment.
+ 	 aboutToClaim < canStillClaim ] whileTrue: 
+ 		[self markSegmentAsBeingCompacted: aboutToClaimSegment.
+ 		 atLeastOneSegmentToCompact := true.
+ 		 canStillClaim := canStillClaim - aboutToClaim.
+ 		 aboutToClaimSegment := self findNextSegmentToCompact].
+ 	^atLeastOneSegmentToCompact!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>doIncrementalCompact (in category 'incremental compaction') -----
+ doIncrementalCompact
+ 
+ 	| segInfo |
+ 	currentSegment to: manager numSegments - 1 do:
+ 		[:i | 
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		(self isSegmentBeingCompacted: segInfo)
+ 			ifTrue: [currentSegment := i.
+ 				currentHeapPointer := self compactSegment: segInfo freeStart: currentHeapPointer segIndex: i.
+ 				
+ 				self flag: #Todo. "for now we compact on segment at a time"
+ 				^ currentSegment = manager numSegments - 1
+ 					ifTrue: [true]
+ 					ifFalse: [false]]].
+ 	^ true!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>findAndSetSegmentToFill (in category 'segment to fill') -----
+ findAndSetSegmentToFill
+ 	| segInfo |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	0 to: manager numSegments - 1 do:
+ 		[:i| 
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		(self segmentIsEmpty: segInfo)
+ 			ifTrue: [segmentToFill := segInfo. ^i]].
+ 	^-1!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>findNextSegmentToCompact (in category 'compaction planning') -----
+ findNextSegmentToCompact
+ 	"Answers the next segment to compact or nil if none.
+ 	  The next segment to compact:
+ 	 - cannot be segment 0 (Segment 0 has specific objects 
+ 	  (nil, true, etc.) and special size computed at start-up 
+ 	  that we don't want to deal with)
+ 	 - cannot have a high occupation rate (> MaxOccupationForCompaction)"
+ 	| leastOccupied leastOccupiedSegment tempOccupied segInfo |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	leastOccupied := 16rFFFF.
+ 	1 to: manager numSegments - 1 do:
+ 		[:i|
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		 ((self isSegmentBeingCompacted: segInfo) or: [segInfo containsPinned or: [manager segmentManager isEmptySegment: segInfo] ])
+ 			ifFalse: 
+ 				[(tempOccupied := self occupationOf: segInfo) <= leastOccupied
+ 					ifTrue: [ leastOccupied := tempOccupied.
+ 							 leastOccupiedSegment := segInfo ]]].
+ 	leastOccupied > MaxOccupationForCompaction ifTrue:
+ 		[^self cCoerceSimple: nil to: #'SpurSegmentInfo *'].
+ 	^leastOccupiedSegment!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>findOrAllocateSegmentToFill (in category 'segment to fill') -----
+ findOrAllocateSegmentToFill
+ 	"There was no compacted segments from past GC that we can directly re-use.
+ 	 We need either to find an empty segment or allocate a new one."
+ 	| segIndex |
+ 	self findAndSetSegmentToFill.
+ 	segmentToFill ifNotNil: [^0].
+ 	
+ 	"No empty segment. We need to allocate a new one"
+ 	(manager growOldSpaceByAtLeast: manager growHeadroom) ifNil: ["failed to allocate"^0].
+ 	
+ 	"We don't know which segment it is that we've just allocated... So we look for it... This is a bit dumb."
+ 	segIndex := self findAndSetSegmentToFill.
+ 	self assert: segmentToFill ~~ nil.!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>finishCompaction (in category 'incremental compaction') -----
+ finishCompaction
+ 
+ 	self setFreeChunkOfCompactedIntoSegment.
+ 	self postCompactionAction!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>freePastSegmentsAndSetSegmentToFill (in category 'api') -----
+ freePastSegmentsAndSetSegmentToFill	
+ 	"The first segment being claimed met becomes the segmentToFill. The others are just freed."
+ 	| segInfo |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	segmentToFill := nil.
+ 	0 to: manager numSegments - 1 do:
+ 		[:i|
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		 (self isSegmentBeingCompacted: segInfo)
+ 			ifTrue: 
+ 				[manager 
+ 					initFreeChunkWithBytes: segInfo segSize - manager bridgeSize 
+ 					at: segInfo segStart.
+ 				 segmentToFill ifNil: [segmentToFill := segInfo]]]!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>incrementalCompact (in category 'api') -----
+ incrementalCompact
+ 
+ 	self initializeCompactionIfNecessary.
+ 	
+ 	self doIncrementalCompact
+ 		ifTrue: [
+ 			self finishCompaction.
+ 			^ true].
+ 		
+ 	^ false!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	isCompacting := false.
+ 	currentSegment := 0!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>initializeCompactionIfNecessary (in category 'incremental compaction') -----
+ initializeCompactionIfNecessary
+ 
+ 	isCompacting
+ 		ifFalse: [self assertNoSegmentBeingCompacted.
+ 				self planCompactionAndReserveSpace.
+ 				
+ 				shouldCompact ifTrue: [currentHeapPointer := segmentToFill segStart]].
+ 			
+ 	isCompacting := true
+ 	!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>isSegmentBeingCompacted: (in category 'testing') -----
+ isSegmentBeingCompacted: segInfo 
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	"Swizzle is abused bit 16 isBeingCompacted bits 0-15 occupation"
+ 	^ segInfo swizzle anyMask: 1 << 16!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>markSegmentAsBeingCompacted: (in category 'segment access') -----
+ markSegmentAsBeingCompacted: segInfo 
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	"Swizzle is abused bit 16 isBeingCompacted bits 0-15 occupation"
+ 	segInfo swizzle: (segInfo swizzle bitOr: 1 << 16)!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>occupationOf: (in category 'segment access') -----
+ occupationOf: segInfo 
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	"Swizzle is abused bit 16 isBeingCompacted bits 0-15 occupation"
+ 	^segInfo swizzle bitAnd: 16rFFFF!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>planCompactionAndReserveSpace (in category 'compaction planning') -----
+ planCompactionAndReserveSpace
+ 
+ 	shouldCompact := self computeSegmentsToCompact.
+ 	shouldCompact
+ 		ifTrue: [self reserveSegmentToFill]
+ 	
+ 	!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>postCompactionAction (in category 'as yet unclassified') -----
+ postCompactionAction
+ 	| allFlags |
+ 	"For now we don't optimize and just follow everything everywhere on stack and in caches, let's see in the profiler if we need to optimize with those cases. My guess is that this is < 100 microSecond"
+ 	manager followSpecialObjectsOop.
+ 	allFlags := BecamePointerObjectFlag + BecameActiveClassFlag bitOr: BecameCompiledMethodFlag.
+ 	"Note: there is not the OldBecameNewFlag"
+ 	"gcMode flag is cleared after postBecomeAction, reset it."
+ 	manager coInterpreter postBecomeAction: allFlags.
+ 	manager coInterpreter setGCMode: GCModeFull.
+ 	
+ 	"Special to selective, crazy objects can be forwarded..."
+ 	"manager postBecomeScanClassTable: allFlags. => Done in followClassTable"
+ 	manager followClassTable.
+ 	manager followProcessList.
+ 	manager followForwardedObjStacks.
+ 	
+ 	"Not sure the following are needed...
+ 	coInterpreter mapInterpreterOops.
+ 	manager mapExtraRoots."
+ 	self assert: manager validClassTableHashes.!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>reserveSegmentToFill (in category 'segment access') -----
+ reserveSegmentToFill
+ 	"remove the free space from the freeLists so the mutator cannot allocate in this segment"
+ 	
+ 	| freeChunk |
+ 	self assert: segmentToFill notNil.
+ 	
+ 	freeChunk := manager objectStartingAt: segmentToFill segStart.
+ 	self assert: (self segmentIsEmpty: freeChunk).
+ 	
+ 	manager detachFreeObject: freeChunk!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>restoreSwizzle (in category 'api') -----
+ restoreSwizzle
+ 	"Since the compact abuses the swizzle field of segment, it needs to be reset after start-up."
+ 	
+ 	| segInfo |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	0 to: manager numSegments - 1 do:
+ 		[:i|
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		 segInfo swizzle: 0 ]!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>segmentIsEmpty: (in category 'testing') -----
+ segmentIsEmpty: segInfo
+ 	"a free segment contains only a free chunk and a bridge (every segment ends in one of these)"
+ 
+ 	^ manager segmentManager isEmptySegment: segInfo
+ 
+ 	!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>setFreeChunkOfCompactedIntoSegment (in category 'segment access') -----
+ setFreeChunkOfCompactedIntoSegment
+ 
+ 	segmentToFill ifNil: [^ self].
+ 
+ 	manager 
+ 		addFreeChunkWithBytes: segmentToFill segSize - manager bridgeSize + segmentToFill segStart - currentHeapPointer 
+ 		at: currentHeapPointer.!

Item was added:
+ ----- Method: SpurIncrementalCompactor>>sizeClaimedIn: (in category 'segment access') -----
+ sizeClaimedIn: segment 
+ 	<var: 'segment' type: #'SpurSegmentInfo *'>
+ 	<var: 'ratio' type: #'double'>
+ 	"careful with overflow here"
+ 	"roundedup used ratio (+1 to round up)"
+ 	| ratio |
+ 	ratio := ((self occupationOf: segment) + 1) asFloat / 16rFFFF.
+ 	^(ratio * (segment segSize - manager bridgeSize)) asInteger !

Item was added:
+ SpurGarbageCollector subclass: #SpurIncrementalGarbageCollector
+ 	instanceVariableNames: 'phase'
+ 	classVariableNames: 'InCompactingPhase InMarkingPhase InSweepingPhase'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector class>>classesForTranslation (in category 'as yet unclassified') -----
+ classesForTranslation
+ 
+ 	^ { SpurGarbageCollector . self . SpurGenerationScavenger . SpurIncrementalMarker . SpurIncrementalSweeper . SpurIncrementalCompactor . SpurIncrementalSweepAndCompact }!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector class>>compactorClass (in category 'as yet unclassified') -----
+ compactorClass
+ 
+ 	^ SpurIncrementalSweepAndCompact!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 
+ 	InCompactingPhase := 0.
+ 	InMarkingPhase := 1.
+ 	InSweepingPhase := 2.!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector class>>markerClass (in category 'as yet unclassified') -----
+ markerClass
+ 
+ 	^ SpurIncrementalMarker!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector class>>simulatorClass (in category 'as yet unclassified') -----
+ simulatorClass
+ 
+ 	^ SpurIncrementalGarbageCollectorSimulator!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector>>fullGC (in category 'global') -----
+ fullGC
+ 	"We need to be able to make a full GC, e.g. when we save the image. Use the made progress and finish the collection"
+ 	
+ 	self assert: self validObjStacks.
+ 	
+ 	coInterpreter setGCMode: GCModeNewSpace.
+ 	self doScavenge: MarkOnTenure.
+ 	coInterpreter setGCMode: GCModeIncremental.
+ 	
+ 	marker completeMarkObjects.
+ 	compactor compact.
+ 	
+ 	"we do not need to make a complete mark, we just need to resolve and delete forwarders"
+ 	marker resolveAllForwarders!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector>>incrementalCollect (in category 'as yet unclassified') -----
+ incrementalCollect
+ 
+ 	phase = InMarkingPhase
+ 		ifTrue: [
+ 			marker incrementalMarkObjects
+ 				ifTrue: [
+ 					manager allPastSpaceObjectsDo: [:obj | self assert: (manager isWhite: obj)].
+ 					
+ 					"when sweeping the mutator needs to allocate new objects black as we do not have any information about them.
+ 					We only know if they should get swept after the next marking -> keep them alive for this cycle"
+ 					self allocatorShouldAllocateBlack: true.
+ 					phase := InSweepingPhase.
+ 					
+ 					"marking is done and thus all forwarding references are resolved -> we can use the now free segments that were 
+ 					compacted during the last cycle"
+ 					compactor freePastSegmentsAndSetSegmentToFill.
+ 					
+ 					^ self]].
+ 		
+ 	phase = InSweepingPhase
+ 		ifTrue: [
+ 			compactor incrementalSweep
+ 				ifTrue: [
+ 					self allocatorShouldAllocateBlack: false.
+ 					manager allOldSpaceObjectsDo: [:ea | self assert: (manager isWhite: ea) ].
+ 					"self assert: manager allObjectsUnmarked."
+ 					phase := InCompactingPhase.
+ 					^ self]].
+ 		
+ 	phase = InCompactingPhase
+ 		ifTrue: [
+ 			compactor incrementalCompact
+ 				ifTrue: [phase := InMarkingPhase.
+ 					^ self]]!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	super initialize.
+ 	phase := InMarkingPhase!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollector>>maybeModifyGCFlagsOf: (in category 'as yet unclassified') -----
+ maybeModifyGCFlagsOf: objOop
+ 
+ 	<inline: true>
+ 	((manager isOldObject: objOop) and: [allocatorShouldAllocateBlack and: [objOop < compactor currentSweepingEntity]])
+ 		ifTrue: [manager setIsMarkedOf: objOop to: true]!

Item was added:
+ SpurIncrementalGarbageCollector subclass: #SpurIncrementalGarbageCollectorSimulator
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollectorSimulation'!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollectorSimulator>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 
+ 	super initialize.
+ 	GCEventLog reset!

Item was added:
+ ----- Method: SpurIncrementalGarbageCollectorSimulator>>manager: (in category 'as yet unclassified') -----
+ manager: manager
+ 
+ 	super manager: manager.
+ 	GCEventLog instance manager: manager!

Item was added:
+ SpurMarker subclass: #SpurIncrementalMarker
+ 	instanceVariableNames: 'isCurrentlyMarking'
+ 	classVariableNames: 'SlotLimitPerPass'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurIncrementalMarker class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 
+ 	"experimental value. needs some measurements"
+ 	SlotLimitPerPass := 1024 * 1024!

Item was added:
+ ----- Method: SpurIncrementalMarker class>>simulatorClass (in category 'as yet unclassified') -----
+ simulatorClass
+ 
+ 	^ SpurIncrementalMarkerSimulation!

Item was added:
+ ----- Method: SpurIncrementalMarker>>blackenObject: (in category 'as yet unclassified') -----
+ blackenObject: obj
+ 
+ 	self flag: #Todo. "do we need to ungrey the object or can we save the call? Idea:
+ 		-> if grey set -> grey
+ 		-> if mark set -> ignore grey, interpret it as black"
+ 	manager setIsGreyOf: obj to: false.
+ 	manager setIsMarkedOf: obj to: true!

Item was added:
+ ----- Method: SpurIncrementalMarker>>completeMark (in category 'marking - global') -----
+ completeMark
+ 	"finishes the current mark pass"
+ 
+ 	| currentObj slotsLeft |
+ 	"manager objStack: manager markStack do: [:index :page | Transcript showln: (manager fetchPointer: index ofObject: page)].
+ 	manager sizeOfObjStack: manager markStack"
+ 	currentObj := manager popObjStack: manager markStack.
+ 	currentObj
+ 		ifNil: [^ true]. "there is nothing more on the stack and we are done"
+ 		
+ 	slotsLeft := SlotLimitPerPass.
+ 	
+ 	[
+ 		| slotNumber slotsToVisit startIndex |
+ 		
+ 		"after passing the limit we push the current index on the stack. Is the currentObj only an index? "
+ 		(manager isImmediate: currentObj)
+ 			ifTrue: [startIndex := currentObj.
+ 				currentObj := manager popObjStack: manager markStack.]
+ 			ifFalse: [startIndex := 0].
+ 			
+ 		slotNumber := manager numStrongSlotsOfInephemeral: currentObj.
+ 		slotsToVisit := slotNumber - startIndex.
+ 		
+ 		"we can mark all"
+ 		slotsLeft := slotsLeft - slotsToVisit.
+ 		
+ 		self markFrom: startIndex nSlots: slotsToVisit of: currentObj.		
+ 
+ 		"we finished everything there is to be done with to obj -> make it black"
+ 		self blackenObject: currentObj.
+ 		currentObj := manager popObjStack: manager markStack.
+ 	"repeat while there still are objects"
+ 	currentObj notNil] whileTrue.
+ 
+ 	^ true!

Item was added:
+ ----- Method: SpurIncrementalMarker>>completeMarkObjects (in category 'marking - global') -----
+ completeMarkObjects
+ 	"this method is meant to be run for a complete GC that is used for snapshots. It discards previous marking information, because
+ 	this will probably include some objects that should be collected
+ 	It makes me a bit sad but I cannot see how this could be avoided"
+ 
+ 	<inline: #never> "for profiling"
+ 	
+ 	manager runLeakCheckerFor: GCModeFull.
+ 	
+ 	"reset and reinitialize all helper structures and do actions to be done at the start of marking"
+ 	self resetMarkProgress.
+ 	self initializeForNewMarkingPassIfNecessary.
+ 	
+ 	self pushAllRootsOnMarkStack.
+ 	self completeMark.
+ 	
+ 	self finishMarking
+ 
+ 	!

Item was added:
+ ----- Method: SpurIncrementalMarker>>finishMarking (in category 'as yet unclassified') -----
+ finishMarking
+ 	"marks the structures needed during GC"
+ 	<inline: #never>
+ 	
+ 	1 to: manager numClassTablePages - 1 do:
+ 		[:i| manager setIsMarkedOf: (manager fetchPointer: i ofObject: manager hiddenRootsObj)
+ 				to: true].
+ 			
+ 	self flag: #Todo. "handle ephemerons"
+ 	
+ 	"lets assume there are not too many for now"
+ 	self markWeaklingsAndMarkAndFireEphemerons.
+ 	manager expungeDuplicateAndUnmarkedClasses: true.
+ 	manager nilUnmarkedWeaklingSlots.
+ 			
+ 	isCurrentlyMarking := false.
+ 	marking := false!

Item was added:
+ ----- Method: SpurIncrementalMarker>>incrementalMark (in category 'marking - incremental') -----
+ incrementalMark
+ 	"does one marking cycle. Breaks after a certain amount of slots is marked and the last object, that amount is crossed in, is completely scanned"
+ 
+ 	| currentObj slotsLeft |
+ 	"manager objStack: manager markStack do: [:index :page | Transcript showln: (manager fetchPointer: index ofObject: page)].
+ 	manager sizeOfObjStack: manager markStack"
+ 	currentObj := manager popObjStack: manager markStack.
+ 	"skip young objects. They get already scanned as they are part of the roots"
+ 	[(currentObj notNil) and: [(manager isNonImmediate: currentObj) and: [manager isYoung: currentObj]]]
+ 			whileTrue: [currentObj := manager popObjStack: manager markStack.].
+ 	
+ 	currentObj
+ 		ifNil: [^ true]. "there is nothing more on the stack and we are done"
+ 		
+ 	slotsLeft := SlotLimitPerPass.
+ 	
+ 	[
+ 		| slotNumber slotsToVisit startIndex |
+ 		
+ 		"after passing the limit we push the current index on the stack. Is the currentObj only an index? "
+ 		(manager isImmediate: currentObj)
+ 			ifTrue: [startIndex := manager integerValueOf: currentObj.
+ 				currentObj := manager popObjStack: manager markStack.]
+ 			ifFalse: [startIndex := 0.
+ 				
+ 				 self markAndTraceClassOf: currentObj.
+ 				
+ 				"eager color the object black. Either it will get scanned completely and the color is correct
+ 				or we have at least scanned some of the slots. In the second case the mutator could 
+ 				modify one of the slots of the object that already were scanned and we would could lose
+ 				this object. Therefore color the object early to trigger the write barrier on writes. There will
+ 				be some overhead (trigger the barrier always although only the already scanned slots are
+ 				technically black) but it seems we need to do this for correctness"
+ 				self blackenObject: currentObj].
+ 			
+ 		slotNumber := manager numStrongSlotsOfInephemeral: currentObj.
+ 		slotsToVisit := slotNumber - startIndex.
+ 		
+ 		slotsLeft - slotsToVisit < 0
+ 			ifTrue: [
+ 				self 
+ 					markFrom: startIndex
+ 					nSlots: slotsLeft
+ 					of: currentObj.
+ 						
+ 				"If we need to abort earlier we push the index and the currently scanned object on the marking stack. Otherwise it is not possible
+ 				for immediates to be on the stack (they have no fields to be scanned) -> we can use the immediated to detect this pattern"
+ 				(manager topOfObjStack: manager markStack) ~= currentObj ifTrue: 
+ 						[manager push: currentObj onObjStack: manager markStack].
+ 				manager push: (manager integerObjectOf: slotsLeft + 1) onObjStack: manager markStack.
+ 				
+ 				"we need to abort early to not run into some extreme corner cases (giant objects) that would explode our mark time assumptions"
+ 				^ false]
+ 			ifFalse: ["we can mark all"
+ 				slotsLeft := slotsLeft - slotsToVisit.
+ 				
+ 				self markFrom: startIndex nSlots: slotsToVisit of: currentObj].		
+ 
+ 		currentObj := manager popObjStack: manager markStack.
+ 		
+ 		[(currentObj notNil) and: [(manager isNonImmediate: currentObj) and: [manager isYoung: currentObj]]]
+ 			whileTrue: [currentObj := manager popObjStack: manager markStack.].
+ 	"repeat while there still are objects"
+ 	currentObj notNil] whileTrue.
+ 
+ 	^ true!

Item was added:
+ ----- Method: SpurIncrementalMarker>>incrementalMarkAndTrace: (in category 'marking - incremental') -----
+ incrementalMarkAndTrace: objOop
+ 
+ 	<api>
+ 	<inline: #never>
+ 	"if markAndTrace: is to follow and eliminate forwarding pointers
+ 	 in its scan it cannot be handed an r-value which is forwarded.
+ 	 The assert for this is in markAndShouldScan:"
+ 	(self markAndShouldScan: objOop) ifFalse:
+ 		[^self].
+ 
+ 	"Now scan the object, and any remaining objects on the mark stack."
+ 	self incrementalMarkFrom: objOop!

Item was added:
+ ----- Method: SpurIncrementalMarker>>incrementalMarkFrom: (in category 'marking - incremental') -----
+ incrementalMarkFrom: objOop
+ 	"does one marking cycle. Breaks after a certain amount of slots is marked and the last object, that amount is crossed in, is completely scanned"
+ 
+ 	| currentObj slotsLeft |
+ 	"manager objStack: manager markStack do: [:index :page | Transcript showln: (manager fetchPointer: index ofObject: page)].
+ 	manager sizeOfObjStack: manager markStack"
+ 	currentObj := objOop.
+ 	currentObj
+ 		ifNil: [^ true]. "there is nothing more on the stack and we are done"
+ 		
+ 	slotsLeft := SlotLimitPerPass.
+ 	
+ 	[
+ 		| slotNumber slotsToVisit startIndex |
+ 		
+ 		"after passing the limit we push the current index on the stack. Is the currentObj only an index? "
+ 		(manager isImmediate: currentObj)
+ 			ifTrue: [startIndex := manager integerValueOf: currentObj.
+ 				currentObj := manager popObjStack: manager markStack.]
+ 			ifFalse: [startIndex := 0].
+ 			
+ 		slotNumber := manager numStrongSlotsOfInephemeral: currentObj.
+ 		slotsToVisit := slotNumber - startIndex.
+ 		
+ 		slotsLeft - slotsToVisit < 0
+ 			ifTrue: [
+ 				self 
+ 					markFrom: startIndex
+ 					nSlots: slotsLeft
+ 					of: currentObj.
+ 						
+ 				"If we need to abort earlier we push the index and the currently scanned object on the marking stack. Otherwise it is not possible
+ 				for immediates to be on the stack (they have no fields to be scanned) -> we can use the immediated to detect this pattern"
+ 				(manager topOfObjStack: manager markStack) ~= currentObj ifTrue: 
+ 						[manager push: currentObj onObjStack: manager markStack].
+ 				manager push: (manager integerObjectOf: slotsLeft + 1) onObjStack: manager markStack.
+ 				
+ 				"we need to abort early to not run into some extreme corner cases (giant objects) that would explode our mark time assumptions"
+ 				^ false]
+ 			ifFalse: ["we can mark all"
+ 				slotsLeft := slotsLeft - slotsToVisit.
+ 				
+ 				self markFrom: startIndex nSlots: slotsToVisit of: currentObj].		
+ 
+ 		"we finished everything there is to be done with to obj -> make it black"
+ 		self blackenObject: currentObj.
+ 		currentObj := manager popObjStack: manager markStack.
+ 	"repeat while there still are objects"
+ 	currentObj notNil] whileTrue.
+ 
+ 	^ true!

Item was added:
+ ----- Method: SpurIncrementalMarker>>incrementalMarkObjects (in category 'marking - incremental') -----
+ incrementalMarkObjects
+ 	"this method is to be run directly after a scavenge -> we can assume there are ony objects in the now past survivor space"
+ 
+ 	<inline: #never> "for profiling"
+ 	
+ 	"manager runLeakCheckerFor: GCModeIncremental."
+ 	
+ 	self initializeForNewMarkingPassIfNecessary.
+ 
+ 	[(manager isEmptyObjStack: manager markStack)
+ 		ifTrue: [self pushAllRootsOnMarkStack.
+ 			" manager sizeOfObjStack: manager markStack.
+ 			did we finish marking?"
+ 			(manager isEmptyObjStack: manager markStack)
+ 				ifTrue: [self finishMarking.
+ 					^ true]].
+ 	
+ 	
+ 	self incrementalMark] whileTrue.
+ 
+ 	^ false
+ 	!

Item was added:
+ ----- Method: SpurIncrementalMarker>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	super initialize.
+ 	isCurrentlyMarking := false.
+ 	marking := false!

Item was added:
+ ----- Method: SpurIncrementalMarker>>initializeForNewMarkingPassIfNecessary (in category 'marking-initialization') -----
+ initializeForNewMarkingPassIfNecessary
+ 
+ 	isCurrentlyMarking 
+ 		ifFalse: [
+ 			manager initializeMarkStack.
+ 			manager initializeWeaklingStack.
+ 			manager initializeEphemeronStack.
+ 			
+ 			"This must come first to enable stack page reclamation.  It clears
+ 			  the trace flags on stack pages and so must precede any marking.
+ 			  Otherwise it will clear the trace flags of reached pages."
+ 			coInterpreter initStackPageGC.
+ 			
+ 			self markHelperStructures].
+ 		
+ 	isCurrentlyMarking := true.
+ 	marking := true!

Item was added:
+ ----- Method: SpurIncrementalMarker>>isCurrentlyMarking (in category 'accessing') -----
+ isCurrentlyMarking
+ 
+ 	^ isCurrentlyMarking!

Item was added:
+ ----- Method: SpurIncrementalMarker>>isCurrentlyMarking: (in category 'accessing') -----
+ isCurrentlyMarking: anObject
+ 
+ 	isCurrentlyMarking := anObject.!

Item was added:
+ ----- Method: SpurIncrementalMarker>>isLeafInObjectGraph: (in category 'barrier') -----
+ isLeafInObjectGraph: anObject
+ 	
+ 	^ (manager isImmediate: anObject) or: [manager isPureBitsNonImm: anObject]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markAllUnscannedEphemerons (in category 'weaklings and ephemerons') -----
+ markAllUnscannedEphemerons
+ 	"After firing the unscanned ephemerons we must scan-mark them.
+ 	 The wrinkle is that doing so may add more ephemerons to the set.
+ 	 So we remove the first element, by overwriting it with the last element,
+ 	 and decrementing the top, and then markAndTrace its contents."
+ 	self assert: (manager isEmptyObjStack: manager ephemeronStack) not.
+ 	self assert: manager allUnscannedEphemeronsOnObjStackAreActive.
+ 	
+ 	[(manager isEmptyObjStack: manager ephemeronStack) not] whileTrue:
+ 		[| pointer ephemeron key |
+ 		 pointer := manager popObjStack: manager ephemeronStack.
+ 		 ephemeron := manager longAt: pointer.
+ 
+ 		 key := manager followedKeyOfMaybeFiredEphemeron: ephemeron.
+ 		 manager setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
+ 		 self
+ 			incrementalMarkAndTrace: key;
+ 			incrementalMarkAndTrace: ephemeron]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markAndShouldScan: (in category 'marking - incremental') -----
+ markAndShouldScan: objOop
+ 	"marks the object (grey or black as neccessary) and returns if the object should be scanned
+ 	Objects that get handled later on get marked as black, as they are practically a leaf in the object tree (we scan them later on, so we cannot lose objects and do not
+ 	need to adhere to the tricolor invariant)"
+ 
+ 	| format |
+ 	<inline: true>
+ 	(manager isYoung: objOop)
+ 		ifTrue: [^ false].
+ 	
+ 	(manager isImmediate: objOop) ifTrue:
+ 		[^false].
+ 	
+ 	self assert: (manager isForwarded: objOop) not.
+ 
+ 	"if it is marked we already did everything we needed to do and if is grey we already saw it and do not have to do anything here"
+ 	(manager isWhite: objOop) not ifTrue:
+ 		[^false].
+ 	
+ 	format := manager formatOf: objOop.
+ 	
+ 	(manager isPureBitsFormat: format) ifTrue: "avoid pushing non-pointer objects on the markStack."
+ 		["Avoid tracing classes of non-objects on the heap, e.g. IRC caches, Sista counters."
+ 		 (manager classIndexOf: objOop) > manager lastClassIndexPun ifTrue:
+ 			[self markAndTraceClassOf: objOop].
+ 		
+ 		"the object does not need to enter the marking stack as there are no pointer to visit -> it is already finished and we can make it black"
+ 		self blackenObject: objOop.
+ 		 ^false].
+ 	
+ 	(manager isWeakFormat: format) ifTrue: "push weaklings on the weakling stack to scan later"
+ 		[manager push: objOop onObjStack: manager weaklingStack.
+ 		"do not follow weak references. They get scanned at the end of marking -> it should be ok to not follow the tricolor invariant"
+ 		self blackenObject: objOop.
+ 		 ^false].
+ 	
+ 	((manager isEphemeronFormat: format)
+ 	 and: [manager activeAndDeferredScan: objOop]) ifTrue:
+ 		[self blackenObject: objOop.
+ 		^false].
+ 	
+ 	"we know it is an object that can contain we have to follow"
+ 	self pushOnMarkingStackAndMakeGrey: objOop.
+ 	
+ 	^ true!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markAndTrace: (in category 'marking - incremental') -----
+ markAndTrace: objOop
+ 
+ 	self halt.!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markAndTraceClassOf: (in category 'marking - incremental') -----
+ markAndTraceClassOf: objOop
+ 	"Ensure the class of the argument is marked, pushing it on the markStack if not already marked.
+ 	 And for one-way become, which can create duplicate entries in the class table, make sure
+ 	 objOop's classIndex refers to the classObj's actual classIndex.
+ 	 Note that this is recursive, but the metaclass chain should terminate quickly."
+ 	<inline: false>
+ 	| classIndex classObj realClassIndex |
+ 	classIndex := manager classIndexOf: objOop.
+ 	classObj := manager classOrNilAtIndex: classIndex.
+ 	self assert: (coInterpreter objCouldBeClassObj: classObj).
+ 	realClassIndex := manager rawHashBitsOf: classObj.
+ 	(classIndex ~= realClassIndex
+ 	 and: [classIndex > manager lastClassIndexPun]) ifTrue:
+ 		[manager setClassIndexOf: objOop to: realClassIndex].
+ 	(manager isWhite: classObj) ifTrue:
+ 		[self pushOnMarkingStackAndMakeGrey: classObj.
+ 		 self markAndTraceClassOf: classObj]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markAndTraceObjStack:andContents: (in category 'marking-initialization') -----
+ 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."
+ 	<inline: false>
+ 	| index field |
+ 	stackOrNil = manager nilObj ifTrue:
+ 		[^self].
+ 	manager setIsMarkedOf: stackOrNil to: true.
+ 	self assert: (manager numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
+ 	field := manager fetchPointer: ObjStackNextx ofObject: stackOrNil.
+ 	field ~= 0 ifTrue:
+ 		[self markAndTraceObjStack: field andContents: markAndTraceContents].
+ 	field := stackOrNil.
+ 	[field := manager fetchPointer: ObjStackFreex ofObject: field.
+ 	 field ~= 0] whileTrue:
+ 		[manager setIsMarkedOf: field to: true].
+ 	markAndTraceContents ifFalse:
+ 		[^self].
+ 	"There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
+ 	  if there were 6 slots in an oop stack, full would be 2, and the last 0-rel index is 5."
+ 	index := (manager fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
+ 	[index >= ObjStackFixedSlots] whileTrue:
+ 		[field := manager followObjField: index ofObject: stackOrNil.
+ 		 (manager isImmediate: field) ifFalse:
+ 			[self pushOnMarkingStackAndMakeGrey: field].
+ 		 index := index - 1]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markAndTraceWeaklingsFrom: (in category 'weaklings and ephemerons') -----
+ 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."
+ 	^manager objStack: manager weaklingStack from: startIndex do:
+ 		[:weakling|
+ 		 self deny: (manager isForwarded: weakling).
+ 		self flag: #Todo. "this will probably just push a part on the marking stack. This will get resolved with the next mark loop"
+ 		 self markAndTraceClassOf: weakling.
+ 		
+ 		"N.B. generateToByDoLimitExpression:negative:on: guards against (unsigned)0 - 1 going +ve"
+ 		 0 to: (manager numStrongSlotsOfWeakling: weakling) - 1 do:
+ 			[:i| | field |
+ 			field := manager followOopField: i ofObject: weakling.
+ 			((manager isImmediate: field) or: [manager isMarked: field]) ifFalse:
+ 				[self incrementalMarkAndTrace: field]]]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markFrom:nSlots:of: (in category 'as yet unclassified') -----
+ markFrom: startIndex nSlots: anAmount of: objOop
+ 
+ 	startIndex to: startIndex + anAmount - 1
+ 		do: [:index | | slot |
+ 			slot := manager fetchPointer: index ofObject: objOop.
+ 			
+ 			(manager isNonImmediate: slot)
+ 				ifTrue: [
+ 					(manager isForwarded: slot)
+ 						ifTrue: [slot := manager fixFollowedField: slot ofObject: objOop withInitialValue: slot].
+ 					self markAndShouldScan: slot]]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markHelperStructures (in category 'marking-initialization') -----
+ markHelperStructures
+ 	"marks the structures needed during GC"
+ 	
+ 	manager setIsMarkedOf: manager rememberedSetObj to: true.
+ 	manager setIsMarkedOf: manager freeListsObj to: true.
+ 	
+ 	(manager isWeakNonImm: manager classTableFirstPage) ifTrue:
+ 		[self pushOnMarkingStackAndMakeGrey: manager hiddenRootsObj].
+ 	
+ 	manager setIsMarkedOf: manager hiddenRootsObj to: true!

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

Item was added:
+ ----- Method: SpurIncrementalMarker>>markNSlots:of: (in category 'as yet unclassified') -----
+ markNSlots: aNumber of: objOop
+ 
+ 	self markFrom: 0 nSlots: aNumber of: objOop!

Item was added:
+ ----- Method: SpurIncrementalMarker>>markWeaklingsAndMarkAndFireEphemerons (in category 'weaklings and ephemerons') -----
+ 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 strong slots traced before firing ephemerons..."
+ 	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
+ 	  (manager sizeOfObjStack: manager weaklingStack) > numTracedWeaklings] whileTrue.
+ 	 manager noUnscannedEphemerons ifTrue:
+ 		[coInterpreter
+ 			markAndTraceUntracedReachableStackPages;
+ 	 		markAndTraceMachineCodeOfMarkedMethods;
+ 			freeUntracedStackPages;
+ 			freeUnmarkedMachineCode.
+ 		 ^self].
+ 	 self markInactiveEphemerons ifFalse:
+ 		[manager fireAllUnscannedEphemerons].
+ 	 self markAllUnscannedEphemerons]
+ 		repeat!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushAllRootsOnMarkStack (in category 'root-scanning') -----
+ pushAllRootsOnMarkStack
+ 	"Roots are:
+ 		1. references from the stack
+ 		2. references from the hidden roots
+ 		3. references from extra roots?
+ 		4. references from young space (it was recently scavenged -> only alive objects)"
+ 		
+ 		
+ 	self pushStackReferencesOnMarkingStack.
+ 	self pushHiddenRootsReferencesOnMarkingStack.
+ 	self pushExtraRootsReferencesOnMarkingStack.
+ 	self pushNewSpaceReferencesOnMarkingStack.!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushExtraRootsReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushExtraRootsReferencesOnMarkingStack
+ 
+ 	self assert: manager remapBufferCount = 0.
+ 
+ 	1 to: manager extraRootCount do:
+ 		[:i| | oop |
+ 		oop := (manager extraRoots at: i) at: 0.
+ 		((manager isImmediate: oop) or: [manager isFreeObject: oop]) ifFalse:
+ 			[
+ 			self flag: #Todo. "lets see how it goes "
+ 			self markAndShouldScan: oop]]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushHiddenRootsReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushHiddenRootsReferencesOnMarkingStack
+ 
+ 	| classTablePageSize |
+ 	self markAndTraceObjStack: manager markStack andContents: false.
+ 	self markAndTraceObjStack: manager weaklingStack andContents: false.
+ 	self markAndTraceObjStack: manager mournQueue andContents: true.
+ 	
+ 	classTablePageSize := manager numStrongSlotsOfInephemeral: manager classTableFirstPage.
+ 	self markNSlots: classTablePageSize of: manager classTableFirstPage.
+ 	self blackenObject: manager classTableFirstPage!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushNewSpaceReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushNewSpaceReferencesOnMarkingStack
+ 
+ 	manager allNewSpaceObjectsDo: [:objOop | | format |
+ 		self flag: #Todo. "ephermorons"
+ 		format := manager formatOf: objOop.
+ 		((manager isNonImmediate: objOop) and: [(manager isPureBitsFormat: format) not and: [(manager isWeakFormat: format) not]])
+ 			ifTrue: [ | slotNumber |
+ 				slotNumber := manager numStrongSlotsOfInephemeral: objOop.
+ 				
+ 				0 to: slotNumber - 1
+ 					do: [ :slotIndex | | slot |
+ 						slot := manager fetchPointer: slotIndex ofObject: objOop.
+ 							
+ 						(self shoudlBeOnMarkingStack: objOop)
+ 							ifTrue: [self markAndShouldScan: objOop]]]]
+ 				!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushOnMarkingStack: (in category 'marking-stack') -----
+ pushOnMarkingStack: objOop
+ 
+ 	manager push: objOop onObjStack: manager markStack!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushOnMarkingStackAndMakeGrey: (in category 'marking-stack') -----
+ pushOnMarkingStackAndMakeGrey: objOop
+ 
+ 	manager push: objOop onObjStack: manager markStack.
+ 	manager setIsGreyOf: objOop to: true !

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushOnMarkingStackAndMakeGreyIfNecessary: (in category 'marking-stack') -----
+ pushOnMarkingStackAndMakeGreyIfNecessary: objOop
+ 
+ 	(manager isWhite: objOop)
+ 		ifTrue: [self pushOnMarkingStackAndMakeGrey: objOop]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>pushStackReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushStackReferencesOnMarkingStack
+ 
+ 	coInterpreter incrementalMarkAndTraceInterpreterOops!

Item was added:
+ ----- Method: SpurIncrementalMarker>>resetMarkProgress (in category 'marking - global') -----
+ resetMarkProgress
+ 	
+ 	manager shutDownGlobalIncrementalGC: true.
+ 	
+ 	isCurrentlyMarking := false.
+ 	marking := false.
+ 	
+ 	manager emptyObjStack: manager markStack.
+ 	manager emptyObjStack: manager weaklingStack.
+ 	manager emptyObjStack: manager ephemeronStack!

Item was added:
+ ----- Method: SpurIncrementalMarker>>resolveAllForwarders (in category 'marking - global') -----
+ resolveAllForwarders
+ 
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: SpurIncrementalMarker>>shoudlBeOnMarkingStack: (in category 'marking-stack') -----
+ shoudlBeOnMarkingStack: objOop
+ 
+ 	<inline: true>
+ 	self flag: #Todo. "should be not immediate and no bit array"
+ 	^ (manager isOldObject: objOop) and: [manager isWhite: objOop]!

Item was added:
+ ----- Method: SpurIncrementalMarker>>writeBarrierFor:at:with: (in category 'barrier') -----
+ writeBarrierFor: anObject at: index with: value
+ 	"a dijkstra style write barrier with the addition of the generation check
+ 	objects that are not able to contain pointers are ignored too, as the write barries
+ 	should ensure we lose no references and this objects do not hold any of them"
+ 	<inline: true>
+ 	
+ 	self flag: #Todo. "we probably want the oldObject check to be the first one as it is only a pointer comparison and no dereferencing is needed"
+ 	((self isLeafInObjectGraph: anObject) not and: [(manager isOldObject: anObject) and: [manager isMarked: anObject]])
+ 		ifTrue: [self pushOnMarkingStackAndMakeGreyIfNecessary: value]!

Item was added:
+ SpurIncrementalMarker subclass: #SpurIncrementalMarkerSimulation
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollectorSimulation'!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>blackenObject: (in category 'as yet unclassified') -----
+ blackenObject: obj
+ 
+ 	^ GCEventLog 
+ 		register: (GCBlackenEvent address: obj)
+ 		expecting: {[:evt | (evt isKindOf: GCUngreyEvent) and: [evt address = obj]].
+ 			[:evt | (evt isKindOf: GCMarkEvent) and: [evt address = obj]]} 
+ 		doing: [super blackenObject: obj]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>finishMarking (in category 'as yet unclassified') -----
+ finishMarking
+ 
+ 	^ GCEventLog
+ 		inContext: #finishMarking 
+ 		do: [super finishMarking]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>incrementalMark (in category 'marking - incremental') -----
+ incrementalMark
+ 
+ 	^ GCEventLog 
+ 	 	inContext: #IncrementalMark 
+ 		do: [super incrementalMark]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>incrementalMarkObjects (in category 'marking - incremental') -----
+ incrementalMarkObjects
+ 
+ 	^ GCEventLog
+ 		inContext: #marking 
+ 		do: [super incrementalMarkObjects]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>initializeForNewMarkingPassIfNecessary (in category 'marking-initialization') -----
+ initializeForNewMarkingPassIfNecessary
+ 
+ 	^ GCEventLog
+ 		inContext: #markingInit 
+ 		do: [super initializeForNewMarkingPassIfNecessary]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>pushAllRootsOnMarkStack (in category 'root-scanning') -----
+ pushAllRootsOnMarkStack
+ 
+ 	GCEventLog 
+ 		inContext: #rootScanning 
+ 		do: [super pushAllRootsOnMarkStack] !

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>pushExtraRootsReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushExtraRootsReferencesOnMarkingStack
+ 
+ 	GCEventLog 
+ 		inContext: #extraRootScanning 
+ 		do: [super pushExtraRootsReferencesOnMarkingStack] !

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>pushHiddenRootsReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushHiddenRootsReferencesOnMarkingStack
+ 
+ 	GCEventLog 
+ 		inContext: #hiddenRootScanning 
+ 		do: [super pushHiddenRootsReferencesOnMarkingStack] !

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>pushNewSpaceReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushNewSpaceReferencesOnMarkingStack
+ 
+ 	GCEventLog 
+ 		inContext: #newSpaceScanning 
+ 		do: [super pushNewSpaceReferencesOnMarkingStack]!

Item was added:
+ ----- Method: SpurIncrementalMarkerSimulation>>pushStackReferencesOnMarkingStack (in category 'root-scanning') -----
+ pushStackReferencesOnMarkingStack
+ 
+ 	GCEventLog 
+ 		inContext: #stackScanning 
+ 		do: [super pushStackReferencesOnMarkingStack]!

Item was added:
+ SpurCompactor subclass: #SpurIncrementalSweepAndCompact
+ 	instanceVariableNames: 'sweeper compactor'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact class>>simulatorClass (in category 'as yet unclassified') -----
+ simulatorClass
+ 
+ 	^ SpurIncrementalSweepAndCompactSimulator!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>biasForGC (in category 'api') -----
+ biasForGC!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>compact (in category 'api - global') -----
+ compact
+ 
+ 	<doNotGenerate>
+ 	compactor compact!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>compactor (in category 'as yet unclassified') -----
+ compactor
+ 
+ 	<doNotGenerate>
+ 	^ compactor!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>currentSweepingEntity (in category 'as yet unclassified') -----
+ currentSweepingEntity
+ 
+ 	<doNotGenerate>
+ 	^ sweeper currentSweepingEntity!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>freePastSegmentsAndSetSegmentToFill (in category 'api - incremental') -----
+ freePastSegmentsAndSetSegmentToFill
+ 	
+ 	<doNotGenerate>
+ 	compactor freePastSegmentsAndSetSegmentToFill!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>incrementalCompact (in category 'api - incremental') -----
+ incrementalCompact
+  	
+ 	<doNotGenerate>
+ 	^ compactor incrementalCompact!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>incrementalSweep (in category 'api - incremental') -----
+ incrementalSweep
+ 	
+ 	<doNotGenerate>
+ 	^ sweeper incrementalSweep!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	sweeper := SpurIncrementalSweeper simulatorClass new.
+ 	compactor := SpurIncrementalCompactor simulatorClass new!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>manager: (in category 'as yet unclassified') -----
+ manager: manager
+ 
+ 	<doNotGenerate>
+ 	super manager: manager.
+ 	sweeper manager: manager.
+ 	compactor manager: manager!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>remapObj: (in category 'api') -----
+ remapObj: objOop
+ 	"Scavenge or simply follow objOop.  Answer the new location of objOop.
+ 	 The send should have been guarded by a send of shouldRemapOop:.
+ 	 The method is called remapObj: for compatibility with ObjectMemory."
+ 	<api>
+ 	<inline: false>
+ 	^manager slidingCompactionRemapObj: objOop!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>shouldRemapObj: (in category 'api') -----
+ shouldRemapObj: objOop
+ 	"Answer if the obj should be scavenged, or simply followed. Sent via the compactor
+ 	 from shouldRemapObj:.  We test for being already scavenged because mapStackPages
+ 	 via mapInterpreterOops may be applied twice in the context of a global GC where a
+ 	 scavenge, followed by a scan-mark-free, and final compaction passes may result in
+ 	 scavenged fields being visited twice."
+ 	<api>
+ 	<inline: false>
+ 	^manager slidingCompactionShouldRemapObj: objOop!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompact>>sweeper (in category 'as yet unclassified') -----
+ sweeper
+ 
+ 	^ sweeper!

Item was added:
+ SpurIncrementalSweepAndCompact subclass: #SpurIncrementalSweepAndCompactSimulator
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollectorSimulation'!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompactSimulator>>incrementalCompact (in category 'api - incremental') -----
+ incrementalCompact
+ 
+ 	^ GCEventLog 
+ 		inContext: #compact 
+ 		do: [super incrementalCompact]
+ 	!

Item was added:
+ ----- Method: SpurIncrementalSweepAndCompactSimulator>>incrementalSweep (in category 'api - incremental') -----
+ incrementalSweep
+ 
+ 	^ GCEventLog
+ 		inContext: #sweep
+ 		do: [super incrementalSweep]
+ 	!

Item was added:
+ SpurCompactor subclass: #SpurIncrementalSweeper
+ 	instanceVariableNames: 'currentSweepingEntity isCurrentlySweeping currentSegmentUsed currentSegmentUnused currentSegmentsIndex currentsCycleSeenObjectCount'
+ 	classVariableNames: 'MaxObjectsToFree'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurIncrementalSweeper class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 
+ 	MaxObjectsToFree := 100000!

Item was added:
+ ----- Method: SpurIncrementalSweeper class>>simulatorClass (in category 'as yet unclassified') -----
+ simulatorClass
+ 
+ 	^ SpurIncrementalSweeperSimulator!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>biasForGC (in category 'api') -----
+ biasForGC!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>biasForSnapshot (in category 'api') -----
+ biasForSnapshot!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>bulkFreeChunkFrom: (in category 'api - global') -----
+ bulkFreeChunkFrom: objOop
+ 	"The old space entity before objOop is necessarily a marked object. Attempts to free as many bytes 
+ 	from objOop start as possible, looking ahead to free contiguous freechunks / unmarked objects"
+ 	| bytes start next currentObj |
+ 	self assert: (self canUseAsFreeSpace: true).
+ 	start := manager startOfObject: objOop.
+ 	currentObj := objOop.
+ 	bytes := 0.
+ 	[bytes := bytes + (manager bytesInBody: currentObj).
+ 	(manager isRemembered: currentObj)
+ 		ifTrue: 
+ 			[self assert: (manager isFreeObject: currentObj) not.
+ 			 scavenger forgetObject: currentObj].
+ 
+ 	next := manager objectStartingAt: start + bytes.
+ 	self assert: ((manager oop: next isLessThan: manager endOfMemory)
+ 		or: [next = manager endOfMemory and: [(self canUseAsFreeSpace: next) not]]).
+ 
+ 	self canUseAsFreeSpace: next] 
+ 		whileTrue: [currentObj := next].
+ 	
+ 	^ manager addFreeChunkWithBytes: bytes at: start!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>canUseAsFreeSpace: (in category 'testing') -----
+ canUseAsFreeSpace: objOop
+ 	<inline: true>
+ 	^ (manager isFreeObject: objOop) or: [(manager isMarked: objOop) not]!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>cautiousBulkFreeChunkFrom: (in category 'api - incremental') -----
+ cautiousBulkFreeChunkFrom: objOop
+ 	"The old space entity before objOop is necessarily a marked object. Attempts to free as many bytes 
+ 	from objOop start as possible, looking ahead to free contiguous freechunks / unmarked objects"
+ 	| bytes start next currentObj currentSegmentsBridge |
+ 	self assert: (self canUseAsFreeSpace: objOop).
+ 	
+ 	start := manager startOfObject: objOop.
+ 	currentObj := objOop.
+ 	bytes := 0.
+ 	
+ 	currentSegmentsBridge := manager segmentManager bridgeAt: currentSegmentsIndex.
+ 	
+ 	[bytes := bytes + (manager bytesInBody: currentObj).
+ 	(manager isRemembered: currentObj)
+ 		ifTrue: 
+ 			[self assert: (manager isFreeObject: currentObj) not.
+ 			 scavenger forgetObject: currentObj].
+ 
+ 	(manager isFreeObject: currentObj)
+ 		ifTrue: [ "we need to unlink chunks for concurrent sweeping. In the stop the world sweeper we can just reset the freeLists but here we need to keep them
+ 			around so the mutator can still work between sweeping passes"
+ 			
+ 			self flag: #Todo. "we want to optimize for lilliputian chunks!! For now it is ok(ish) but we have to do something about it. 
+ 								At the moment I see 3 possibilities:
+ 									- have the lilliputian list always sorted (O(n) insert in the worst case!!)
+ 									- sort the lilliputian part before sweeping (O(n log n) at the start. but everytime before sweeping)
+ 									- be cheeky and discard the  lilliputian list (problem: the mutator has no access to the list + it can insert unsorted chunks (for the duration of sweeping we could let it use a second list and just append it after sweeping)"
+ 			manager unlinkFreeChunk: currentObj chunkBytes: (manager bytesInBody: currentObj).
+ 			manager totalFreeOldSpace: manager totalFreeOldSpace - (manager bytesInBody: currentObj).
+ 			currentSegmentUnused := currentSegmentUnused + (manager bytesInBody: currentSweepingEntity)].
+ 
+ 	next := manager objectStartingAt: start + bytes.
+ 	currentsCycleSeenObjectCount := currentsCycleSeenObjectCount + 1.
+ 	self assert: ((manager oop: next isLessThan: manager endOfMemory)
+ 		or: [next = manager endOfMemory and: [(self canUseAsFreeSpace: next) not]]).
+ 		
+ 	"we found the end of a segment (old space segments always end in a bridge). Advance to the next"
+ 	next = currentSegmentsBridge
+ 		ifTrue: [
+ 			self setOccupationAtIndex: currentSegmentsIndex used: currentSegmentUsed unused: currentSegmentUnused.
+ 			currentSegmentUsed := currentSegmentUnused := 0.
+ 			currentSegmentsIndex := currentSegmentsIndex + 1.
+ 			currentSegmentsIndex < manager segmentManager numSegments
+ 				ifTrue: [currentSegmentsBridge := manager segmentManager bridgeAt: currentSegmentsIndex]].
+ 
+ 	(self canUseAsFreeSpace: next) and: [currentsCycleSeenObjectCount < MaxObjectsToFree]] 
+ 		whileTrue: [currentObj := next].
+ 	
+ 	^ manager addFreeChunkWithBytes: bytes at: start!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>compact (in category 'api') -----
+ compact
+ 
+ 	<doNotGenerate>
+ 	^ self shouldNotImplement
+ 	
+ 	!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>currentSweepingEntity (in category 'accessing') -----
+ currentSweepingEntity
+ 
+ 	^ currentSweepingEntity!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>currentSweepingEntity: (in category 'accessing') -----
+ currentSweepingEntity: anObject
+ 
+ 	currentSweepingEntity := anObject.!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>doGlobalSweep (in category 'api - global') -----
+ doGlobalSweep
+ 	"Iterate over all entities, in order, making large free chunks from free chunks and unmarked objects, 
+ 	unmarking live objects and rebuilding the free lists."
+ 
+ 	currentSweepingEntity := manager firstObject.
+ 	[self oop: currentSweepingEntity isLessThan: manager endOfMemory] whileTrue:
+ 		[(self canUseAsFreeSpace: currentSweepingEntity) 
+ 			ifTrue: [currentSweepingEntity := self bulkFreeChunkFrom: currentSweepingEntity]
+ 			ifFalse: [self unmark: currentSweepingEntity].
+ 		 currentSweepingEntity := manager objectAfter: currentSweepingEntity limit: manager endOfMemory].
+ 			
+ 	manager checkFreeSpace: GCModeFull.
+ 	manager unmarkSurvivingObjectsForCompact.!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>doIncrementalSweeping (in category 'api - incremental') -----
+ doIncrementalSweeping
+ 	
+ 	"Iterate over all entities, in order, making large free chunks from free chunks and unmarked objects, 
+ 	unmarking live objects and rebuilding the free lists."
+ 	self assert: currentSweepingEntity notNil.
+ 	
+ 	currentsCycleSeenObjectCount := 0.
+ 
+ 	[self oop: currentSweepingEntity isLessThan: manager endOfMemory] whileTrue:
+ 		[ | oldEntity |
+ 		(self canUseAsFreeSpace: currentSweepingEntity) 
+ 			ifTrue: [currentSweepingEntity := self cautiousBulkFreeChunkFrom: currentSweepingEntity]
+ 			ifFalse: [self unmark: currentSweepingEntity. 
+ 				currentSegmentUsed := currentSegmentUsed + (manager bytesInBody: currentSweepingEntity).
+ 				currentsCycleSeenObjectCount := currentsCycleSeenObjectCount + 1].
+ 			
+ 		oldEntity := currentSweepingEntity.
+ 		currentSweepingEntity := manager objectAfter: currentSweepingEntity limit: manager endOfMemory.
+ 		self assert: oldEntity <= currentSweepingEntity.
+ 		self assert: currentSweepingEntity notNil.
+ 		
+ 		currentsCycleSeenObjectCount >= MaxObjectsToFree
+ 			ifTrue: [^ false]].
+ 			
+ 	manager checkFreeSpace: GCModeIncremental.
+ 	^ true!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>finishSweeping (in category 'as yet unclassified') -----
+ finishSweeping
+ 
+ 	isCurrentlySweeping := false.
+ 	manager updateSweepEndUsecs!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>globalSweep (in category 'api - global') -----
+ globalSweep
+ 	<inline: #never> "for profiling"
+ 	
+ 	"throw away all free list info. As this appears to the mutator as an atomic operation it does not need it and we can rebuild it from scratch"
+ 	self resetFreeLists.
+ 	self doGlobalSweep.
+ 	self finishSweeping!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>incrementalSweep (in category 'api - incremental') -----
+ incrementalSweep
+ 	<inline: #never> "for profiling"
+ 	
+ 	self initializeIfNecessary.
+ 	
+ 	self doIncrementalSweeping
+ 		ifTrue: [self finishSweeping.
+ 			^ true].
+ 		
+ 	^ false
+ 	!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 
+ 	super initialize.
+ 	isCurrentlySweeping := false!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>initializeIfNecessary (in category 'api - incremental') -----
+ initializeIfNecessary
+ 
+ 	isCurrentlySweeping
+ 		ifFalse: [currentSegmentUsed := currentSegmentUnused := 0.
+ 				currentSegmentsIndex := 0.
+ 	
+ 				currentSweepingEntity := manager firstObject.
+ 				
+ 				isCurrentlySweeping := true]
+ 	!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>resetFreeLists (in category 'api - global') -----
+ resetFreeLists
+ 	manager resetFreeListHeads.
+ 	manager totalFreeOldSpace: 0.!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>setOccupationAtIndex:used:unused: (in category 'compactor support') -----
+ setOccupationAtIndex: segmentIndex used: used unused: unused
+ 	"WARNING: Resets the isCompacted bit"
+ 	"Swizzle is abused bit 16 isBeingCompacted bits 0-15 occupation
+ 	 Setting occupation resets the claim bit"
+ 	| occupation segInfo |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	segInfo := self addressOf: (manager segmentManager segments at: segmentIndex).
+ 	"careful with overflow here..."
+ 	occupation := ((used asFloat / (used + unused)) * 16rFFFF) asInteger.
+ 	self assert: (occupation between: 0 and: 16rFFFF).
+ 	segInfo swizzle: occupation!

Item was added:
+ ----- Method: SpurIncrementalSweeper>>unmark: (in category 'api') -----
+ unmark: objOop
+ 
+ 	self assert: ((manager isMarked: objOop) and: [(manager isFreeObject: objOop) not]).
+ 	(manager isSegmentBridge: objOop) ifFalse: [
+ 		manager 
+ 			setIsMarkedOf: objOop to: false;
+ 			setIsGreyOf: objOop to: false].
+ 	(manager isPinned: objOop) ifTrue: [manager segmentManager notePinned: objOop]!

Item was added:
+ SpurIncrementalSweeper subclass: #SpurIncrementalSweeperSimulator
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollectorSimulation'!

Item was added:
+ ----- Method: SpurIncrementalSweeperSimulator>>doIncrementalSweeping (in category 'api - incremental') -----
+ doIncrementalSweeping
+ 
+ 	^ GCEventLog
+ 		inContext: #doIncrementalSweep 
+ 		do: [super doIncrementalSweeping]!

Item was added:
+ ----- Method: SpurIncrementalSweeperSimulator>>finishSweeping (in category 'as yet unclassified') -----
+ finishSweeping
+ 
+ 	^ GCEventLog
+ 		inContext: #finishSweeping 
+ 		do: [super finishSweeping]!

Item was added:
+ ----- Method: SpurIncrementalSweeperSimulator>>incrementalSweep (in category 'api - incremental') -----
+ incrementalSweep
+ 
+ 	^ GCEventLog
+ 		inContext: #incrementalSweep 
+ 		do: [super incrementalSweep]!

Item was added:
+ ----- Method: SpurIncrementalSweeperSimulator>>initializeIfNecessary (in category 'api - incremental') -----
+ initializeIfNecessary
+ 
+ 	^ GCEventLog
+ 		inContext: #sweepInit 
+ 		do: [super initializeIfNecessary]!

Item was added:
+ ----- Method: SpurIncrementalSweeperSimulator>>unmark: (in category 'api') -----
+ unmark: objOop
+ 
+ 	^ GCEventLog 
+ 		register: (GCWhitenEvent address: objOop) 
+ 		expecting: {
+ 			[:evt | evt = (GCUnmarkEvent address: objOop)].
+ 			[:evt | evt = (GCUngreyEvent address: objOop)]} 
+ 		doing: [super unmark: objOop]!

Item was added:
+ CogClass subclass: #SpurMarker
+ 	instanceVariableNames: 'manager coInterpreter marking'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'SpurObjStackConstants VMBasicConstants'
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurMarker>>coInterpreter: (in category 'accessing') -----
+ coInterpreter: aVMSimulator
+ 	<doNotGenerate>
+ 	
+ 	coInterpreter := aVMSimulator!

Item was added:
+ ----- Method: SpurMarker>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	marking := false!

Item was added:
+ ----- Method: SpurMarker>>manager: (in category 'accessing') -----
+ manager: aSpurNBitMMXEndianSimulator
+ 	<doNotGenerate>
+ 	manager := aSpurNBitMMXEndianSimulator.
+ 
+ 	aSpurNBitMMXEndianSimulator coInterpreter ifNotNil:
+ 		[:coint | coInterpreter := coint].!

Item was added:
+ ----- Method: SpurMarker>>markAndTrace: (in category 'marking') -----
+ markAndTrace: objOop
+ 
+ 	^ self subclassResponsibility!

Item was added:
+ ----- Method: SpurMarker>>marking (in category 'marking') -----
+ marking 
+ 	<cmacro: '() GIV(marking)'>
+ 	
+ 	^ marking!

Item was added:
+ ----- Method: SpurMarker>>writeBarrierFor:at:with: (in category 'barrier') -----
+ writeBarrierFor: anObject at: index with: value!

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

Item was changed:
  ----- Method: SpurMemoryManager class>>ancilliaryClasses (in category 'translation') -----
  ancilliaryClasses
  	"Answer any extra classes to be included in the translation."
+ 	^{	 SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo }, 
+ 		self gcClass classesForTranslation,
- 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo }, 
- 		self compactorClass classesForTranslation,
  		SpurNewSpaceSpace withAllSubclasses
  		
  	!

Item was changed:
  ----- Method: SpurMemoryManager class>>compactorClass (in category 'accessing class hierarchy') -----
  compactorClass
  	"Answer the compaction algorithm to use."
+ 	^Smalltalk classNamed: (InitializationOptions at: #compactorClass ifAbsent: [self gcClass compactorClass name])!
- 	^Smalltalk classNamed: (InitializationOptions at: #compactorClass ifAbsent: [#SpurPlanningCompactor])!

Item was added:
+ ----- Method: SpurMemoryManager class>>gcClass (in category 'accessing class hierarchy') -----
+ gcClass
+ 	"Answer the garbage collection algorithm to use."
+ 	^Smalltalk classNamed: (InitializationOptions at: #gcClass ifAbsent: [#SpurIncrementalGarbageCollector])!

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.
  
  	"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.
  	 ObjStackNextx must be the last field for swizzleObjStackAt:."
  	ObjStackPageSlots := 4092. "+ double header = 16k bytes per page in 32-bits, 32k bytes per page in 64 bits"
  	ObjStackTopx := 0.
  	ObjStackMyx := 1.
  	ObjStackFreex := 2.
  	ObjStackNextx := 3.
  	ObjStackFixedSlots := 4.
  	ObjStackLimit := ObjStackPageSlots - ObjStackFixedSlots.
  	"The hiddenRootsObject 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.
+ 	EphemeronStackRootIndex := MarkStackRootIndex + 4.
  
  	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 := 64. "max. # of external roots; used e.g. by the PyBridge plugin which uses three entries"
  
  	"gcPhaseInProgress takes these values to identify phases as required."
  	ScavengeInProgress := 1.
  	SlidingCompactionInProgress := 2!

Item was changed:
  ----- Method: SpurMemoryManager class>>isNonArgumentImplicitReceiverVariableName: (in category 'translation') -----
  isNonArgumentImplicitReceiverVariableName: aString
+ 	^#('self' 'coInterpreter' 'manager' 'scavenger' 'segmentManager' 'compactor' 'planningCompactor' 'selectiveCompactor' 'heapMap' 'marker' 'sweeper') includes: aString!
- 	^#('self' 'coInterpreter' 'manager' 'scavenger' 'segmentManager' 'compactor' 'planningCompactor' 'selectiveCompactor' 'heapMap') includes: aString!

Item was added:
+ ----- Method: SpurMemoryManager class>>markerClass (in category 'accessing class hierarchy') -----
+ markerClass
+ 	"Answer the marking algorithm to use."
+ 	^Smalltalk classNamed: (InitializationOptions at: #markerClass ifAbsent: [self gcClass markerClass name])!

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 ifTrue:
  		[freeChunk := self allocateSlots: 0 format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 ^freeChunk].
  	MarkObjectsForEnumerationPrimitives ifTrue:
+ 		[marker markObjects: true]. "may not want to revive objects unnecessarily; but marking is sloooow."
- 		[self markObjects: true]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk. "N.B. Does /not/ update totalFreeOldSpace"
  	start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	(self isClassAtUniqueIndex: aClass)
  		ifTrue:
  			[self uniqueIndex: classIndex allInstancesInto: start limit: limit resultsInto: [:c :p| count := c. ptr := p]]
  		ifFalse:
  			[self ambiguousClass: aClass allInstancesInto: start limit: limit resultsInto: [:c :p| count := c. ptr := p]].
  	self assert: (self isEmptyObjStack: markStack).
  	MarkObjectsForEnumerationPrimitives
  		ifTrue:
  			[self assert: self allObjectsUnmarked.
  			 self emptyObjStack: weaklingStack]
  		ifFalse:
  			[self assert: (self isEmptyObjStack: weaklingStack)].
  	(count > (ptr - start / self bytesPerOop) "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 bytesInBody: freeChunk) at: (self startOfObject: freeChunk).
  		 self beRootIfOld: smallObj.
  		 self checkFreeSpace: GCModeFull.
  		 ^smallObj].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self rawOverflowSlotsOf: freeChunk put: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace: GCModeFull.
  	self runLeakCheckerFor: GCModeFull.
  	^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:
+ 		[marker markObjects: true]. "may not want to revive objects unnecessarily; but marking is sloooow."
- 		[self markObjects: true]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk. "N.B. Does /not/ update totalFreeOldSpace"
  	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 bytesPerOop]]
  				ifFalse:
  					[MarkObjectsForEnumerationPrimitives ifTrue:
  						[(self isSegmentBridge: obj) ifFalse:
  							[self setIsMarkedOf: obj to: false]]]]].
  	self assert: (self isEmptyObjStack: markStack).
  	MarkObjectsForEnumerationPrimitives
  		ifTrue:
  			[self assert: self allObjectsUnmarked.
  			 self emptyObjStack: weaklingStack]
  		ifFalse:
  			[self assert: (self isEmptyObjStack: weaklingStack)].
  	self assert: count >= self numSlotsMask.
  	(count > (ptr - start / self bytesPerOop) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeChunkWithBytes: (self bytesInBody: freeChunk) at: (self startOfObject: freeChunk).
  		 self checkFreeSpace: GCModeFull.
  		 ^self integerObjectOf: count].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self rawOverflowSlotsOf: freeChunk put: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace: GCModeFull.
  	self runLeakCheckerFor: GCModeFull.
  	^freeChunk!

Item was added:
+ ----- Method: SpurMemoryManager>>allUnscannedEphemeronsOnObjStackAreActive (in category 'weakness and ephemerality') -----
+ allUnscannedEphemeronsOnObjStackAreActive
+ 
+ 	[(self isEmptyObjStack: ephemeronStack) not]
+ 		whileTrue: [ | pointer key |
+ 				pointer := self popObjStack: ephemeronStack.
+ 				key := self keyOfMaybeFiredEphemeron: (self longAt: pointer).
+ 				((self isImmediate: key) or: [self isMarked: key]) ifTrue:
+ 					[^false]].
+ 	
+ 	
+ 	^true!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:stackSize:codeSize: (in category 'spur bootstrap') -----
  allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes stackSize: stackBytes codeSize: codeBytes
  	"Intialize the receiver for bootsraping an image.
  	 Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
  	 to allocate in oldSpace.  Later on (in initializePostBootstrap) freeStart and scavengeThreshold
  	 will be set to sane values."
  	<doNotGenerate>
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
  	self allocateMemoryOfSize: memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	newSpaceStart := codeBytes + stackBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes + stackBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + newSpaceStart.
  	oldSpaceStart := newSpaceBytes + newSpaceStart.
  	scavengeThreshold := memory size * memory bytesPerElement. "i.e. /don't/ scavenge."
+ 	
+ 	marker := self class markerClass simulatorClass new manager: self; yourself.
+ 	
  	scavenger := SpurGenerationScavenger simulatorClass new.
  	scavenger manager: self.
  	scavenger newSpaceStart: newSpaceStart
  				newSpaceBytes: newSpaceBytes
  				survivorBytes: newSpaceBytes // self scavengerDenominator.
+ 				
+ 	compactor := self class compactorClass simulatorClass new manager: self; yourself.
+ 	
+ 	gc := self class gcClass simulatorClass new manager: self; marker: marker; compactor: compactor; scavenger: scavenger; yourself.
+ 	!
- 	compactor := self class compactorClass simulatorClass new manager: self; yourself!

Item was changed:
  ----- Method: SpurMemoryManager>>classTableFirstPage (in category 'accessing') -----
  classTableFirstPage
+ 	<cmacro: '() GIV(classTableFirstPage)'>
+ 	
- 	<cmacro>
  	^classTableFirstPage!

Item was changed:
  ----- Method: SpurMemoryManager>>coInterpreter: (in category 'simulation') -----
  coInterpreter: aCoInterpreter
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
+ 	marker ifNotNil:
+ 		[marker coInterpreter: aCoInterpreter].
  	scavenger ifNotNil:
  		[scavenger coInterpreter: aCoInterpreter].
  	compactor ifNotNil:
+ 		[compactor coInterpreter: aCoInterpreter].
+ 	gc ifNotNil:
+ 		[gc coInterpreter: aCoInterpreter]!
- 		[compactor coInterpreter: aCoInterpreter]!

Item was added:
+ ----- Method: SpurMemoryManager>>compactionStartUsecs: (in category 'accessing') -----
+ compactionStartUsecs: anInteger
+ 
+ 	compactionStartUsecs := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>debugGCCollect (in category 'debug support') -----
+ debugGCCollect
+ 	"empties the heap for writing "
+ 
+ 	coInterpreter preGCAction: GCModeFull.
+ 	self flushNewSpace.
+ 	marker markObjects: true.
+ 	scavenger forgetUnmarkedRememberedObjects.
+ 	segmentManager prepareForGlobalSweep.
+ 	compactor compact.
+ 	coInterpreter postGCAction: GCModeFull.
+ 	
+ 	self assert: self validObjStacks.
+ 	self assert: (self isEmptyObjStack: markStack).
+ 	self assert: (self isEmptyObjStack: weaklingStack).
+ 	self assert: self allObjectsUnmarked.!

Item was changed:
  ----- Method: SpurMemoryManager>>doScavenge: (in category 'gc - scavenging') -----
  doScavenge: tenuringCriterion
+ 	
+ 	<doNotGenerate>
+ 	gc doScavenge: tenuringCriterion!
- 	"The inner shell for scavenge, abstrascted out so globalGarbageCollect can use it."
- 	<inline: false>
- 	self doAllocationAccountingForScavenge.
- 	gcPhaseInProgress := ScavengeInProgress.
- 	pastSpaceStart := scavenger scavenge: tenuringCriterion.
- 	self assert: (self
- 					oop: pastSpaceStart
- 					isGreaterThanOrEqualTo: scavenger pastSpace start
- 					andLessThanOrEqualTo: scavenger pastSpace limit).
- 	freeStart := scavenger eden start.
- 	gcPhaseInProgress := 0.
- 	self resetAllocationAccountingAfterGC!

Item was changed:
  ----- Method: SpurMemoryManager>>ensureRoomOnObjStackAt: (in category 'obj stacks') -----
  ensureRoomOnObjStackAt: 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 := stackOrNil = nilObj
  								ifTrue: [0]
  								ifFalse: [self fetchPointer: ObjStackFreex ofObject: stackOrNil].
  		 freeOrNewPage ~= 0
  			ifTrue: "the free page list is always on the new page."
  				[self storePointer: ObjStackFreex ofObjStack: stackOrNil withValue: 0.
+ 				 self assert: (marker marking not or: [self isMarked: freeOrNewPage])]
- 				 self assert: (marking not or: [self isMarked: freeOrNewPage])]
  			ifFalse:
  				[freeOrNewPage := self allocateSlotsInOldSpace: ObjStackPageSlots
  										format: self wordIndexableFormat
  										classIndex: self wordSizeClassIndexPun.
  				 freeOrNewPage ifNil: 
  					["Allocate a new segment an retry. This is very uncommon. But it happened to me (Clement)."
  					 self growOldSpaceByAtLeast: ObjStackPageSlots.
  					 freeOrNewPage := self allocateSlotsInOldSpace: ObjStackPageSlots
  										format: self wordIndexableFormat
  										classIndex: self wordSizeClassIndexPun.
  					freeOrNewPage ifNil: [self error: 'no memory to allocate or extend obj stack']].
  				 self storePointer: ObjStackFreex ofObjStack: freeOrNewPage withValue: 0.
+ 				 marker marking ifTrue: [self setIsMarkedOf: freeOrNewPage to: true].
+ 				 gc maybeModifyGCFlagsOf: freeOrNewPage].
- 				 marking ifTrue: [self setIsMarkedOf: freeOrNewPage to: true]].
  		 self storePointer: ObjStackMyx ofObjStack: freeOrNewPage withValue: objStackRootIndex;
  			  storePointer: ObjStackNextx ofObjStack: freeOrNewPage withValue: (stackOrNil = nilObj ifTrue: [0] ifFalse: [stackOrNil]);
  			  storePointer: ObjStackTopx ofObjStack: freeOrNewPage withValue: 0;
  			  storePointer: objStackRootIndex ofObject: hiddenRootsObj withValue: freeOrNewPage.
  		 self assert: (self isValidObjStackAt: objStackRootIndex).
  		 "Added a new page; now update and answer the relevant cached first page."
  		 stackOrNil := self updateRootOfObjStackAt: objStackRootIndex with: freeOrNewPage].
  	self assert: (self isValidObjStackAt: objStackRootIndex).
  	^stackOrNil!

Item was added:
+ ----- Method: SpurMemoryManager>>ephemeronStack (in category 'accessing') -----
+ ephemeronStack
+ 	
+ 	<doNotGenerate>
+ 	^ ephemeronStack!

Item was added:
+ ----- Method: SpurMemoryManager>>extraRootCount (in category 'accessing') -----
+ extraRootCount
+ 
+ 	^ extraRootCount!

Item was added:
+ ----- Method: SpurMemoryManager>>extraRoots (in category 'accessing') -----
+ extraRoots
+ 	<cmacro: '() GIV(extraRoots)'>
+ 	^ extraRoots!

Item was changed:
  ----- Method: SpurMemoryManager>>followClassTable (in category 'selective compaction') -----
  followClassTable
  	"In addition to postBecomeScanClassTable:, I follow the pages in the class table.
  	 Because hiddenRootsObj follows nil, false, true and the freeLists, it can never be forwarded."
  	self deny: (self isForwarded: hiddenRootsObj).
  	0 to: numClassTablePages - 1 do:
  		[:i| | page |
  		page := self followField: i ofObject: hiddenRootsObj.
  		0 to: (self numSlotsOf: page) - 1 do:
  			[:j| | classOrNil |
  			classOrNil := self fetchPointer: j ofObject: page.
+ 			self assert: (self isFreeObject: classOrNil) not.
  			classOrNil ~= nilObj ifTrue:
  				[(self isForwarded: classOrNil) ifTrue:
  					[classOrNil := self followForwarded: classOrNil.
  					 self storePointer: j ofObject: page withValue: classOrNil].
  				 (self rawHashBitsOf: classOrNil) = 0 ifTrue:
  					[self storePointerUnchecked: j ofObject: page withValue: nilObj.
  					 "If the removed class is before the classTableIndex, set the
  					  classTableIndex to point to the empty slot so as to reuse it asap."
  					 (i << self classTableMajorIndexShift + j) < classTableIndex ifTrue:
  						[classTableIndex := i << self classTableMajorIndexShift + j]]]]].
  	"classTableIndex must never index the first page, which is reserved for classes known to the VM."
  	self assert: classTableIndex >= (1 << self classTableMajorIndexShift).
  	self assert: self validClassTableRootPages!

Item was changed:
  ----- Method: SpurMemoryManager>>followForwardedObjStacks (in category 'compaction') -----
  followForwardedObjStacks
  	"Compaction will move objStack pages as well as ordinary objects.
  	 So they need their slots followed."
  	self followForwardedInObjStack: markStack atIndex: MarkStackRootIndex.
  	self followForwardedInObjStack: weaklingStack atIndex: WeaklingStackRootIndex.
+ 	self followForwardedInObjStack: mournQueue atIndex: MournQueueRootIndex.
+ 	self followForwardedInObjStack: ephemeronStack atIndex: EphemeronStackRootIndex!
- 	self followForwardedInObjStack: mournQueue atIndex: MournQueueRootIndex!

Item was added:
+ ----- Method: SpurMemoryManager>>freeLists (in category 'accessing') -----
+ freeLists
+ 
+ 	^ freeLists!

Item was added:
+ ----- Method: SpurMemoryManager>>freeStart: (in category 'accessing') -----
+ freeStart: anInteger
+ 
+ 	freeStart := anInteger!

Item was changed:
  ----- Method: SpurMemoryManager>>fullGC (in category 'gc - global') -----
  fullGC
+ 	<doNotGenerate>
+ 	
+ 	gc fullGC!
- 	"Perform a full eager compacting GC.  Answer the size of the largest free chunk."
- 	<returnTypeC: #usqLong>
- 	<inline: #never> "for profiling"
- 	needGCFlag := false.
- 	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
- 	statMarkCount := 0.
- 	coInterpreter preGCAction: GCModeFull.
- 	self globalGarbageCollect.
- 	coInterpreter postGCAction: GCModeFull.
- 	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
- 	self updateFullGCStats.
- 	^(freeLists at: 0) ~= 0
- 		ifTrue: [self bytesInBody: self findLargestFreeChunk]
- 		ifFalse: [0]!

Item was added:
+ ----- Method: SpurMemoryManager>>gc (in category 'accessing') -----
+ gc
+ 
+ 	^ gc!

Item was added:
+ ----- Method: SpurMemoryManager>>gc: (in category 'accessing') -----
+ gc: aSpurGarbageCollector
+ 
+ 	gc := aSpurGarbageCollector!

Item was added:
+ ----- Method: SpurMemoryManager>>gcMarkEndUsecs: (in category 'accessing') -----
+ gcMarkEndUsecs: anInteger
+ 
+ 	gcMarkEndUsecs := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>gcPhaseInProgress: (in category 'accessing') -----
+ gcPhaseInProgress: anInteger
+ 
+ 	gcPhaseInProgress := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>gcStartUsecs: (in category 'accessing') -----
+ gcStartUsecs: anInteger
+ 	
+ 	gcStartUsecs := anInteger!

Item was removed:
- ----- Method: SpurMemoryManager>>globalGarbageCollect (in category 'gc - global') -----
- globalGarbageCollect
- 	<inline: true> "inline into fullGC"
- 	self assert: self validObjStacks.
- 	self assert: (self isEmptyObjStack: markStack).
- 	self assert: (self isEmptyObjStack: weaklingStack).
- 
- 	"Mark objects /before/ scavenging, to empty the rememberedTable of unmarked roots."
- 	self markObjects: true.
- 	gcMarkEndUsecs := coInterpreter ioUTCMicrosecondsNow.
- 	
- 	scavenger forgetUnmarkedRememberedObjects.
- 
- 	coInterpreter setGCMode: GCModeNewSpace.
- 	self doScavenge: MarkOnTenure.
- 	coInterpreter setGCMode: GCModeFull.
- 
- 	"Mid-way the leak check must be more lenient.  Unmarked classes will have been
- 	 expunged from the table, but unmarked instances will not yet have been reclaimed."
- 	self runLeakCheckerFor: GCModeFull
- 		excludeUnmarkedObjs: true
- 		classIndicesShouldBeValid: true.
- 
- 	compactionStartUsecs := coInterpreter ioUTCMicrosecondsNow.
- 	segmentManager prepareForGlobalSweep. "for notePinned:"
- 	compactor compact.
- 	self attemptToShrink.
- 	self setHeapSizeAtPreviousGC.
- 
- 	self assert: self validObjStacks.
- 	self assert: (self isEmptyObjStack: markStack).
- 	self assert: (self isEmptyObjStack: weaklingStack).
- 	self assert: self allObjectsUnmarked.
- 	self runLeakCheckerFor: GCModeFull!

Item was added:
+ ----- Method: SpurMemoryManager>>hiddenRootsObj (in category 'accessing') -----
+ hiddenRootsObj
+ 
+ 	^ hiddenRootsObj!

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."
  	| moreThanEnough |
  	remapBuffer := Array new: RemapBufferSize.
  	remapBufferCount := extraRootCount := 0. "see below"
  	freeListsMask := totalFreeOldSpace := lowSpaceThreshold := 0.
  	checkForLeaks := 0.
+ 	needGCFlag := signalLowSpace := false.
- 	needGCFlag := signalLowSpace := marking := false.
  	becomeEffectsFlags := gcPhaseInProgress := validatedIntegerClassFlags := 0.
  	statScavenges := statIncrGCs := statFullGCs := 0.
  	statMaxAllocSegmentTime := 0.
  	statMarkUsecs := statSweepUsecs := statScavengeGCUsecs := statIncrGCUsecs := statFullGCUsecs := statCompactionUsecs := statGCEndUsecs := gcSweepEndUsecs := 0.
  	statSGCDeltaUsecs := statIGCDeltaUsecs := statFGCDeltaUsecs := 0.
  	statGrowMemory := statShrinkMemory := statRootTableCount := statAllocatedBytes := 0.
  	statRootTableOverflows := statMarkCount := statCompactPassCount := statCoalesces := 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 := SpurGenerationScavenger simulatorClass new manager: self; yourself.
  	segmentManager := SpurSegmentManager simulatorClass new manager: self; yourself.
  	compactor := self class compactorClass simulatorClass new manager: self; yourself.
+ 	marker := self class markerClass simulatorClass new manager: self; yourself.
+ 	gc := self class gcClass simulatorClass new manager: self; marker: marker; compactor: compactor; scavenger: scavenger; yourself.
  
  	"We can also initialize here anything that is only for simulation."
  	heapMap := CogCheck32BitHeapMap new.
  
  	"N.B. We *don't* initialize extraRoots because we don't simulate it."
  
  	"This is needed on 64-bits. We don't want a simulation creating a huge heap by default.
  	 By default use 512Mb on 64-bits, 256Mb on 32-bits."
  	moreThanEnough := 1024 * 1024 * 1024 / (16 / self wordSize). "One million dollars, ha ha ha ha ha,... ha, ha ha ha ha, ..."
  	maxOldSpaceSize := self class initializationOptions
  							ifNotNil: [:initOpts| initOpts at: #maxOldSpaceSize ifAbsent: [moreThanEnough]]
  							ifNil: [moreThanEnough]!

Item was added:
+ ----- Method: SpurMemoryManager>>initializeEphemeronStack (in category 'gc - global') -----
+ initializeEphemeronStack
+ 	self ensureRoomOnObjStackAt: EphemeronStackRootIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory at al are
  	 initialised by the image-reading code via setHeapBase:memoryLimit:endOfMemory:.
  	 endOfMemory is assumed to point to the end of the last object in the image.
  	 Assume: image reader also initializes the following variables:
  		specialObjectsOop
  		lastHash"
  	<inline: false>
  	| freeListObj |
  	"Catch mis-initializations leading to bad translations to C"
  	self assert: self baseHeaderSize = self baseHeaderSize.
  	self assert: (self maxSlotsForAlloc * self wordSize) asInteger > 0.
  	self bootstrapping ifFalse:
  		[self
  			initSegmentBridgeWithBytes: self bridgeSize
  			at: endOfMemory - self bridgeSize].
  	segmentManager adjustSegmentSwizzlesBy: bytesToShift.
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
  	specialObjectsOop := segmentManager swizzleObj: specialObjectsOop.
  
  	"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 = oldSpaceStart.
  	self assert: falseObj = (self oldSpaceObjectAfter: nilObj).
  	self assert: trueObj = (self oldSpaceObjectAfter: falseObj).
  	freeListObj := self oldSpaceObjectAfter: trueObj.
  	self setHiddenRootsObj: (self oldSpaceObjectAfter: freeListObj).
  	markStack := self swizzleObjStackAt: MarkStackRootIndex.
  	weaklingStack := self swizzleObjStackAt: WeaklingStackRootIndex.
  	mournQueue := self swizzleObjStackAt: MournQueueRootIndex.
+ 	ephemeronStack := self swizzleObjStackAt: EphemeronStackRootIndex.
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
+ 	self assert: (self isEmptyObjStack: ephemeronStack).
  
  	self initializeFreeSpacePostLoad: freeListObj.
  	segmentManager collapseSegmentsPostSwizzle.
  	self updateFreeLists.
  	self computeFreeSpacePostSwizzle.
  	compactor postSwizzleAction.
  	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart, free space"
  	self initializeNewSpaceVariables.
  	scavenger initializeRememberedSet.
  	segmentManager checkSegments.
  	compactor biasForGC.
  
  	"These defaults should depend on machine size; e.g. too small on a powerful laptop, too big on a Pi."
  	growHeadroom := 16*1024*1024.		"headroom when growing"
  	shrinkThreshold := 32*1024*1024.		"free space before shrinking"
  	self setHeapSizeAtPreviousGC.
  	heapGrowthToSizeGCRatio := 0.333333. "By default GC after scavenge if heap has grown by a third since the last GC"!

Item was changed:
  ----- Method: SpurMemoryManager>>isValidObjStackPage:myIndex: (in category 'obj stacks') -----
  isValidObjStackPage: objStackPage myIndex: myx
  	"Just check the page itself."
  	<inline: false>
  	(self classIndexOf: objStackPage) = self wordSizeClassIndexPun ifFalse:
  		[objStackInvalidBecause := 'wrong class index'.
  		 invalidObjStackPage := objStackPage.
  		 ^false].
  	(self formatOf: objStackPage) = self wordIndexableFormat ifFalse:
  		[objStackInvalidBecause := 'wrong format'.
  		 invalidObjStackPage := objStackPage.
  		 ^false].
  	(self numSlotsOfAny: objStackPage) = ObjStackPageSlots ifFalse:
  		[objStackInvalidBecause := 'wrong num slots'.
  		 invalidObjStackPage := objStackPage.
  		 ^false].
  	myx = (self fetchPointer: ObjStackMyx ofObject: objStackPage) ifFalse:
  		[objStackInvalidBecause := 'wrong myx'.
  		 invalidObjStackPage := objStackPage.
  		 ^false].
+ 	(marker marking and: [(self isMarked: objStackPage) not]) ifTrue:
- 	(marking and: [(self isMarked: objStackPage) not]) ifTrue:
  		[objStackInvalidBecause := 'marking but page is unmarked'.
  		 invalidObjStackPage := objStackPage.
  		 ^false].
  	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>isWhite: (in category 'header access') -----
+ isWhite: objOop
+ 	"The object was not seen by the marker until now"
+ 	
+ 	^ ((self isMarked: objOop) or: [self isGrey: objOop]) not!

Item was added:
+ ----- Method: SpurMemoryManager>>lowSpaceThreshold (in category 'accessing') -----
+ lowSpaceThreshold
+ 
+ 	^ lowSpaceThreshold!

Item was added:
+ ----- Method: SpurMemoryManager>>makeWhite: (in category 'header access') -----
+ makeWhite: objOop
+ 	"The object was not seen by the marker until now"
+ 	
+ 	self 
+ 		setIsMarkedOf: objOop to: false;
+ 		setIsGreyOf: objOop to: false!

Item was removed:
- ----- Method: SpurMemoryManager>>markAccessibleObjectsAndFireEphemerons (in category 'gc - global') -----
- markAccessibleObjectsAndFireEphemerons
- 	self assert: marking.
- 	self assert: self validClassTableRootPages.
- 	self assert: segmentManager allBridgesMarked.
- 	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
- 		inSmalltalk: [MarkStackRecord ifNotNil: [MarkStackRecord resetTo: 1]].
- 
- 	"This must come first to enable stack page reclamation.  It clears
- 	  the trace flags on stack pages and so must precede any marking.
- 	  Otherwise it will clear the trace flags of reached pages."
- 	coInterpreter initStackPageGC.
- 	self markAndTraceHiddenRoots.
- 	self markAndTraceExtraRoots.
- 	self assert: self validClassTableRootPages.
- 	coInterpreter markAndTraceInterpreterOops: true.
- 	self assert: self validObjStacks.
- 	self markWeaklingsAndMarkAndFireEphemerons.
- 	self assert: self validObjStacks!

Item was removed:
- ----- Method: SpurMemoryManager>>markAllUnscannedEphemerons (in category 'weakness and ephemerality') -----
- markAllUnscannedEphemerons
- 	"After firing the unscanned ephemerons we must scan-mark them.
- 	 The wrinkle is that doing so may add more ephemerons to the set.
- 	 So we remove the first element, by overwriting it with the last element,
- 	 and decrementing the top, and then markAndTrace its contents."
- 	self assert: (self noUnscannedEphemerons) not.
- 	self assert: self allUnscannedEphemeronsAreActive.
- 	[unscannedEphemerons top > unscannedEphemerons start] whileTrue:
- 		[| ephemeron key lastptr |
- 		 ephemeron := self longAt: unscannedEphemerons start.
- 		 lastptr := unscannedEphemerons top - self bytesPerOop.
- 		 lastptr > unscannedEphemerons start ifTrue:
- 			[self longAt: unscannedEphemerons start put: (self longAt: lastptr)].
- 		 unscannedEphemerons top: lastptr.
- 		 key := self followedKeyOfMaybeFiredEphemeron: ephemeron.
- 		 self setIsMarkedOf: ephemeron to: false. "to get it to be fully scanned in markAndTrace:"
- 		 self
- 			markAndTrace: key;
- 			markAndTrace: ephemeron]!

Item was removed:
- ----- Method: SpurMemoryManager>>markAndShouldScan: (in category 'gc - global') -----
- markAndShouldScan: objOop
- 	"Helper for markAndTrace:.
- 	 Mark the argument, and answer if its fields should be scanned now.
- 	 Immediate objects don't need to be marked.
- 	 Already marked objects have already been processed.
- 	 Pure bits objects don't need scanning, although their class does.
- 	 Weak objects should be pushed on the weakling stack.
- 	 Anything else need scanning."
- 	| format |
- 	<inline: true>
- 	(self isImmediate: objOop) ifTrue:
- 		[^false].
- 	"if markAndTrace: is to follow and eliminate forwarding pointers
- 	 in its scan it cannot be handed an r-value which is forwarded."
- 	self assert: (self isForwarded: objOop) not.
- 	(self isMarked: objOop) ifTrue:
- 		[^false].
- 	self setIsMarkedOf: objOop to: true.
- 	format := self formatOf: objOop.
- 	(self isPureBitsFormat: format) ifTrue: "avoid pushing non-pointer objects on the markStack."
- 		["Avoid tracing classes of non-objects on the heap, e.g. IRC caches, Sista counters."
- 		 (self classIndexOf: objOop) > self lastClassIndexPun ifTrue:
- 			[self markAndTraceClassOf: objOop].
- 		 ^false].
- 	format = self weakArrayFormat ifTrue: "push weaklings on the weakling stack to scan later"
- 		[self push: objOop onObjStack: weaklingStack.
- 		 ^false].
- 	(format = self ephemeronFormat
- 	 and: [self activeAndDeferredScan: objOop]) ifTrue:
- 		[^false].
- 	^true!

Item was changed:
  ----- 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. Follow forwarding pointers in the scan. This behaviour is now
+ 	 extracted to the SpurMarker hierarchy, so bridge to it."
+ 	<doNotGenerate>
- 	 on the mark stack. Follow forwarding pointers in the scan."
- 	<api>
- 	<inline: #never>
- 	"if markAndTrace: is to follow and eliminate forwarding pointers
- 	 in its scan it cannot be handed an r-value which is forwarded.
- 	 The assert for this is in markAndShouldScan:"
- 	(self markAndShouldScan: objOop) ifFalse:
- 		[^self].
  
+ 	^marker markAndTrace: objOop!
- 	"Now scan the object, and any remaining objects on the mark stack."
- 	self markLoopFrom: objOop!

Item was removed:
- ----- Method: SpurMemoryManager>>markAndTraceClassOf: (in category 'gc - global') -----
- markAndTraceClassOf: objOop
- 	"Ensure the class of the argument is marked, pushing it on the markStack if not already marked.
- 	 And for one-way become, which can create duplicate entries in the class table, make sure
- 	 objOop's classIndex refers to the classObj's actual classIndex.
- 	 Note that this is recursive, but the metaclass chain should terminate quickly."
- 	<inline: false>
- 	| classIndex classObj realClassIndex |
- 	classIndex := self classIndexOf: objOop.
- 	classObj := self classOrNilAtIndex: classIndex.
- 	self assert: (coInterpreter objCouldBeClassObj: classObj).
- 	realClassIndex := self rawHashBitsOf: classObj.
- 	(classIndex ~= realClassIndex
- 	 and: [classIndex > self lastClassIndexPun]) ifTrue:
- 		[self setClassIndexOf: objOop to: realClassIndex].
- 	(self isMarked: classObj) ifFalse:
- 		[self setIsMarkedOf: classObj to: true.
- 		 self markAndTraceClassOf: classObj.
- 		 self push: classObj onObjStack: markStack]!

Item was removed:
- ----- Method: SpurMemoryManager>>markAndTraceExtraRoots (in category 'gc - global') -----
- markAndTraceExtraRoots
- 	| oop |
- 	self assert: remapBufferCount = 0.
- 	"1 to: remapBufferCount do:
- 		[:i|
- 		 oop := remapBuffer at: i.
- 		 ((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
- 			[self markAndTrace: oop]]."
- 	1 to: extraRootCount do:
- 		[:i|
- 		oop := (extraRoots at: i) at: 0.
- 		((self isImmediate: oop) or: [self isFreeObject: oop]) ifFalse:
- 			[self markAndTrace: oop]]!

Item was removed:
- ----- Method: SpurMemoryManager>>markAndTraceHiddenRoots (in category 'gc - global') -----
- markAndTraceHiddenRoots
- 	"The hidden roots hold both the class table pages and the obj stacks,
- 	 and hence need special treatment.  The obj stacks must be marked
- 	 specially; their pages must be marked, but only the contents of the
- 	 mournQueue should be marked.
- 
- 	 If a class table page is weak we can mark and trace the hiddenRoots,
- 	 which will not trace through class table pages because they are weak.
- 	 But if class table pages are strong, we must mark the pages and *not*
- 	 trace them so that only classes reachable from the true roots will be
- 	 marked, and unreachable classes will be left unmarked."
- 
- 	self markAndTraceObjStack: markStack andContents: false.
- 	self markAndTraceObjStack: weaklingStack andContents: false.
- 	self markAndTraceObjStack: mournQueue andContents: true.
- 
- 	self setIsMarkedOf: self rememberedSetObj to: true.
- 	self setIsMarkedOf: self freeListsObj to: true.
- 
- 	(self isWeakNonImm: classTableFirstPage) ifTrue:
- 		[^self markAndTrace: hiddenRootsObj].
- 
- 	self setIsMarkedOf: hiddenRootsObj to: true.
- 	self markAndTrace: classTableFirstPage.
- 	1 to: numClassTablePages - 1 do:
- 		[:i| self setIsMarkedOf: (self fetchPointer: i ofObject: hiddenRootsObj)
- 				to: true]!

Item was removed:
- ----- 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."
- 	<inline: false>
- 	| index field |
- 	stackOrNil = nilObj ifTrue:
- 		[^self].
- 	self setIsMarkedOf: stackOrNil to: true.
- 	self assert: (self numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
- 	field := self fetchPointer: ObjStackNextx ofObject: stackOrNil.
- 	field ~= 0 ifTrue:
- 		[self markAndTraceObjStack: field andContents: markAndTraceContents].
- 	field := stackOrNil.
- 	[field := self fetchPointer: ObjStackFreex ofObject: field.
- 	 field ~= 0] whileTrue:
- 		[self setIsMarkedOf: field to: true].
- 	markAndTraceContents ifFalse:
- 		[^self].
- 	"There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
- 	  if there were 6 slots in an oop stack, full would be 2, and the last 0-rel index is 5."
- 	index := (self fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
- 	[index >= ObjStackFixedSlots] whileTrue:
- 		[field := self followObjField: index ofObject: stackOrNil.
- 		 (self isImmediate: field) ifFalse:
- 			[self markAndTrace: field].
- 		 index := index - 1]!

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

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

Item was removed:
- ----- Method: SpurMemoryManager>>markLoopFrom: (in category 'gc - global') -----
- markLoopFrom: objOop
- 	"Scan objOop and all objects on the mark stack, until the mark stack is empty.
- 	 N.B. When the incremental GC is written this will probably be refactored as
- 	 markLoopFrom: objOop while: aBlock"
- 	<inline: true>
- 	| objToScan field index numStrongSlots scanLargeObject |
- 
- 	"Now scan the object, and any remaining objects on the mark stack."
- 	objToScan := objOop.
- 	"To avoid overflowing the mark stack when we encounter large objects, we
- 	 push the obj, then its numStrongSlots, and then index the object from the stack."
- 	[(self isImmediate: objToScan)
- 		ifTrue: [scanLargeObject := true]
- 		ifFalse:
- 			[numStrongSlots := self numStrongSlotsOfInephemeral: objToScan.
- 			 scanLargeObject := numStrongSlots > self traceImmediatelySlotLimit].
- 	 scanLargeObject
- 		ifTrue: "scanning a large object. scan until hitting an unmarked object, then switch to it, if any."
- 			[(self isImmediate: objToScan)
- 				ifTrue:
- 					[index := self integerValueOf: objToScan.
- 					 objToScan := self topOfObjStack: markStack]
- 				ifFalse:
- 					[index := numStrongSlots.
- 					 self markAndTraceClassOf: objToScan].
- 			 [index > 0] whileTrue:
- 				[index := index - 1.
- 				 field := self fetchPointer: index ofObject: objToScan.
- 				 (self isNonImmediate: field) ifTrue:
- 					[(self isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
- 						[field := self fixFollowedField: index ofObject: objToScan withInitialValue: field].
- 					 (self markAndShouldScan: field) ifTrue:
- 						[index > 0 ifTrue:
- 							[(self topOfObjStack: markStack) ~= objToScan ifTrue: 
- 								[self push: objToScan onObjStack: markStack].
- 							 self push: (self integerObjectOf: index) onObjStack: markStack].
- 						 objToScan := field.
- 						 index := -1]]].
- 			 index >= 0 ifTrue: "if loop terminated without finding an unmarked referent, switch to top of stack."
- 				[objToScan := self popObjStack: markStack.
- 				 objToScan = objOop ifTrue:
- 					[objToScan := self popObjStack: markStack]]]
- 		ifFalse: "scanning a small object. scan, marking, pushing unmarked referents, then switch to the top of the stack."
- 			[index := numStrongSlots.
- 			 self markAndTraceClassOf: objToScan.
- 			 [index > 0] whileTrue:
- 				[index := index - 1.
- 				 field := self fetchPointer: index ofObject: objToScan.
- 				 (self isNonImmediate: field) ifTrue:
- 					[(self isForwarded: field) ifTrue: "fixFollowedField: is /not/ inlined"
- 						[field := self fixFollowedField: index ofObject: objToScan withInitialValue: field].
- 					 (self markAndShouldScan: field) ifTrue:
- 						[self push: field onObjStack: markStack.
- 						 ((self rawNumSlotsOf: field) > self traceImmediatelySlotLimit
- 						  and: [(numStrongSlots := self numStrongSlotsOfInephemeral: field) > self traceImmediatelySlotLimit]) ifTrue:
- 							[self push: (self integerObjectOf: numStrongSlots) onObjStack: markStack]]]].
- 			 objToScan := self popObjStack: markStack].
- 	 objToScan notNil] whileTrue!

Item was removed:
- ----- Method: SpurMemoryManager>>markObjects: (in category 'gc - global') -----
- markObjects: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
- 	<inline: #never> "for profiling"
- 	"Mark all accessible objects.  objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged
- 	 is true if all objects are unmarked and/or if unmarked classes shoud be removed from the class table."
- 	"If the incremental collector is running mark bits may be set; stop it and clear them if necessary."
- 	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'marking...'; flush].
- 	self runLeakCheckerFor: GCModeFull.
- 
- 	self shutDownGlobalIncrementalGC: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
- 	self initializeUnscannedEphemerons.
- 	self initializeMarkStack.
- 	self initializeWeaklingStack.
- 	marking := true.
- 	self markAccessibleObjectsAndFireEphemerons.
- 	self expungeDuplicateAndUnmarkedClasses: objectsShouldBeUnmarkedAndUnmarkedClassesShouldBeExpunged.
- 	self nilUnmarkedWeaklingSlots.
- 	marking := false!

Item was removed:
- ----- 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 strong slots traced before firing ephemerons..."
- 	 [numTracedWeaklings := self markAndTraceWeaklingsFrom: numTracedWeaklings.
- 	  (self sizeOfObjStack: weaklingStack) > numTracedWeaklings] whileTrue.
- 	 self noUnscannedEphemerons ifTrue:
- 		[coInterpreter
- 			markAndTraceUntracedReachableStackPages;
- 	 		markAndTraceMachineCodeOfMarkedMethods;
- 			freeUntracedStackPages;
- 			freeUnmarkedMachineCode.
- 		 ^self].
- 	 self markInactiveEphemerons ifFalse:
- 		[self fireAllUnscannedEphemerons].
- 	 self markAllUnscannedEphemerons]
- 		repeat!

Item was added:
+ ----- Method: SpurMemoryManager>>marker (in category 'accessing') -----
+ marker
+ 
+ 	^ marker!

Item was added:
+ ----- Method: SpurMemoryManager>>needGCFlag: (in category 'accessing') -----
+ needGCFlag: anInteger
+ 	
+ 	needGCFlag := anInteger ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>nilObj (in category 'accessing') -----
+ nilObj
+ 
+ 	^ nilObj!

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: #never> "for profiling"
  	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'nilling...'; flush].
  	self eassert: [self allOldMarkedWeakObjectsOnWeaklingStack].
  	weaklingStack = nilObj ifTrue:
  		[^self].
  	self objStack: weaklingStack from: 0 do:
  		[:weakling| | anyUnmarked |
  		anyUnmarked := self nilUnmarkedWeaklingSlotsIn: weakling.
  		anyUnmarked ifTrue:
  			["fireFinalization: could grow the mournQueue and if so,
  			  additional pages must be marked to avoid being GC'ed."
+ 			 self assert: marker marking.
- 			 self assert: marking.
  			 coInterpreter fireFinalization: weakling]].
  	self emptyObjStack: weaklingStack!

Item was added:
+ ----- Method: SpurMemoryManager>>numClassTablePages (in category 'accessing') -----
+ numClassTablePages
+ 
+ 	^ numClassTablePages!

Item was changed:
  ----- Method: SpurMemoryManager>>objectsReachableFromRoots: (in category 'image segment in/out') -----
  objectsReachableFromRoots: arrayOfRoots
  	"This is part of storeImageSegmentInto:outPointers:roots:.
  	 Answer an Array of all the objects only reachable from the argument, an Array of root objects,
  	 starting with arrayOfRoots.  If there is no space, answer a SmallInteger whose value is the
  	 number of slots required.  This is used to collect the objects to include in an image segment
  	 on Spur, separate from creating the segment, hence simplifying the implementation.
  	 Thanks to Igor Stasenko for this idea."
  
  	| freeChunk ptr start limit count oop objOop |
  	<var: #freeChunk type: #usqInt> "& hence start & ptr are too; limit is also because of addressAfter:"
  	<inline: #never>
  	self assert: (self isArray: arrayOfRoots).
  	"Mark all objects except those only reachable from the arrayOfRoots by marking
  	 each object in arrayOfRoots and then marking all reachable objects (from the
  	 system roots).  This leaves unmarked only objects reachable from the arrayOfRoots.
  	 N.B. A side-effect of the marking is that all forwarders in arrayOfRoots will be followed."
   	self assert: self allObjectsUnmarked.
  	self markObjectsIn: arrayOfRoots.
+ 	marker markObjects: false.
- 	self markObjects: false.
  
  	"After the mark phase all unreachable weak slots will have been nilled
  	 and all active ephemerons fired."
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  	self assert: self noUnscannedEphemerons.
  
  	"Now unmark the roots before collecting the transitive closure of unmarked objects accessible from the roots."
  	self unmarkObjectsIn: arrayOfRoots.
  
  	"Use the largest free chunk to answer the result."
  	freeChunk := self allocateLargestFreeChunk. "N.B. Does /not/ update totalFreeOldSpace"
  	totalFreeOldSpace := totalFreeOldSpace - (self bytesInBody: freeChunk). "but must update so that growth in the markStack does not cause assert fails."
  	ptr := start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	count := 0.
  
  	"First put the arrayOfRoots; order is important."
  	self noCheckPush: arrayOfRoots onObjStack: markStack.
  
  	"Now collect the roots and the transitive closure of unmarked objects from them."
  	[self isEmptyObjStack: markStack] whileFalse:
  		[objOop := self popObjStack: markStack.
  		 self assert: (self isMarked: objOop).
  		 count := count + 1.
  		 ptr < limit ifTrue:
  			[self longAt: ptr put: objOop.
  			 ptr := ptr + self bytesPerOop].
  		 oop := self fetchClassOfNonImm: objOop.
  		 (self isMarked: oop) ifFalse:
  			[self setIsMarkedOf: oop to: true.
  			 self noCheckPush: oop onObjStack: markStack].
  		 ((self isContextNonImm: objOop)
  		  and: [coInterpreter isStillMarriedContext: objOop]) "widow now, before the copy loop"
  			ifTrue:
  				[0 to: (coInterpreter numSlotsOfMarriedContext: objOop) - 1 do:
  					[:i|
  					 oop := coInterpreter fetchPointer: i ofMarriedContext: objOop.
  					 ((self isImmediate: oop)
  					  or: [self isMarked: oop]) ifFalse:
  						[self setIsMarkedOf: oop to: true.
  						 self noCheckPush: oop onObjStack: markStack]]]
  			ifFalse:
  				[0 to: (self numPointerSlotsOf: objOop) - 1 do:
  					[:i|
  					 oop := self fetchPointer: i ofObject: objOop.
  					 ((self isImmediate: oop)
  					  or: [self isMarked: oop]) ifFalse:
  						[self setIsMarkedOf: oop to: true.
  						 self noCheckPush: oop onObjStack: markStack]]]].
  
  	self unmarkAllObjects.
  
  	"Now try and allocate the result"
  	(count > (ptr - start / self bytesPerOop) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
  		[self freeObject: freeChunk.
  		 self checkFreeSpace: GCCheckImageSegment.
  		 ^self integerObjectOf: count].
  	"There's room; set the format, & classIndex and shorten."
  	self setFormatOf: freeChunk to: self arrayFormat.
  	self setClassIndexOf: freeChunk to: ClassArrayCompactIndex.
  	self shorten: freeChunk toIndexableSize: count.
  	(self isForwarded: freeChunk) ifTrue:
  		[freeChunk := self followForwarded: freeChunk].
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace: GCCheckImageSegment.
  	self runLeakCheckerFor: GCCheckImageSegment.
  	^freeChunk!

Item was added:
+ ----- Method: SpurMemoryManager>>oldSpaceObjectCount (in category 'debug printing') -----
+ oldSpaceObjectCount
+ 
+ 	| num |
+ 	num := 0.
+ 	self allOldSpaceObjectsDo: [:ea | num := num+1].
+ 	^ num!

Item was added:
+ ----- Method: SpurMemoryManager>>pastSpaceStart: (in category 'accessing') -----
+ pastSpaceStart: anInteger
+ 
+ 	pastSpaceStart := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>preGlobalGCActions (in category 'gc - global') -----
+ preGlobalGCActions
+ 	<doNotGenerate>!

Item was changed:
  ----- Method: SpurMemoryManager>>prepareObjStacksForPlanningCompactor (in category 'compaction') -----
  prepareObjStacksForPlanningCompactor
  	"SpurPlanningCompactor overwrites the first fields of all moved objects, and saves these
  	 fields in a data structure from which they can only be retrieved while scanning the heap.
  	 The first field of an objStack page is its stack index, and so to know how many fields in an
  	 objStack page to update it is necessary to save the ObjStackTopx field somewhere temporarily.
  	 We use the hash field."
  
  	self
  		prepareObjStackForPlanningCompactor: markStack;
  		prepareObjStackForPlanningCompactor: weaklingStack;
+ 		prepareObjStackForPlanningCompactor: mournQueue;
+ 		prepareObjStackForPlanningCompactor: ephemeronStack!
- 		prepareObjStackForPlanningCompactor: mournQueue!

Item was changed:
  ----- Method: SpurMemoryManager>>relocateObjStacksForPlanningCompactor (in category 'compaction') -----
  relocateObjStacksForPlanningCompactor
  	"Relocate all non-empty objStack pages, following the objStacks from the roots."
  
  	markStack := self relocateObjStackForPlanningCompactor: markStack andContents: false.
  	weaklingStack := self relocateObjStackForPlanningCompactor: weaklingStack andContents: false.
+ 	mournQueue := self relocateObjStackForPlanningCompactor: mournQueue andContents: true.
+ 	ephemeronStack := self relocateObjStackForPlanningCompactor: ephemeronStack andContents: true.!
- 	mournQueue := self relocateObjStackForPlanningCompactor: mournQueue andContents: true!

Item was changed:
  ----- Method: SpurMemoryManager>>scavengingGCTenuringIf: (in category 'gc - scavenging') -----
  scavengingGCTenuringIf: tenuringCriterion
+ 	
+ 	<doNotGenerate>
+ 	gc scavengingGCTenuringIf: tenuringCriterion!
- 	"Run the scavenger."
- 	<inline: false>
- 	self assert: remapBufferCount = 0.
- 	(self asserta: scavenger eden limit - freeStart > coInterpreter interpreterAllocationReserveBytes) ifFalse:
- 		[coInterpreter tab;
- 			printNum: scavenger eden limit - freeStart; space;
- 			printNum: coInterpreter interpreterAllocationReserveBytes; space;
- 			printNum: coInterpreter interpreterAllocationReserveBytes - (scavenger eden limit - freeStart); cr].
- 	self checkMemoryMap.
- 	self checkFreeSpace: GCModeNewSpace.
- 	self runLeakCheckerFor: GCModeNewSpace.
- 
- 	coInterpreter
- 		preGCAction: GCModeNewSpace;
- 		"would prefer this to be in mapInterpreterOops, but
- 		 compatibility with ObjectMemory dictates it goes here."
- 		flushMethodCacheFrom: newSpaceStart to: oldSpaceStart.
- 	needGCFlag := false.
- 
- 	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
- 
- 	self doScavenge: tenuringCriterion.
- 
- 	statScavenges := statScavenges + 1.
- 	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
- 	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
- 	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
- 	statRootTableCount := scavenger rememberedSetSize.
- 
- 	scavenger logScavenge.
- 
- 	coInterpreter postGCAction: GCModeNewSpace.
- 
- 	self runLeakCheckerFor: GCModeNewSpace.
- 	self checkFreeSpace: GCModeNewSpace!

Item was added:
+ ----- Method: SpurMemoryManager>>statGCEndUsecs: (in category 'accessing') -----
+ statGCEndUsecs: anInteger
+ 	
+ 	statGCEndUsecs := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>statMarkCount: (in category 'accessing') -----
+ statMarkCount: anInteger
+ 	
+ 	statMarkCount := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>statRootTableCount: (in category 'accessing') -----
+ statRootTableCount: anInteger
+ 	
+ 	statRootTableCount := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>statSGCDeltaUsecs: (in category 'accessing') -----
+ statSGCDeltaUsecs: anInteger
+ 	
+ 	statSGCDeltaUsecs := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>statScavengeGCUsecs: (in category 'accessing') -----
+ statScavengeGCUsecs: anInteger
+ 	
+ 	statScavengeGCUsecs := anInteger!

Item was added:
+ ----- Method: SpurMemoryManager>>statScavenges: (in category 'accessing') -----
+ statScavenges: anInteger
+ 	
+ 	statScavenges := anInteger!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofObjStack:withValue: (in category 'object access') -----
  storePointer: fieldIndex ofObjStack: objStackPage withValue: thang
  	self assert: (self formatOf: objStackPage) = self wordIndexableFormat.
  	self cCode: ''
  		inSmalltalk:
  			[fieldIndex caseOf: {
  				[ObjStackTopx]		->	[self assert: (thang between: 0 and: ObjStackLimit)].
+ 				[ObjStackMyx]		->	[self assert: (thang between: MarkStackRootIndex and: EphemeronStackRootIndex)].
- 				[ObjStackMyx]		->	[self assert: (thang between: MarkStackRootIndex and: MournQueueRootIndex)].
  				[ObjStackFreex]	->	[self assert: (thang = 0
  														or: [(self addressCouldBeObj: thang)
  															and: [(self numSlotsOfAny: thang) = ObjStackPageSlots
  															and: [(self formatOf: thang) = self wordIndexableFormat]]])].
  				[ObjStackNextx]	->	[self assert: (thang = 0
  														or: [(self addressCouldBeObj: thang)
  															and: [(self numSlotsOfAny: thang) = ObjStackPageSlots
  															and: [(self formatOf: thang) = self wordIndexableFormat]]])]. }
  				otherwise: []].
  	^self
  		longAt: objStackPage + self baseHeaderSize + (fieldIndex << self shiftForWord)
  		put: thang!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofObject:withValue: (in category 'object access') -----
  storePointer: fieldIndex ofObject: objOop withValue: valuePointer
  	"Note must check here for stores of young objects into old ones."
+ 	<inline: true>
+ 	
  	self assert: (self isForwarded: objOop) not.
  
  	(self isOldObject: objOop) ifTrue: "most stores into young objects"
  		[(self isYoung: valuePointer) ifTrue:
  			[self possibleRootStoreInto: objOop]].
  
+ 	self
- 	^self
  		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
+ 		put: valuePointer.
+ 		
+ 	self marker writeBarrierFor: objOop at: fieldIndex with: valuePointer.
+ 	
+ 	^ valuePointer!
- 		put: valuePointer!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointerImmutabilityCheck:ofObject:withValue: (in category 'object access') -----
  storePointerImmutabilityCheck: fieldIndex ofObject: objOop withValue: valuePointer
  	"Note must check here for stores of young objects into old ones."
  	<inline: true> "Must be inlined for the normal send in cannotAssign:to:withIndex:"
  
  	self cppIf: IMMUTABILITY ifTrue: 
  		[self deny: (self isImmediate: objOop).
  		 (self isImmutable: objOop) ifTrue: 
  			[^coInterpreter cannotAssign: valuePointer to: objOop withIndex: fieldIndex]].
  
+ 	self storePointer: fieldIndex ofObject: objOop withValue: valuePointer.
+ 	
+ 	self marker writeBarrierFor: objOop at: fieldIndex with: valuePointer!
- 	self storePointer: fieldIndex ofObject: objOop withValue: valuePointer!

Item was removed:
- ----- 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.
- 	 We do require traceImmediatelySlotLimit to be < numSlotsMask."
- 	^64!

Item was added:
+ ----- Method: SpurMemoryManager>>unscannedEphemerons (in category 'accessing') -----
+ unscannedEphemerons
+ 	<cmacro: '() GIV(unscannedEphemerons)'>
+ 	^ unscannedEphemerons!

Item was changed:
  ----- Method: SpurMemoryManager>>updateRootOfObjStackAt:with: (in category 'obj stacks') -----
  updateRootOfObjStackAt: objStackRootIndex with: newRootPage
  	self storePointer: objStackRootIndex
  		ofObject: hiddenRootsObj
  		withValue: newRootPage.
  	objStackRootIndex caseOf: {
  		[MarkStackRootIndex]		->	[markStack := newRootPage].
  		[WeaklingStackRootIndex]	->	[weaklingStack := newRootPage].
+ 		[MournQueueRootIndex]	->	[mournQueue := newRootPage].
+ 		[EphemeronStackRootIndex] -> [ephemeronStack := newRootPage] }.
- 		[MournQueueRootIndex]	->	[mournQueue := newRootPage] }.
  	^newRootPage!

Item was changed:
  ----- Method: SpurMemoryManager>>validObjStacks (in category 'obj stacks') -----
  validObjStacks
  	^(markStack = nilObj or: [self isValidObjStack: markStack])
  	  and: [(weaklingStack = nilObj or: [self isValidObjStack: weaklingStack])
+ 	  and: [(mournQueue = nilObj or: [self isValidObjStack: mournQueue])
+ 	  and: [ephemeronStack = nilObj or: [self isValidObjStack: ephemeronStack]]]]!
- 	  and: [mournQueue = nilObj or: [self isValidObjStack: mournQueue]]]!

Item was added:
+ SharedPool subclass: #SpurObjStackConstants
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'ObjStackFixedSlots ObjStackFreex ObjStackNextx ObjStackPageSlots ObjStackTopx'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!

Item was changed:
  SpurCompactor subclass: #SpurPlanningCompactor
  	instanceVariableNames: 'anomaly biasForGC firstFieldOfRememberedSet firstFreeObject firstMobileObject lastMobileObject mobileStart objectAfterLastMobileObject savedFirstFieldsSpace savedFirstFieldsSpaceNotInOldSpace'
  	classVariableNames: ''
  	poolDictionaries: 'VMBytecodeConstants'
+ 	category: 'VMMaker-SpurGarbageCollector'!
- 	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurPlanningCompactor commentStamp: '' prior: 0!
- !SpurPlanningCompactor commentStamp: 'eem 6/11/2018 12:43' prior: 0!
  SpurPlanningCompactor implements the classic planning compaction algorithm for Spur.  It uses the fact that there is room for a forwarding pointer in all objects to store the eventual position of an object in the first field.  It therefore first locates a large free chunk, or eden or a memory segment, to use as the savedFirstFieldsSpace, which it uses to store the first fields of objects that will be compacted.  It then makes at least three passes through the heap.
  
  The first pass plans where live movable objects will go, copying their first field to the next slot in savedFirstFieldsSpace, and setting their forwarding pointer to point to their eventual location (see planCompactSavingForwarders).  The second pass updates all pointers in live pointer objects to point to objects' final destinations, including the fields in savedFirstFieldsSpace (see updatePointers and updatePointersInMobileObjects).  The third pass moves objects to their final positions, unmarking objects, and restoring saved first fields as it does so (see copyAndUnmark: and copyAndUnmarkMobileObjects).  If the forwarding fields of live objects in the to-be-moved portion of the entire heap won't fit in savedFirstFieldsSpace, then additional passes can be made until the entire heap has been compacted.  When snapshotting multiple passes are made, but when doing a normal GC only one pass is made.
  
  Each pass uses a three finger algorithm, a simple extension of the classic two finger algorithm with an extra finger used to identify the lowest pinned object between the to and from fingers.  Objects are moved down, starting at the first free object or chunk, provided that they fit below the lowest pinned object above the to finger.  When an object won't fit the to finger is moved above the pinned object and the third finger is reset to the next pinned object below the from finger, if any.
  
  Instance Variables
  	anomaly							<Oop>
  	biasForGC							<Boolean>
  	firstFieldOfRememberedSet			<Oop>
  	firstFreeObject						<Oop>
  	firstMobileObject					<Oop>
  	lastMobileObject					<Oop>
  	mobileStart							<Integer address>
  	objectAfterLastMobileObject		<Oop|nil>
  	savedFirstFieldsSpace				<SpurContiguousObjStack>
  	savedFirstFieldsSpaceWasAllocated	<Boolean>
  
  anomaly
  	- if any bogus object is detected by asserts, etc, it is stored in anomaly
  
  biasForGC
  	- true if compacting for GC, in which case do only one pass, or false if compacting for snapshot, in which case do as many passes as necessary to compact the entire heap.
  
  firstFieldOfRememberedSet
  	- the saved first field of the rememberedSet.  The rememberedSet must be relocated specially because it is not a pointer object.  And hence the first field needs to be extracted for proper relocation.
  
  firstFreeObject
  	- the first free object in a compaction pass.
  
  firstMobileObject
  	- the first mobile object in a compaction.  Unpinned objects from the firstMobileObject through to the lastMobileObject are implicitly forwarded.
  
  lastMobileObject
  	- the last mobile object in a compaction.  Unpinned objects from the firstMobileObject through to the lastMobileObject are implicitly forwarded.
  
  mobileStart
  	- the address of the first byte in firstFreeObject
  
  objectAfterLastMobileObject
  	- the object following the last object that can be moved, used when more than one pass is needed.
  
  savedFirstFieldsSpace
  	- the space holding the saved first fields, each overwritten by a forwarding pointer, for the objects from firstMobileObject through to lastMobileObject.
  
  savedFirstFieldsSpaceWasAllocated
  	- if true, the memory for savedFirstFieldsSpace was obtained via a call of sqAllocateMemorySegmentOfSize:Above:AllocatedSizeInto:!

Item was changed:
  SpurSweeper subclass: #SpurSelectiveCompactor
  	instanceVariableNames: 'segmentToFill lastLilliputianChunk'
  	classVariableNames: 'MaxOccupationForCompaction'
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!
- 	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurSelectiveCompactor commentStamp: '' prior: 0!
- !SpurSelectiveCompactor commentStamp: 'cb 10/7/2018 19:54' prior: 0!
  SpurSelectiveCompactor compacts memory by selecting the memory segments with the most free space and compacting only those, to limit fragmentation while being really quick to perform. The algorithm is fast mostly because it does not update pointers: they are updated lazily during the next marking phase, so there is no need to read the fields of objects in other memory segments that the one compacted.
  
  The algorithm works as follow. First, a global sweep pass iterates over the memory linearly, changing unmarked objects to free chunks and concatenating free chunks. During the global sweep phase, the segments of the heap are analysed to determine the percentage of occupation. Second, the least occupied segments are compacted by copying the remaining live objects into an entirely free segment, called regionToFill (we detail later in the paragraph where regionToFill comes from), changing their values to forwarding objects and marking the free chunks as unavailable (removed from free list and marked as data objects). Third, the next marking phase removes all forwarders. Fourth, at the beginning of the next compaction phase the compacted segments from the previous GC can be entirely marked as free space (No need to check anything inside, there were only forwarders and trash data). One of the compacted segment is then selected as the segmentToFill, others are just marked as free chunks.
  
  
  The compaction is effectively partial, compacting only the most critical segments of the heap to limit fragmentation. Compaction time is crazy low, since a low number of objects are moved and pointer updated is lazily done during the next marking phase, while still preventing memory fragmentation.
  
  Now this works well when biasForGC is true, but when performing a snapshot, the compactor is just total crap (we need to figure out a solution).
  
  segmentToFill <SegInfo> the segment that will be filled through the copying algorithm
  lastLilliputianChunk <Oop to FreeChunk> This is used as a performance trick for lilliputian free chunks. See below.
  
  Segment abuse:
  The swizzle field of segInfo is abused by using the low 8 bits for occupation and the 9th bit as isBeingCompacted bit.
  
  Performance trick for lilliputian chunks:
  Specific free chunks (called lilliputian, see isLilliputianSize:) are managed using a single linked list instead of a double linked list since there's not enough room in the free chunk for the back pointer. During the sweep phase this is not a problem since we're rebuilding the free chunk structure, but during selective compaction we're detaching free chunks from the free chunk structure and that can be horribly slow (10 seconds sometimes at 20Gb heap due to many iteration over the single linked list). To work around this problem, the sweep phase use lastLilliputianChunk variable to sort the lilliputian free chunk single linked list in ascending address order (See interceptAddFreeChunkWithBytes:at:). During the selective compation phase, the same variable is re-used to iterate at most once over the single linked list while detaching lilliputian chunks (See incrementalUnlinkSmallChunk:). In addition, each segment is annotated during the sweep phase with the last lilliputian chunk it
  holds. Hence, during the compaction phase, the linked list is iterated but the iteration can jump to the last chunk of the previous segment to compact.!

Item was added:
+ SpurGarbageCollector subclass: #SpurStopTheWorldGarbageCollector
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector class>>classesForTranslation (in category 'as yet unclassified') -----
+ classesForTranslation
+ 
+ 	^ {self . SpurGarbageCollector . SpurCompactor . SpurGenerationScavenger . SpurAllAtOnceMarker . SpurPlanningCompactor}!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector class>>compactorClass (in category 'as yet unclassified') -----
+ compactorClass
+ 
+ 	^ SpurPlanningCompactor!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector class>>markerClass (in category 'as yet unclassified') -----
+ markerClass
+ 
+ 	^ SpurAllAtOnceMarker!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector class>>sourceSortingKey (in category 'as yet unclassified') -----
+ sourceSortingKey
+ 	"To keep methods in the same order while refactoring..."
+ 	^SpurMemoryManager name!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector>>fullGC (in category 'as yet unclassified') -----
+ fullGC
+ 	"Perform a full eager compacting GC.  Answer the size of the largest free chunk."
+ 	<returnTypeC: #usqLong>
+ 	<inline: #never> "for profiling"
+ 	
+ 	manager needGCFlag: 0.
+ 	manager gcStartUsecs: coInterpreter ioUTCMicrosecondsNow.
+ 	manager statMarkCount: 0.
+ 	coInterpreter preGCAction: GCModeFull.
+ 	self globalGarbageCollect.
+ 	coInterpreter postGCAction: GCModeFull.
+ 	manager statGCEndUsecs: coInterpreter ioUTCMicrosecondsNow.
+ 	manager updateFullGCStats.
+ 	^(manager freeLists at: 0) ~= 0
+ 		ifTrue: [self bytesInBody: manager findLargestFreeChunk]
+ 		ifFalse: [0]!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector>>globalGarbageCollect (in category 'as yet unclassified') -----
+ globalGarbageCollect
+ 	<inline: true> "inline into fullGC"
+ 	
+ 	manager preGlobalGCActions.
+ 	
+ 	self assert: self validObjStacks.
+ 	self assert: (self isEmptyObjStack: manager markStack).
+ 	self assert: (self isEmptyObjStack: manager weaklingStack).
+ 
+ 	"Mark objects /before/ scavenging, to empty the rememberedTable of unmarked roots."
+ 	marker markObjects: true.
+ 	manager gcMarkEndUsecs: coInterpreter ioUTCMicrosecondsNow.
+ 	
+ 	scavenger forgetUnmarkedRememberedObjects.
+ 
+ 	coInterpreter setGCMode: GCModeNewSpace.
+ 	self doScavenge: MarkOnTenure.
+ 	coInterpreter setGCMode: GCModeFull.
+ 
+ 	"Mid-way the leak check must be more lenient.  Unmarked classes will have been
+ 	 expunged from the table, but unmarked instances will not yet have been reclaimed."
+ 	manager runLeakCheckerFor: GCModeFull
+ 		excludeUnmarkedObjs: true
+ 		classIndicesShouldBeValid: true.
+ 
+ 	manager compactionStartUsecs: coInterpreter ioUTCMicrosecondsNow.
+ 	manager segmentManager prepareForGlobalSweep. "for notePinned:"
+ 	compactor compact.
+ 	manager attemptToShrink.
+ 	manager setHeapSizeAtPreviousGC.
+ 
+ 	self assert: manager validObjStacks.
+ 	self assert: (manager isEmptyObjStack: manager markStack).
+ 	self assert: (manager isEmptyObjStack: manager weaklingStack).
+ 	self assert: manager allObjectsUnmarked.
+ 	manager runLeakCheckerFor: GCModeFull!

Item was added:
+ ----- Method: SpurStopTheWorldGarbageCollector>>incrementalCollect (in category 'as yet unclassified') -----
+ incrementalCollect
+ 	"not supported in a stop the world GC -> no op"
+ 	
+ 	<doNotGenerate>!

Item was changed:
  SpurCompactor subclass: #SpurSweeper
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurGarbageCollector'!
- 	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurSweeper commentStamp: '' prior: 0!
- !SpurSweeper commentStamp: 'cb 4/27/2018 09:43' prior: 0!
  SpurSweeper is a sweep-only algorithm, setting the compactor to SpurSweeper effectively changes the fullGC to a mark-sweep non-moving algorithm. 
  
  SpurSweeper is a reference implementation if one wants to evaluate GC performance and compare it to a Mark-Sweep. It's also the only non-moving GC available right now which can be convenient for some experiments. One of the main reason why it was implemented is because advanced compaction algorithm includes a sweep phase (See SelectiveCompactor for example) and SpurSweeper allows to debug the sweep phase separatedly.
  !

Item was added:
+ ----- Method: StackInterpreter>>incremenalMarkAndTraceTraceLog (in category 'object memory support') -----
+ incremenalMarkAndTraceTraceLog
+ 	"This is a no-op in the StackVM"!

Item was added:
+ ----- Method: StackInterpreter>>incrementalMarkAndTraceInterpreterOops (in category 'object memory support') -----
+ incrementalMarkAndTraceInterpreterOops
+ 	"Mark and trace all oops in the interpreter's state."
+ 	"Assume: All traced variables contain valid oops.
+ 	 N.B. Don't trace messageSelector and lkupClass; these are ephemeral, live
+ 	 only during message lookup and because createActualMessageTo will not
+ 	 cause a GC these cannot change during message lookup."
+ 	| oop |
+ 	"Must mark stack pages first to initialize the per-page trace
+ 	 flags for full garbage collect before any subsequent tracing."
+ 	self incrementalMarkAndTraceStackPages.
+ 	self incrementalMarkAndTraceTraceLog.
+ 	self incrementalMarkAndTracePrimTraceLog.
+ 	objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: objectMemory specialObjectsOop. "also covers nilObj, trueObj, falseObj, and compact classes"
+ 	(objectMemory isImmediate: newMethod) ifFalse:
+ 		[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: newMethod].
+ 	self incrementalTraceProfileState.
+ 	tempOop = 0 ifFalse: [objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: tempOop].
+ 	tempOop2 = 0 ifFalse: [objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: tempOop2].
+ 
+ 	"V3 memory manager support"
+ 	1 to: objectMemory remapBufferCount do:
+ 		[:i | 
+ 		oop := objectMemory remapBuffer at: i.
+ 		(objectMemory isImmediate: oop) ifFalse: [objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: oop]]!

Item was added:
+ ----- Method: StackInterpreter>>incrementalMarkAndTracePrimTraceLog (in category 'object memory support') -----
+ incrementalMarkAndTracePrimTraceLog
+ 	"This is a no-op in the StackVM"!

Item was added:
+ ----- Method: StackInterpreter>>incrementalMarkAndTraceStackPage: (in category 'object memory support') -----
+ incrementalMarkAndTraceStackPage: thePage
+ 	| theSP theFP frameRcvrOffset callerFP oop |
+ 	<var: #thePage type: #'StackPage *'>
+ 	<var: #theSP type: #'char *'>
+ 	<var: #theFP type: #'char *'>
+ 	<var: #frameRcvrOffset type: #'char *'>
+ 	<var: #callerFP type: #'char *'>
+ 	<inline: false>
+ 
+ 	self assert: (stackPages isFree: thePage) not.
+ 	self assert: (self ifCurrentStackPageHasValidHeadPointers: thePage).
+ 	thePage trace: StackPageTraced.
+ 
+ 	theSP := thePage headSP.
+ 	theFP := thePage headFP.
+ 	"Skip the instruction pointer on top of stack of inactive pages."
+ 	thePage = stackPage ifFalse:
+ 		[theSP := theSP + objectMemory wordSize].
+ 	[frameRcvrOffset := self frameReceiverLocation: theFP.
+ 	 [theSP <= frameRcvrOffset] whileTrue:
+ 		[oop := stackPages longAt: theSP.
+ 		 (objectMemory isOopForwarded: oop) ifTrue:
+ 			[oop := objectMemory followForwarded: oop.
+ 			 stackPages longAt: theSP put: oop].
+ 		 (objectMemory isImmediate: oop) ifFalse:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: oop].
+ 		 theSP := theSP + objectMemory wordSize].
+ 	(self frameHasContext: theFP) ifTrue:
+ 		[self assert: (objectMemory isContext: (self frameContext: theFP)).
+ 		 objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: (self frameContext: theFP)].
+ 	objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: (self iframeMethod: theFP).
+ 	(callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
+ 		[theSP := theFP + FoxCallerSavedIP + objectMemory wordSize.
+ 		 theFP := callerFP].
+ 	theSP := theFP + FoxCallerSavedIP. "caller ip is frameCallerContext in a base frame"
+ 	[theSP <= thePage baseAddress] whileTrue:
+ 		[oop := stackPages longAt: theSP.
+ 		 (objectMemory isOopForwarded: oop) ifTrue:
+ 			[oop := objectMemory followForwarded: oop.
+ 			 stackPages longAt: theSP put: oop].
+ 		 (objectMemory isImmediate: oop) ifFalse:
+ 			[objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: oop].
+ 		 theSP := theSP + objectMemory wordSize]!

Item was added:
+ ----- Method: StackInterpreter>>incrementalMarkAndTraceStackPages (in category 'object memory support') -----
+ incrementalMarkAndTraceStackPages
+ 	"GC of pages.  Throwing away all stack pages on full GC is simple but dangerous
+ 	 because it causes us to allocate lots of contexts immediately before a GC.
+ 	 Reclaiming pages whose top context is not referenced is poor because it would
+ 	 take N incrementalGCs to reclaim N unused pages.  Only the page whose top
+ 	 context is not referred to by the bottom context of any other page would be
+ 	 reclaimed.  Not until the next GC would the page whose top contect is the
+ 	 previously reclaimed page's base frame's bottom context be reclaimed.
+ 
+ 	 Better is to not mark stack pages until their contexts are encountered.  We can
+ 	 eagerly trace the active page and the page reachable from its bottom context
+ 	 if any, and so on.  Other pages can be marked when we encounter a married
+ 	 context."
+ 	| thePage |
+ 	<inline: false>
+ 	0 to: numStackPages - 1 do:
+ 			[:i|
+ 			thePage := stackPages stackPageAt: i.
+ 			(stackPages isFree: thePage) ifFalse:
+ 				[self incrementalMarkAndTraceStackPage: thePage]].
+ 		^nil!

Item was added:
+ ----- Method: StackInterpreter>>incrementalMarkAndTraceTraceLog (in category 'object memory support') -----
+ incrementalMarkAndTraceTraceLog
+ 	"This is a no-op in the StackVM"!

Item was added:
+ ----- Method: StackInterpreter>>incrementalTraceProfileState (in category 'object memory support') -----
+ incrementalTraceProfileState
+ 	objectMemory hasSpurMemoryManagerAPI ifTrue:
+ 		[self followForwardingPointersInProfileState].
+ 	objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: profileProcess.
+ 	objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: profileMethod.
+ 	objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: profileSemaphore.
+ 
+ 	self cppIf: #LRPCheck
+ 		ifTrue:
+ 			["The longRunningPrimitiveCheckMethod (LRPCM) is sampled in an interrupt.  Be very careful with it.
+ 			  If longRunningPrimitiveCheckSequenceNumber (LRPCSN) = statCheckForEvents then LRPCM has
+ 			  been recenty sampled, but it must be newMethod and we don't need to trace it twice.  If LRPCSN
+ 			  ~= statCheckForEvents then LRPCM must be some extant object and needs to be traced."
+ 			self sqLowLevelMFence.
+ 			(longRunningPrimitiveCheckMethod ~= nil
+ 			 and: [longRunningPrimitiveCheckSequenceNumber ~= statCheckForEvents]) ifTrue:
+ 				[(objectMemory isForwarded: longRunningPrimitiveCheckMethod) ifTrue:
+ 					[longRunningPrimitiveCheckMethod := objectMemory followForwarded: longRunningPrimitiveCheckMethod].
+ 			objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: longRunningPrimitiveCheckMethod].
+ 			longRunningPrimitiveCheckSemaphore ~= nil ifTrue:
+ 				[(objectMemory isForwarded: longRunningPrimitiveCheckSemaphore) ifTrue:
+ 					[longRunningPrimitiveCheckSemaphore := objectMemory followForwarded: longRunningPrimitiveCheckSemaphore].
+ 				 objectMemory marker pushOnMarkingStackAndMakeGreyIfNecessary: longRunningPrimitiveCheckSemaphore]]!

Item was changed:
  ----- Method: TMethod>>inlineFunctionCall:in: (in category 'inlining') -----
  inlineFunctionCall: aSendNode in: aCodeGen
  	"Answer the body of the called function, substituting the actual
  	 parameters for the formal argument variables in the method body.
  	 Assume caller has established that:
  		1. the method arguments are all substitutable nodes, and
  		2. the method to be inlined contains no additional embedded returns."
  
  	| sel meth doNotRename argsForInlining substitutionDict |
  	aCodeGen maybeBreakForInlineOf: aSendNode in: self.
  	sel := aSendNode selector.
  	meth := (aCodeGen methodNamed: sel) copy.
  	meth ifNil:
  		[^self inlineBuiltin: aSendNode in: aCodeGen].
  	doNotRename := Set withAll: args.
  	argsForInlining := aSendNode argumentsForInliningCodeGenerator: aCodeGen.
+ 	[meth args with: argsForInlining do:
- 	meth args with: argsForInlining do:
  		[ :argName :exprNode |
  		exprNode isLeaf ifTrue:
+ 			[doNotRename add: argName]]]
+ 		on: Error
+ 		do: [:ex | ex messageText = 'Other collection must be the same size'
+ 						ifTrue: [ | errorMessage |
+ 							errorMessage := 'In ' , self definingClass name, '>>' , self  selector.
+ 							errorMessage := errorMessage , ' for method ' , meth definingClass name, '>>' , meth  selector.
+ 							errorMessage := errorMessage , ' following args where expected {' , (argsForInlining joinSeparatedBy: ', ') , '}'.
+ 							errorMessage := errorMessage , ' but got {' , (meth args joinSeparatedBy: ', ') , '}'.
+ 							"the errorMessage is probably extremenly long and not that easy to read in the header of the Debugger
+ 							 window. => print it on the transcript for better readability (as multiline strings in window titles seem 
+ 							not to be supported :( "
+ 							Transcript showln: errorMessage.
+ 							
+ 							self error: errorMessage]
+ 						ifFalse: [ex signal]].
- 			[doNotRename add: argName]].
  	(meth statements size = 2
  	and: [meth statements first isSend
  	and: [meth statements first selector == #flag:]]) ifTrue:
  		[meth statements removeFirst].
  	meth renameVarsForInliningInto: self except: doNotRename in: aCodeGen.
  	meth renameLabelsForInliningInto: self.
  	self addVarsDeclarationsAndLabelsOf: meth except: doNotRename.
  	substitutionDict := Dictionary new: meth args size * 2.
  	meth args with: argsForInlining do:
  		[ :argName :exprNode |
  		(exprNode isVariable and: [exprNode name = argName]) ifFalse:
  			[substitutionDict at: argName put: exprNode].
  		(doNotRename includes: argName) ifFalse:
  			[locals remove: argName]].
  	meth parseTree bindVariablesIn: substitutionDict.
  	^meth parseTree endsWithReturn
  		ifTrue: [meth parseTree copyWithoutReturn]
  		ifFalse: [meth parseTree]!

Item was changed:
  SharedPool subclass: #VMBasicConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM CloneOnGC CloneOnScavenge DisownVMForFFICall DisownVMForThreading DoAssertionChecks DoExpensiveAssertionChecks FastCPrimitiveAlignForFloatsFlag FastCPrimitiveFlag GCCheckFreeSpace GCCheckImageSegment GCCheckPrimCall GCCheckShorten GCModeBecome GCModeFull GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS MarkStackRecord NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrFFIException PrimErrFFIMarshallingError PrimErrGenericFailure PrimErrInappropriate PrimErrInternalError PrimErrLimitExceeded PrimErrNamedInternal PrimErrNeedCompaction PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrOperationFailed PrimErrUnin
 itialized PrimErrUnsupported PrimErrWritePastObject PrimNoErr PrimNumberHandlerMarker PrimNumberNoContextSwitchMarker PrimNumberUnwindMarker SPURVM STACKVM SistaVM TempVectReadBarrier VMBIGENDIAN'
- 	classVariableNames: 'BaseHeaderSize BytecodeSetHasExtensions BytesPerOop BytesPerWord COGMTVM COGVM CloneOnGC CloneOnScavenge DisownVMForFFICall DisownVMForThreading DoAssertionChecks DoExpensiveAssertionChecks FastCPrimitiveAlignForFloatsFlag FastCPrimitiveFlag GCCheckFreeSpace GCCheckImageSegment GCCheckPrimCall GCCheckShorten GCModeBecome GCModeFull GCModeIncremental GCModeNewSpace HashMultiplyConstant HashMultiplyMask IMMUTABILITY LowcodeVM MULTIPLEBYTECODESETS NewspeakVM PharoVM PrimErrBadArgument PrimErrBadIndex PrimErrBadMethod PrimErrBadNumArgs PrimErrBadReceiver PrimErrCallbackError PrimErrFFIException PrimErrFFIMarshallingError PrimErrGenericFailure PrimErrInappropriate PrimErrInternalError PrimErrLimitExceeded PrimErrNamedInternal PrimErrNeedCompaction PrimErrNoCMemory PrimErrNoMemory PrimErrNoModification PrimErrNotFound PrimErrOSError PrimErrObjectIsPinned PrimErrObjectMayMove PrimErrObjectMoved PrimErrObjectNotPinned PrimErrOperationFailed PrimErrUninitialized PrimEr
 rUnsupported PrimErrWritePastObject PrimNoErr PrimNumberHandlerMarker PrimNumberNoContextSwitchMarker PrimNumberUnwindMarker SPURVM STACKVM SistaVM TempVectReadBarrier VMBIGENDIAN'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!
  
  !VMBasicConstants commentStamp: '<historical>' prior: 0!
  I am a shared pool for basic constants upon which the VM as a whole depends.
  
  self ensureClassPool.
  self classPool declare: #BytesPerWord from: VMSqueakV3ObjectRepresentationConstants classPool.
  self classPool declare: #BaseHeaderSize from: VMSqueakV3ObjectRepresentationConstants classPool
  (ObjectMemory classPool keys select: [:k| k beginsWith: 'Byte']) do:
  	[:k| self classPool declare: k from: ObjectMemory classPool]!

Item was changed:
  ----- Method: VMClass class>>openSpurMultiWindowBrowser (in category 'utilities') -----
  openSpurMultiWindowBrowser
  	"Answer a new multi-window browser on the Spur classes, the Cog StackInterpreter classes, and the support classes"
  	"self openSpurMultiWindowBrowser"
  	| b |
  	b := Browser open.
+ 	#(	SpurIncrementalMarker SpurMemoryManager Spur32BitMemoryManager Spur64BitMemoryManager
- 	#(	SpurMemoryManager Spur32BitMemoryManager Spur64BitMemoryManager
  		SpurGenerationScavenger SpurSegmentManager
  		Spur32BitMMLESimulator SpurGenerationScavengerSimulator
  		InterpreterPrimitives StackInterpreter StackInterpreterPrimitives
  		VMStructType VMMaker CCodeGenerator TMethod)
  		do: [:className|
  			(Smalltalk classNamed: className) ifNotNil:
  				[:class| b selectCategoryForClass: class; selectClass: class]]
  		separatedBy:
  			[b multiWindowState addNewWindow].
  	b multiWindowState selectWindowIndex: 1!



More information about the Vm-dev mailing list