[prev in list] [next in list] [prev in thread] [next in thread] 

List:       squeak-vm-dev
Subject:    [Vm-dev] VM Maker: VMMaker.oscog-cb.2379.mcz
From:       commits () source ! squeak ! org
Date:       2018-04-27 11:16:13
Message-ID: E1fC1NM-0004KK-Ex () andreas
[Download RAW message or body]

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

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

Name: VMMaker.oscog-cb.2379
Author: cb
Time: 27 April 2018, 1:15:44.874393 pm
UUID: 92e7c689-d9a4-4d98-bc58-9aa5f10f57e2
Ancestors: VMMaker.oscog-cb.2378

Started implementation of Tracking. Refactor a bit more to share code between \
selective and tracking.

Progress on this topic will take longer time that expected, deadlines are further \
than expected...

=============== Diff against VMMaker.oscog-cb.2378 ===============

Item was removed:
- SpurSweeper subclass: #SpurAnalysingSweeper
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-SpurMemoryManager'!
- 
- !SpurAnalysingSweeper commentStamp: 'cb 4/27/2018 09:45' prior: 0!
- Abstract class, in addition to SpurSweeper, while sweeping the heap I annotate \
segments with occupation rate. This can be used by a compacting algorithm to compact \
only segments which are not used a lot.!

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

Item was removed:
- ----- Method: SpurAnalysingSweeper>>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: SpurAnalysingSweeper>>occupationOf: (in category 'segment access') \
                -----
- occupationOf: segInfo 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SpurAnalysingSweeper>>setOccupationAtIndex:used:unused: (in category \
                'segment access') -----
- setOccupationAtIndex: segmentIndex used: used unused: unused
- 	self subclassResponsibility!

Item was added:
+ 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 added:
+ ----- Method: SpurAnalysingSweeperCompactor class>>declareCVarsIn: (in category \
'translation') ----- + declareCVarsIn: aCCodeGenerator
+ 	aCCodeGenerator var: 'segmentToFill' type: #'SpurSegmentInfo *'!

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

Item was added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- Method: SpurAnalysingSweeperCompactor>>freeSegment: (in category 'segment \
access') ----- + freeSegment: segInfo
+ 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
+ 	 manager addFreeChunkWithBytes: segInfo segSize - manager bridgeSize at: segInfo \
segStart.!

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

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

Item was added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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:
+ SpurAnalysingSweeperCompactor subclass: #SpurSelectiveCompactor
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
- SpurAnalysingSweeper subclass: #SpurSelectiveCompactor
- 	instanceVariableNames: 'segmentToFill'
- 	classVariableNames: 'MaxOccupationForCompaction'
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurSelectiveCompactor commentStamp: 'cb 4/27/2018 13:14' prior: 0!
- !SpurSelectiveCompactor commentStamp: 'cb 4/27/2018 09:50' 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.  
+ TODO: check it seems when memory is decreasing rapidly many empty segment are kept \
                (14 and not 4 - Bug in totalFreeSpace?)
  !

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

Item was removed:
- ----- 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;255]."
- 	MaxOccupationForCompaction := 150. "Basically if segment is occupied by more than \
60%, not worth compacting"!

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

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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.
- 	
- 	 "Follow stack zone and caches..."
- 	self postForwardingAction
- 	!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>computeSegmentsToCompact (in category \
                'compaction') -----
- computeSegmentsToCompact
- 	"Compute segments to claim: 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) // 255. "+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: SpurSelectiveCompactor>>findAndSetSegmentToFill (in category \
                'freeing') -----
- 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: 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 be be a segment already being compacted.
- 	 - cannot contain pinned object (since we're in a copying GC)
- 	 - cannot be entirely empty (no need to block that empty segment until next \
                marking phase)
- 	 - cannot have a high occupation rate (> MaxOccupationForCompaction)"
- 	| leastOccupied leastOccupiedSegment tempOccupied segInfo |
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	leastOccupied := 255.
- 	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: SpurSelectiveCompactor>>findOrAllocateSegmentToFill (in category \
                'freeing') -----
- 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: SpurSelectiveCompactor>>freeSegment: (in category 'freeing') -----
- freeSegment: segInfo
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	 manager addFreeChunkWithBytes: segInfo segSize - manager bridgeSize at: segInfo \
segStart.!

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

Item was removed:
- ----- Method: SpurSelectiveCompactor>>markSegmentAsBeingCompacted: (in category \
                'segment access') -----
- markSegmentAsBeingCompacted: segInfo 
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	"Swizzle is abused bit 8 isBeingCompacted bits 0-7 occupation"
- 	segInfo swizzle: (segInfo swizzle bitOr: 1 << 8)!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>occupationOf: (in category 'segment access') \
                -----
- occupationOf: segInfo 
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	"Swizzle is abused bit 8 isBeingCompacted bits 0-7 occupation"
- 	^segInfo swizzle bitAnd: 16rFF!

Item was removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- 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 removed:
- ----- Method: SpurSelectiveCompactor>>setOccupationAtIndex:used:unused: (in \
                category 'segment access') -----
- setOccupationAtIndex: segmentIndex used: used unused: unused
- 	"WARNING: Resets the isCompacted bit"
- 	"Swizzle is abused bit 8 isBeingCompacted bits 0-7 occupation
- 	 Setting occupation resets the claim bit"
- 	| occupation segInfo |
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	segInfo := self addressOf: (manager segmentManager segments at: segmentIndex).
- 	occupation := used * 255 // (used + unused).
- 	segInfo swizzle: occupation!

Item was changed:
+ SpurAnalysingSweeperCompactor subclass: #SpurTrackingCompactor
- SpurAnalysingSweeper subclass: #SpurTrackingCompactor
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurTrackingCompactor commentStamp: 'cb 4/27/2018 13:12' prior: 0!
- !SpurTrackingCompactor commentStamp: 'cb 4/27/2018 09:58' 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 added:
+ ----- Method: SpurTrackingCompactor>>compact (in category 'api') -----
+ compact
+ 	<inline: #never>
+ 	self globalSweepAndSegmentOccupationAnalysis.
+ 	self selectiveCompaction.
+ 	!

Item was added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- 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 added:
+ ----- Method: SpurTrackingCompactor>>postCompactionAction (in category \
'compaction') ----- + postCompactionAction
+ 	self followAllObjectsInSegmentToFill. "deal with inner segment references"
+ 	self followTrackedReferences. "partial heap scan"
+ 	self freeCompactedSegments.
+ 	self postForwardingAction.!


[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic