[Vm-dev] VM Maker: VMMaker.oscog-cb.2384.mcz

commits at source.squeak.org commits at source.squeak.org
Thu May 17 09:46:17 UTC 2018


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2384.mcz

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

Name: VMMaker.oscog-cb.2384
Author: cb
Time: 17 May 2018, 11:45:53.30252 am
UUID: f90e4f68-f627-4366-bfb0-f37649aa4822
Ancestors: VMMaker.oscog-VB.2383

Compactor clean-ups, we now only have:
- Pig: first spur compactor
- Planning: current production compactor
- Sweeper: Sweep-only algorithm
- Selective: Sweep + partial compaction of the heap.
All of them are working (at least they survive basic GC stress tests)

=============== Diff against VMMaker.oscog-VB.2383 ===============

Item was removed:
- SpurSweeper subclass: #SpurAnalysingSweeperCompactor
- 	instanceVariableNames: 'segmentToFill'
- 	classVariableNames: 'MaxOccupationForCompaction'
- 	poolDictionaries: ''
- 	category: 'VMMaker-SpurMemoryManager'!
- 
- !SpurAnalysingSweeperCompactor commentStamp: 'cb 4/27/2018 10:48' prior: 0!
- Abstract class, in addition to SpurSweeper, while sweeping the heap I annotate segments with occupation rate. This is then used by compacting algorithms to compact only segments which are not used that much.!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor class>>declareCVarsIn: (in category 'translation') -----
- declareCVarsIn: aCCodeGenerator
- 	aCCodeGenerator var: 'segmentToFill' type: #'SpurSegmentInfo *'!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor class>>initialize (in category 'initialization') -----
- 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 := 16rA000. "Basically if segment is occupied by more than 60%, not worth compacting"!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>allocateSegmentToFill (in category 'segment to fill') -----
- allocateSegmentToFill
- 	| res |
- 	res := manager growOldSpaceByAtLeast: manager growHeadroom.
- 	res ifNil: [self error: 'not enough memory for selective compaction'].!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>assertNoSegmentBeingCompacted (in category 'compaction') -----
- 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 removed:
- ----- Method: SpurAnalysingSweeperCompactor>>compact (in category 'api') -----
- compact
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>compactSegment:freeStart: (in category 'compaction') -----
- compactSegment: segInfo freeStart: initialFreeStart
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	| currentEntity fillStart bytesToCopy numSlots bridge |
- 	fillStart := initialFreeStart.
- 	bridge := manager segmentManager bridgeFor: segInfo.
- 	currentEntity := manager objectStartingAt: segInfo segStart.
- 	[self oop: currentEntity isLessThan: bridge] whileTrue:
- 		[(manager isFreeObject: currentEntity)
- 			ifTrue: 
- 				["To avoid confusing too much Spur (especially the leak/free checks), we mark the free chunk as a word object."
- 				 manager detachFreeObject: currentEntity.
- 				 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. 
- 				 numSlots := manager numSlotsOfAny: currentEntity.
- 				 bytesToCopy := manager bytesInObject: currentEntity.
- 				 self assert: (manager objectBytesForSlots: numSlots) = (manager bytesInObject: currentEntity).
- 				 manager mem: fillStart asVoidPointer cp: (manager startOfObject: currentEntity) asVoidPointer y: bytesToCopy.
- 				 self assert: (manager baseHeader: (manager objectStartingAt: fillStart)) = (manager baseHeader: currentEntity).
- 				 self assert: (manager fetchPointer: numSlots - 1 ofObject: (manager objectStartingAt: fillStart)) = (manager fetchPointer: numSlots - 1 ofObject: currentEntity).
- 				 manager forward: currentEntity to: (manager objectStartingAt: fillStart).
- 				 fillStart := fillStart + (manager objectBytesForSlots: numSlots).
- 				 self assert: (manager isForwarded: currentEntity).
- 				 self assert: fillStart < (segmentToFill segLimit - manager bridgeSize)].
- 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
- 	self assert: currentEntity = bridge.
- 	^ fillStart!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>compactSegmentsToCompact (in category 'compaction') -----
- compactSegmentsToCompact
- 	"Forwards all objects in segments to compact and removes their freechunks"
- 	| segInfo fillStart |
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	fillStart := segmentToFill segStart.
- 	
- 	 "Removes initial free chunk in segment to fill... (Segment is entirely free)"
- 	manager detachFreeObject: (manager objectStartingAt: fillStart).
- 	
- 	 "Compact each segment to compact..."
- 	0 to: manager numSegments - 1 do:
- 		[:i| 
- 		 segInfo := self addressOf: (manager segmentManager segments at: i).
- 		(self isSegmentBeingCompacted: segInfo)
- 			ifTrue: [fillStart := self compactSegment: segInfo freeStart: fillStart ]].
- 		
- 	 "Final free chunk in segment to fill..."
- 	 manager 
- 		addFreeChunkWithBytes: segmentToFill segSize - manager bridgeSize + segmentToFill segStart - fillStart 
- 		at: fillStart.
- 	
- 	self postCompactionAction
- 	!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>computeSegmentsToCompact (in category 'compaction') -----
- computeSegmentsToCompact
- 	"Compute segments to compact: least occupied.
- 	 Answers true if at least 1 segment is being compacted."
- 	| 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].
- 	canStillClaim := segmentToFill segSize - manager bridgeSize.
- 	[aboutToClaimSegment ifNil: [^atLeastOneSegmentToCompact].
- 	 aboutToClaim := aboutToClaimSegment segSize - manager bridgeSize * ((self occupationOf: aboutToClaimSegment) + 1) // 16rFFFF. "+1 to round up, this is approx"
- 	 aboutToClaim < canStillClaim ] whileTrue: 
- 		[self markSegmentAsBeingCompacted: aboutToClaimSegment.
- 		 atLeastOneSegmentToCompact := true.
- 		 canStillClaim := canStillClaim - aboutToClaim.
- 		 aboutToClaimSegment := self findNextSegmentToCompact].
- 	^atLeastOneSegmentToCompact!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>findAndSetSegmentToFill (in category 'segment to fill') -----
- findAndSetSegmentToFill
- 	| segInfo firstEntity |
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	0 to: manager numSegments - 1 do:
- 		[:i| 
- 		 segInfo := self addressOf: (manager segmentManager segments at: i).
- 		 firstEntity := manager objectStartingAt: segInfo segStart.
- 		 ((manager isFreeObject: firstEntity) and: [(manager objectAfter: firstEntity limit: manager endOfMemory) = (manager segmentManager bridgeFor: segInfo)])
- 			ifTrue: [segmentToFill := segInfo. ^0]].
- 	!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>findNextSegmentToCompact (in category 'compaction') -----
- 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: [^nil].
- 	^ leastOccupiedSegment!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>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."
- 	self findAndSetSegmentToFill.
- 	segmentToFill ifNotNil: [^0].
- 	"No empty segment. We need to allocate a new one"
- 	self allocateSegmentToFill.
- 	"We don't know which segment it is that we've just allocated... So we look for it... This is a bit dumb."
- 	self findAndSetSegmentToFill.
- 	self assert: segmentToFill ~~ nil.
- 	!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>freeSegment: (in category 'segment access') -----
- freeSegment: segInfo
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	 manager addFreeChunkWithBytes: segInfo segSize - manager bridgeSize at: segInfo segStart.!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>globalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') -----
- globalSweepAndSegmentOccupationAnalysis
- 	self internalGlobalSweepAndSegmentOccupationAnalysis.
- 	manager checkFreeSpace: GCModeFull.
- 	manager unmarkSurvivingObjectsForCompact.!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>internalGlobalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') -----
- internalGlobalSweepAndSegmentOccupationAnalysis
- 	"Iterate over old space, free unmarked objects, annotate each segment with each occupation"
- 	| currentEntity nextBridge start segmentIndex currentUsed currentUnused |
- 	currentEntity := manager firstObject.
- 	nextBridge := manager segmentManager bridgeAt: 0.
- 	segmentIndex := currentUnused := currentUsed := 0.
- 	[self oop: currentEntity isLessThan: manager endOfMemory] whileTrue:
- 		[currentEntity = nextBridge
- 			ifTrue: 
- 				["End of segment, set occupation"
- 				  self 
- 					setOccupationAtIndex: segmentIndex
- 					used: currentUsed 
- 					unused: currentUnused.
- 				  currentUnused := currentUsed := 0.
- 				  segmentIndex := segmentIndex + 1.
- 				  self unmark: currentEntity.
- 				  nextBridge := manager segmentManager bridgeAt: segmentIndex]
- 			ifFalse: 
- 				["In-segment, sweep and compute occupation"
- 				 (self canUseAsFreeSpace: currentEntity) 
- 					ifTrue: 
- 						["bulkFreeChunkFrom: may change a 1 word header
- 						object to a double word header object"
- 						start := manager startOfObject: currentEntity.
- 						self bulkFreeChunkFrom: currentEntity.
- 						currentEntity := manager objectStartingAt: start.
- 						currentUnused := currentUnused + (manager numSlotsOfAny: currentEntity)]
- 					ifFalse: 
- 						[self unmark: currentEntity.
- 						 currentUsed := currentUsed + (manager numSlotsOfAny: currentEntity)]].
- 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
- 	"set last segment (last bridge = endOfMemory)"	
- 	self 
- 		setOccupationAtIndex: segmentIndex
- 		used: currentUsed 
- 		unused: currentUnused.!

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

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>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 removed:
- ----- Method: SpurAnalysingSweeperCompactor>>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 removed:
- ----- Method: SpurAnalysingSweeperCompactor>>postCompactionAction (in category 'compaction') -----
- postCompactionAction
- 	self postForwardingAction!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>postForwardingAction (in category 'compaction') -----
- postForwardingAction
- 	| 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.
- 	manager coInterpreter postBecomeAction: allFlags.
- 	manager postBecomeScanClassTable: allFlags.!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>postSwizzleAction (in category 'api') -----
- postSwizzleAction
- 	"Since the compact abuses the swizzle field of segment, it needs to be rest 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 removed:
- ----- Method: SpurAnalysingSweeperCompactor>>selectiveCompaction (in category 'compaction') -----
- selectiveCompaction
- 	"Figures out which segments to compact and compact them into segmentToFill"
- 	| atLeastOneSegmentToCompact |
- 	self assertNoSegmentBeingCompacted.
- 	atLeastOneSegmentToCompact := self computeSegmentsToCompact.
- 	"If no compaction we don't pay forwarding cost (stack scan, cache scan, etc.)
- 	 and we don't allocate segmentToFill if none available."
- 	atLeastOneSegmentToCompact 
- 		ifTrue:
- 			[self assert: segmentToFill ~~ nil.
- 		 	 self compactSegmentsToCompact].
- 	manager checkFreeSpace: GCModeFull.!

Item was removed:
- ----- Method: SpurAnalysingSweeperCompactor>>setOccupationAtIndex:used:unused: (in category 'segment access') -----
- 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).
- 	occupation := used * 16rFFFF // (used + unused).
- 	segInfo swizzle: occupation!

