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

commits at source.squeak.org commits at source.squeak.org
Tue Jul 26 14:46:53 UTC 2022


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

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

Name: VMMaker.oscog.seperateMarking-WoC.3222
Author: WoC
Time: 26 July 2022, 4:46:39.622721 pm
UUID: d102a150-a9ed-4b32-b4be-f2e2d319383a
Ancestors: VMMaker.oscog.seperateMarking-WoC.3207, VMMaker.oscog-dtl.3221

introduce a new class (hierarchy) for garbage collection and put some (by far not all) gc methods from the SpurMemoryManager there

=============== Diff against VMMaker.oscog.seperateMarking-WoC.3207 ===============

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: 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 changed:
  SpurMarker subclass: #SpurAllAtOnceMarker
+ 	instanceVariableNames: ''
- 	instanceVariableNames: 'marking'
  	classVariableNames: ''
+ 	poolDictionaries: ''
- 	poolDictionaries: 'SpurObjStackConstants VMBasicConstants'
  	category: 'VMMaker-SpurMemoryManager'!

Item was removed:
- ----- Method: SpurAllAtOnceMarker>>initialize (in category 'instance initialization') -----
- initialize
- 
- 	marking := false!

Item was removed:
- ----- Method: SpurAllAtOnceMarker>>marking (in category 'marking') -----
- marking 
- 	<cmacro: '() GIV(marking)'>
- 	
- 	^ marking!

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

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

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

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

Item was added:
+ ----- Method: SpurGarbageCollector>>compactor (in category 'accessing') -----
+ compactor
+ 
+ 	^ 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>
+ 	self 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.
+ 	self resetAllocationAccountingAfterGC!

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>>manager (in category 'accessing') -----
+ manager
+ 
+ 	^ manager!

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

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

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

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: #SpurMarker
+ 	instanceVariableNames: 'manager coInterpreter marking'
- 	instanceVariableNames: 'manager coInterpreter'
  	classVariableNames: ''
+ 	poolDictionaries: 'SpurObjStackConstants VMBasicConstants'
- 	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!

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

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

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. SpurAllAtOnceMarker }, 
- 		self compactorClass classesForTranslation,
  		SpurNewSpaceSpace withAllSubclasses
  		
  	!

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: [#SpurStopTheWorldGarbageCollector])!

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>>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; yourself.
- 	compactor := self class compactorClass simulatorClass new manager: self; yourself
  	!

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]!

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

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>>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."
- 	marker 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 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.
  	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; 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>>marker (in category 'accessing') -----
+ marker
+ 
+ 	^ marker!

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

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>>pastSpaceStart: (in category 'accessing') -----
+ pastSpaceStart: anInteger
+ 
+ 	pastSpaceStart := anInteger!

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

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 added:
+ SpurGarbageCollector subclass: #SpurStopTheWorldGarbageCollector
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!

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

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>
+ 	^ self shouldNotImplement!



More information about the Vm-dev mailing list