Item was changed:
+ SpurSweeper subclass: #SpurSelectiveCompactor
+ 	instanceVariableNames: 'segmentToFill'
+ 	classVariableNames: 'MaxOccupationForCompaction'
- SpurAnalysingSweeperCompactor subclass: #SpurSelectiveCompactor
- 	instanceVariableNames: ''
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurSelectiveCompactor commentStamp: 'cb 5/17/2018 11:43' prior: 0!
- !SpurSelectiveCompactor commentStamp: 'cb 4/27/2018 13:14' 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
  
- ------------------------
- 
  Segment abuse:
+ The swizzle field of segInfo is abused by using the low 8 bits for occupation and the 9th bit as isBeingCompacted bit.!
- The swizzle field of segInfo is abused by using the low 8 bits for occupation and the 9th bit as isBeingCompacted bit.
- 
- TODO: check it seems when memory is decreasing rapidly many empty segment are kept (14 and not 4 - Bug in totalFreeSpace?)
- !

Item was added:
+ ----- Method: SpurSelectiveCompactor class>>declareCVarsIn: (in category 'translation') -----
+ declareCVarsIn: aCCodeGenerator
+ 	aCCodeGenerator var: 'segmentToFill' type: #'SpurSegmentInfo *'!

Item was added:
+ ----- Method: SpurSelectiveCompactor class>>initialize (in category 'initialization') -----
+ 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 := 16rA000. "Basically if segment is occupied by more than 60%, not worth compacting"!

Item was removed:
- ----- Method: SpurSelectiveCompactor class>>simulatorClass (in category 'simulation') -----
- simulatorClass
- 	^SpurSelectiveCompactorSimulator!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>allocateSegmentToFill (in category 'segment to fill') -----
+ allocateSegmentToFill
+ 	| res |
+ 	res := manager growOldSpaceByAtLeast: manager growHeadroom.
+ 	res ifNil: [self error: 'not enough memory for selective compaction'].!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>assertNoSegmentBeingCompacted (in category 'compaction') -----
+ 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 changed:
  ----- Method: SpurSelectiveCompactor>>compact (in category 'api') -----
  compact
  	<inline: #never> "for profiling"
  	self freePastSegmentsAndSetSegmentToFill.
  	self globalSweepAndSegmentOccupationAnalysis.
  	self selectiveCompaction.
  	!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>compactSegment:freeStart: (in category 'compaction') -----
+ compactSegment: segInfo freeStart: initialFreeStart
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	| currentEntity fillStart bytesToCopy numSlots bridge |
+ 	fillStart := initialFreeStart.
+ 	bridge := manager segmentManager bridgeFor: segInfo.
+ 	currentEntity := manager objectStartingAt: segInfo segStart.
+ 	[self oop: currentEntity isLessThan: bridge] whileTrue:
+ 		[(manager isFreeObject: currentEntity)
+ 			ifTrue: 
+ 				["To avoid confusing too much Spur (especially the leak/free checks), we mark the free chunk as a word object."
+ 				 manager detachFreeObject: currentEntity.
+ 				 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. 
+ 				 numSlots := manager numSlotsOfAny: currentEntity.
+ 				 bytesToCopy := manager bytesInObject: currentEntity.
+ 				 self assert: (manager objectBytesForSlots: numSlots) = (manager bytesInObject: currentEntity).
+ 				 manager mem: fillStart asVoidPointer cp: (manager startOfObject: currentEntity) asVoidPointer y: bytesToCopy.
+ 				 self assert: (manager baseHeader: (manager objectStartingAt: fillStart)) = (manager baseHeader: currentEntity).
+ 				 self assert: (manager fetchPointer: numSlots - 1 ofObject: (manager objectStartingAt: fillStart)) = (manager fetchPointer: numSlots - 1 ofObject: currentEntity).
+ 				 manager forward: currentEntity to: (manager objectStartingAt: fillStart).
+ 				 fillStart := fillStart + (manager objectBytesForSlots: numSlots).
+ 				 self assert: (manager isForwarded: currentEntity).
+ 				 self assert: fillStart < (segmentToFill segLimit - manager bridgeSize)].
+ 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
+ 	self assert: currentEntity = bridge.
+ 	^ fillStart!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>compactSegmentsToCompact (in category 'compaction') -----
+ compactSegmentsToCompact
+ 	"Forwards all objects in segments to compact and removes their freechunks"
+ 	| segInfo fillStart |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	fillStart := segmentToFill segStart.
+ 	
+ 	 "Removes initial free chunk in segment to fill... (Segment is entirely free)"
+ 	manager detachFreeObject: (manager objectStartingAt: fillStart).
+ 	
+ 	 "Compact each segment to compact..."
+ 	0 to: manager numSegments - 1 do:
+ 		[:i| 
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		(self isSegmentBeingCompacted: segInfo)
+ 			ifTrue: [fillStart := self compactSegment: segInfo freeStart: fillStart ]].
+ 		
+ 	 "Final free chunk in segment to fill..."
+ 	 manager 
+ 		addFreeChunkWithBytes: segmentToFill segSize - manager bridgeSize + segmentToFill segStart - fillStart 
+ 		at: fillStart.
+ 	
+ 	self postCompactionAction
+ 	!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>computeSegmentsToCompact (in category 'compaction') -----
+ computeSegmentsToCompact
+ 	"Compute segments to compact: least occupied.
+ 	 Answers true if at least 1 segment is being compacted."
+ 	| 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].
+ 	canStillClaim := segmentToFill segSize - manager bridgeSize.
+ 	[aboutToClaimSegment ifNil: [^atLeastOneSegmentToCompact].
+ 	 aboutToClaim := aboutToClaimSegment segSize - manager bridgeSize * ((self occupationOf: aboutToClaimSegment) + 1) // 16rFFFF. "+1 to round up, this is approx"
+ 	 aboutToClaim < canStillClaim ] whileTrue: 
+ 		[self markSegmentAsBeingCompacted: aboutToClaimSegment.
+ 		 atLeastOneSegmentToCompact := true.
+ 		 canStillClaim := canStillClaim - aboutToClaim.
+ 		 aboutToClaimSegment := self findNextSegmentToCompact].
+ 	^atLeastOneSegmentToCompact!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>findAndSetSegmentToFill (in category 'segment to fill') -----
+ findAndSetSegmentToFill
+ 	| segInfo firstEntity |
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	0 to: manager numSegments - 1 do:
+ 		[:i| 
+ 		 segInfo := self addressOf: (manager segmentManager segments at: i).
+ 		 firstEntity := manager objectStartingAt: segInfo segStart.
+ 		 ((manager isFreeObject: firstEntity) and: [(manager objectAfter: firstEntity limit: manager endOfMemory) = (manager segmentManager bridgeFor: segInfo)])
+ 			ifTrue: [segmentToFill := segInfo. ^0]].
+ 	!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>findNextSegmentToCompact (in category 'compaction') -----
+ 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: [^nil].
+ 	^ leastOccupiedSegment!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>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."
+ 	self findAndSetSegmentToFill.
+ 	segmentToFill ifNotNil: [^0].
+ 	"No empty segment. We need to allocate a new one"
+ 	self allocateSegmentToFill.
+ 	"We don't know which segment it is that we've just allocated... So we look for it... This is a bit dumb."
+ 	self findAndSetSegmentToFill.
+ 	self assert: segmentToFill ~~ nil.
+ 	!

Item was changed:
+ ----- Method: SpurSelectiveCompactor>>freePastSegmentsAndSetSegmentToFill (in category 'segment access') -----
- ----- Method: SpurSelectiveCompactor>>freePastSegmentsAndSetSegmentToFill (in category 'freeing') -----
  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: 
  				[self freeSegment: segInfo.
  				 segmentToFill ifNil: [segmentToFill := segInfo]]]!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>freeSegment: (in category 'segment access') -----
+ freeSegment: segInfo
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	 manager addFreeChunkWithBytes: segInfo segSize - manager bridgeSize at: segInfo segStart.!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>globalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') -----
+ globalSweepAndSegmentOccupationAnalysis
+ 	self internalGlobalSweepAndSegmentOccupationAnalysis.
+ 	manager checkFreeSpace: GCModeFull.
+ 	manager unmarkSurvivingObjectsForCompact.!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>internalGlobalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') -----
+ internalGlobalSweepAndSegmentOccupationAnalysis
+ 	"Iterate over old space, free unmarked objects, annotate each segment with each occupation"
+ 	| currentEntity nextBridge start segmentIndex currentUsed currentUnused |
+ 	currentEntity := manager firstObject.
+ 	nextBridge := manager segmentManager bridgeAt: 0.
+ 	segmentIndex := currentUnused := currentUsed := 0.
+ 	[self oop: currentEntity isLessThan: manager endOfMemory] whileTrue:
+ 		[currentEntity = nextBridge
+ 			ifTrue: 
+ 				["End of segment, set occupation"
+ 				  self 
+ 					setOccupationAtIndex: segmentIndex
+ 					used: currentUsed 
+ 					unused: currentUnused.
+ 				  currentUnused := currentUsed := 0.
+ 				  segmentIndex := segmentIndex + 1.
+ 				  self unmark: currentEntity.
+ 				  nextBridge := manager segmentManager bridgeAt: segmentIndex]
+ 			ifFalse: 
+ 				["In-segment, sweep and compute occupation"
+ 				 (self canUseAsFreeSpace: currentEntity) 
+ 					ifTrue: 
+ 						["bulkFreeChunkFrom: may change a 1 word header
+ 						object to a double word header object"
+ 						start := manager startOfObject: currentEntity.
+ 						self bulkFreeChunkFrom: currentEntity.
+ 						currentEntity := manager objectStartingAt: start.
+ 						currentUnused := currentUnused + (manager numSlotsOfAny: currentEntity)]
+ 					ifFalse: 
+ 						[self unmark: currentEntity.
+ 						 currentUsed := currentUsed + (manager numSlotsOfAny: currentEntity)]].
+ 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
+ 	"set last segment (last bridge = endOfMemory)"	
+ 	self 
+ 		setOccupationAtIndex: segmentIndex
+ 		used: currentUsed 
+ 		unused: currentUnused.!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>isSegmentBeingCompacted: (in category 'segment access') -----
+ 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: SpurSelectiveCompactor>>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: SpurSelectiveCompactor>>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: SpurSelectiveCompactor>>postCompactionAction (in category 'compaction') -----
+ postCompactionAction
+ 	self postForwardingAction!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>postForwardingAction (in category 'compaction') -----
+ postForwardingAction
+ 	| 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.
+ 	manager coInterpreter postBecomeAction: allFlags.
+ 	manager postBecomeScanClassTable: allFlags.!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>postSwizzleAction (in category 'api') -----
+ postSwizzleAction
+ 	"Since the compact abuses the swizzle field of segment, it needs to be rest 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: SpurSelectiveCompactor>>selectiveCompaction (in category 'compaction') -----
+ selectiveCompaction
+ 	"Figures out which segments to compact and compact them into segmentToFill"
+ 	| atLeastOneSegmentToCompact |
+ 	self assertNoSegmentBeingCompacted.
+ 	atLeastOneSegmentToCompact := self computeSegmentsToCompact.
+ 	"If no compaction we don't pay forwarding cost (stack scan, cache scan, etc.)
+ 	 and we don't allocate segmentToFill if none available."
+ 	atLeastOneSegmentToCompact 
+ 		ifTrue:
+ 			[self assert: segmentToFill ~~ nil.
+ 		 	 self compactSegmentsToCompact].
+ 	manager checkFreeSpace: GCModeFull.!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>setOccupationAtIndex:used:unused: (in category 'segment access') -----
+ 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).
+ 	occupation := used * 16rFFFF // (used + unused).
+ 	segInfo swizzle: occupation!

Item was changed:
+ AnObsoleteSpurSelectiveCompactor subclass: #SpurSelectiveCompactorSimulator
- SpurSelectiveCompactor subclass: #SpurSelectiveCompactorSimulator
  	instanceVariableNames: ''
  	classVariableNames: 'Talking'
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was removed:
- SpurCompactor subclass: #SpurSlidingCompactor
- 	instanceVariableNames: 'compactedCopySpace'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-SpurMemoryManager'!
- 
- !SpurSlidingCompactor commentStamp: 'eem 12/17/2016 15:30' prior: 0!
- SpurSlidingCompactor compacts memory completely by sliding objects down in memory.  It does so by using a buffer (compactedCopySpace) to hold a copy of compacted objects in some region of the heap being compacted.  Starting at the first object above free space (up until a pinned object), objects are copied into CCS until it fills up, and as objects are copied, their originals are forwarded to the location they would occupy.  Once the CCS is full, or all of the heap has been copied to it, memory is scanned searching for oops in the range being compacted, and oops are updated to their actual positions.  Then the contents of the CCS are block copied into place.  The process repeats until all of the heap has been compacted.  This will leave one contiguous free chunk in the topmost occupied segment (ignoring pinned objects).  The number of passes made to follow forwarders is approximately the allocated size of the heap divided by the size of CCS; the larger CCS the more objects that can
  be compacted in one go (ignoring the effect of pinned objects).
- 
- Instance Variables
- 	coInterpreter:				<StackInterpreter>
- 	compactedCopySpace:		<SpurNewSpaceSpace>
- 	manager:					<SpurMemoryManager>
- 	scavenger:					<SpurGenerationScavenger>
- 
- compactedCopySpace
- 	- a large contiguous region of memory used to copy objects into during compaction.  The compactor may try and allocate a segment, use a large free chunk or use eden for this memory.!

Item was removed:
- ----- Method: SpurSlidingCompactor>>biasForGC (in category 'compaction - api') -----
- biasForGC
- 	<inline: true>!

Item was removed:
- ----- Method: SpurSlidingCompactor>>biasForSnapshot (in category 'compaction - api') -----
- biasForSnapshot
- 	<inline: true>!

Item was removed:
- ----- Method: SpurSlidingCompactor>>compact (in category 'compaction - api') -----
- compact
- 	"Sweep all of old space, sliding unpinned marked objects down over free and unmarked objects.
- 	 Let the segmentManager mark which segments contain pinned objects via notePinned:.
- 		destination: nil or the start of a run of free and/or unmarked objects
- 		pinnedObject: nil or the pinned object found in the sweep around which unpinned objects must be copied."
- 	| destination pinnedObject |
- 	<inline: #never> "for profiling"
- 	manager checkFreeSpace: GCModeFull.
- 	manager resetFreeListHeads.
- 	self selectCompactedCopySpace.
- 	destination := pinnedObject := nil.
- 	manager allOldSpaceEntitiesFrom: manager firstObject do:
- 		[:o|
- 		 (manager isMarked: o)
- 			ifTrue: "forwarders should have been followed in markAndTrace:"
- 				[self assert: (manager isForwarded: o) not.
- 				 destination
- 					ifNil:
- 						[manager setIsMarkedOf: o to: false.
- 						 (manager isPinned: o) ifTrue:
- 							[manager segmentManager notePinned: o]]
- 					ifNotNil:
- 						[(manager isPinned: o)
- 							ifTrue:
- 								[manager segmentManager notePinned: o.
- 								 destination := self copyObjectsInCompactedCopySpaceTo: destination followingUpTo: o.
- 								 (manager startOfObject: o) - destination > manager allocationUnit
- 									ifTrue: "Possible to move objects below the pinnedObject"
- 										[pinnedObject
- 											ifNil: []
- 											ifNotNil: [].
- 										 pinnedObject := o]
- 									ifFalse: "Impossible; ensure there's a free chunk if necessary."
- 										[pinnedObject
- 											ifNil: []
- 											ifNotNil: [].
- 										 destination := nil]] "WAIT; NEED AT LEAST 2 WORDS FOR FREE CHUNK"
- 							ifFalse:
- 								[manager setIsMarkedOf: o to: false.
- 								 (self fitsInCompactedCopySpace: o) ifFalse:
- 									[destination := self copyObjectsInCompactedCopySpaceTo: destination followingUpTo: o].
- 								  (self fitsInCompactedCopySpace: o)
- 									ifFalse: [destination := self slideHugeObject: o downTo: destination]
- 									ifTrue:
- 										[self copyToCompactedCopySpace: o andForwardTargetedAt: destination]]]]
- 			ifFalse: "unmarked; two cases, an unreachable object or a free chunk. Should be faster to set free than to check if already free..."
- 				[destination ifNil: [destination := manager startOfObject: o].
- 				 manager setObjectFree: o]]!

Item was removed:
- SpurAnalysingSweeperCompactor subclass: #SpurTrackingCompactor
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-SpurMemoryManager'!
- 
- !SpurTrackingCompactor commentStamp: 'cb 4/27/2018 13:12' prior: 0!
- SpurTrackingCompactor is a derived simplified implementation of Garbage First (G1) algorithm (Java 9 default GC).
- 
- SpurTrackingCompactor 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. To update efficiently the references to moved objects, SpurTrackingCompactor uses a per segment remembered table in the form with a card marking scheme, hence when compacting segments, instead of scanning all the heap for pointer updates, it scans only the moved objects and the objects remembered for the segment. Since segments compacted are almost free segments, the remembered table is small upon compaction.
- 
- This algorithm requires extra GC write barriers and higher aligment in segments for efficient write barrier (bits in the pointer are used to know to which segment an object belongs). 
- 
- TODO:
- followTrackedReference and reference tracking
- Implement global card mark with 1 byte per 1024 byte (1 bit has object, 7 bits starting index of object in the range covered)
- Implement per segment card mark with 1 bit per 1024 bytes.
- Implement cards for 2Gb (2Mb global card and 250kb), allow only segments within the 2 Gb range to avoid issues
- - Sweep phase can update global card to avoid changing whole VM
- - Write barrier: based on some bits in pointer, figure out which card to dirty and in which segment's card mark
- - followTrackReference is commented with idea: find what to follow and heap and follow all.
- !

Item was removed:
- ----- Method: SpurTrackingCompactor>>compact (in category 'api') -----
- compact
- 	<inline: #never>
- 	self globalSweepAndSegmentOccupationAnalysis.
- 	self selectiveCompaction.
- 	!

Item was removed:
- ----- Method: SpurTrackingCompactor>>followAllObjectsInSegmentToFill (in category 'compaction') -----
- followAllObjectsInSegmentToFill
- 	| currentEntity bridge |
- 	bridge := manager segmentManager bridgeFor: segmentToFill.
- 	currentEntity := manager objectStartingAt: segmentToFill segStart.
- 	[self oop: currentEntity isLessThan: bridge] whileTrue:
- 		[((manager isEnumerableObject: currentEntity) and: [manager isPointersNonImm: currentEntity])
- 			ifTrue: 
- 				[0 to: (manager numSlotsOfAny: currentEntity) do: 
- 					[:i | self followField: i ofObject: currentEntity]]].
- 	self assert: currentEntity = bridge.!

Item was removed:
- ----- Method: SpurTrackingCompactor>>followTrackedReferences (in category 'compaction') -----
- followTrackedReferences
- 	"Each segment has a remembered set in the form of a card table. We need to create a local card table, bitAnd it with all compacted segments, then follow all dirty areas"
- 	1halt. #TODO.	!

Item was removed:
- ----- Method: SpurTrackingCompactor>>freeCompactedSegments (in category 'compaction') -----
- freeCompactedSegments
- 	0 to: manager numSegments - 1 do:
- 		[:i| self freeSegment: (self addressOf: (manager segmentManager segments at: i))].
- 		!

Item was removed:
- ----- Method: SpurTrackingCompactor>>postCompactionAction (in category 'compaction') -----
- postCompactionAction
- 	self followAllObjectsInSegmentToFill. "deal with inner segment references"
- 	self followTrackedReferences. "partial heap scan"
- 	self freeCompactedSegments.
- 	self postForwardingAction.!




More information about the Vm-dev mailing list