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

commits at source.squeak.org commits at source.squeak.org
Mon Oct 2 10:06:01 UTC 2017


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

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

Name: VMMaker.oscog-cb.2269
Author: cb
Time: 2 October 2017, 12:05:13.12497 pm
UUID: e4a7f564-11d6-43e2-b616-be2488675bda
Ancestors: VMMaker.oscog-tpr.2268

Normally this commit has no impact on the production VM (some refactorings were made to share code between different part of the GC, but no new things). I tried to simulate the whole VM and generate a VM and it works, but only Travis can confirm us everything's ok.

This is the first commit for the work done in the direction of a low pause GC. The work is split in two, an "engineering" part which consists in incremental marking derived from Dijkstra tri-color, and a "research" part which consists in selective compaction of the heap reusing forwarding objects.

This commit introduces SpurCompactor, an abstract class over the available compactors (Pig, Planning and the experimental ones). The full GC work is divided in Spur in two phases, the marking phase (incremental or not) and the compaction phase (Pig, planning or the experimental ones). 

The new compactor I want to build (SpurSelectiveCompactor) is a sweep algorithm which also compacts part of the heap. I started to do it in 2 steps. First I added SpurSweeper, a compactor which does not compact (if the programmer choose SpurSweeper as the compaction phase, the fullGC is a mark-sweep algorithm). Second I added SpurSelectiveCompactor, which reuses SpurSweeper to sweep the heap. We note that as these new compactors are not compacting the full heap, they should not be used for snapshots, hence snapshots use another compactor (currently SpurPlanningCompactor instead).

=============== Diff against VMMaker.oscog-tpr.2268 ===============

Item was added:
+ CogClass subclass: #SpurCompactor
+ 	instanceVariableNames: 'manager scavenger coInterpreter'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'SpurMemoryManagementConstants VMBasicConstants VMSpurObjectRepresentationConstants'
+ 	category: 'VMMaker-SpurMemoryManager'!
+ 
+ !SpurCompactor commentStamp: 'cb 9/29/2017 16:38' prior: 0!
+ Common superclass of all compactors to define apis and common behaviors.
+ 
+ Instance Variables
+ 	coInterpreter:				<StackInterpreter>
+ 	compactedCopySpace:		<SpurNewSpaceSpace>
+ 	manager:					<SpurMemoryManager>!

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

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

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

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

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

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

Item was added:
+ ----- Method: SpurCompactor>>printTheBogons: (in category 'debugging') -----
+ printTheBogons: bogon!

Item was added:
+ ----- Method: SpurCompactor>>remapObj: (in category 'debugging') -----
+ remapObj: objOop!

Item was added:
+ ----- Method: SpurCompactor>>shouldRemapObj: (in category 'debugging') -----
+ shouldRemapObj: objOop!

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

Item was changed:
+ SpurCompactor subclass: #SpurPigCompactor
+ 	instanceVariableNames: 'firstFreeChunk lastFreeChunk numCompactionPasses'
- CogClass subclass: #SpurPigCompactor
- 	instanceVariableNames: 'manager scavenger coInterpreter firstFreeChunk lastFreeChunk numCompactionPasses'
  	classVariableNames: 'CompactionPassesForGC CompactionPassesForSnapshot'
+ 	poolDictionaries: ''
- 	poolDictionaries: 'SpurMemoryManagementConstants VMBasicConstants VMSpurObjectRepresentationConstants'
  	category: 'VMMaker-SpurMemoryManager'!
  
  !SpurPigCompactor commentStamp: 'eem 12/16/2016 16:20' prior: 0!
  SpurPigCompactor implements the second compactioon algorithm implemented for Spur.  It attempts to move ovbjects down from the end of memory to occupy free chunks in low memory.  It uses Knuth's xor-encoding technique to encode a doubly-linked list in the forwarding field of each free chunk (free chunks, like Spiur objects, being known to have at least one field).  This algorithm has poor performance for two reasons.  First, it does not preserve object order, scrambling the order of objects as it moves the highest objects down to the lowest free chunks.  Second it appears to perform badly, occasionally causing very long pauses.
  
  Instance Variables
  	coInterpreter:				<StackInterpreter>
  	firstFreeChunk:				<Integer>
  	lastFreeChunk:				<Integer>
  	manager:					<SpurMemoryManager>
  	numCompactionPasses:		<Integer>
  	scavenger:					<SpurGenerationScavenger>
  
  firstFreeChunk
  	- oop of freeChunk or 0
  
  lastFreeChunk
  	- oop of freeChunk or 0
  
  numCompactionPasses
  	- 2 for normal GC, 3 for snapshot!

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

Item was removed:
- ----- Method: SpurPigCompactor>>coInterpreter: (in category 'initialization') -----
- coInterpreter: aVMSimulator
- 	<doNotGenerate>
- 	coInterpreter := aVMSimulator!

Item was removed:
- ----- Method: SpurPigCompactor>>manager: (in category 'initialization') -----
- manager: aSpurNBitMMXEndianSimulator
- 	<doNotGenerate>
- 	manager := aSpurNBitMMXEndianSimulator.
- 	aSpurNBitMMXEndianSimulator coInterpreter ifNotNil:
- 		[:coint| coInterpreter := coint].
- 	aSpurNBitMMXEndianSimulator scavenger ifNotNil:
- 		[:scav| scavenger := scav]!

Item was changed:
+ SpurCompactor subclass: #SpurPlanningCompactor
+ 	instanceVariableNames: 'biasForGC firstFreeObject mobileStart firstMobileObject lastMobileObject savedFirstFieldsSpace savedFirstFieldsSpaceNotInOldSpace firstFieldOfRememberedSet anomaly objectAfterLastMobileObject'
- CogClass subclass: #SpurPlanningCompactor
- 	instanceVariableNames: 'manager scavenger coInterpreter biasForGC firstFreeObject mobileStart firstMobileObject lastMobileObject savedFirstFieldsSpace savedFirstFieldsSpaceNotInOldSpace firstFieldOfRememberedSet anomaly objectAfterLastMobileObject'
  	classVariableNames: ''
+ 	poolDictionaries: 'VMBytecodeConstants'
- 	poolDictionaries: 'SpurMemoryManagementConstants VMBasicConstants VMBytecodeConstants VMSpurObjectRepresentationConstants'
  	category: 'VMMaker-SpurMemoryManager'!
  
  !SpurPlanningCompactor commentStamp: 'eem 12/23/2016 17:50' prior: 0!
  SpurPlanningCompactor implements the classic planning compaction algorithm for Spur.  It makes at least three passes through the heap.  The first pass plans where live movable objects will go, copying their forwarding field to the next slot in savedFirstFieldsSpace, and setting their forwarding pointer to point to their eventual location.  The second pass updates all pointers in live pointer objects to point to objects' final destinations.  The third pass moves objects to their final positions, unmarking objects as it does so.  If the forwarding fields of live objects in the to-be-moved portion of the entire heap won't fit in savedFirstFieldsSpace, then additional passes are made until the entire heap has been compacted.
  
  Instance Variables
  	biasForGC						<Boolean>
  	coInterpreter:					<StackInterpreter>
  	firstFieldOfRememberedSet		<Oop>
  	firstFreeObject					<Oop>
  	firstMobileObject				<Oop>
  	lastMobileObject				<Oop>
  	manager:						<SpurMemoryManager>
  	savedFirstFieldsSpace				<SpurContiguousObjStack>
  	savedFirstFieldsSpaceWasAllocated	<Boolean>
  	scavenger:						<SpurGenerationScavenger>
  
  biasForGC
  	- true if compacting for GC, in which case do only one pass, or false if compacting for snapshot, in which case do as many passes as necessary to compact the entire heap.
  
  firstFieldOfRememberedSet
  	- the saved first field of the rememberedSet.  The rememberedSet must be relocated specially because it is not a pointer object.  And hence the first field needs to be extracted for proper relocation.
  
  firstFreeObject
  	- the first free object in a compaction pass.
  
  firstMobileObject
  	- the first mobile object in a compaction.  Unpinned objects from the firstMobileObject through to the lastMobileObject are implicitly forwarded.
  
  lastMobileObject
  	- the last mobile object in a compaction.  Unpinned objects from the firstMobileObject through to the lastMobileObject are implicitly forwarded.
  
  savedFirstFieldsSpace
  	- the space holding the saved first fields, each overwritten by a forwarding pointer, for the objects from firstMobileObject through to lastMobileObject.
  
  savedFirstFieldsSpaceWasAllocated
  	- if true, the memory for savedFirstFieldsSpace was obtained via a call of sqAllocateMemorySegmentOfSize:Above:AllocatedSizeInto:!

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

Item was removed:
- ----- Method: SpurPlanningCompactor>>coInterpreter: (in category 'instance initialization') -----
- coInterpreter: aVMSimulator
- 	<doNotGenerate>
- 	coInterpreter := aVMSimulator!

Item was removed:
- ----- Method: SpurPlanningCompactor>>manager: (in category 'instance initialization') -----
- manager: aSpurNBitMMXEndianSimulator
- 	<doNotGenerate>
- 	manager := aSpurNBitMMXEndianSimulator.
- 	aSpurNBitMMXEndianSimulator coInterpreter ifNotNil:
- 		[:coint| coInterpreter := coint].
- 	aSpurNBitMMXEndianSimulator scavenger ifNotNil:
- 		[:scav| scavenger := scav]!

Item was added:
+ SpurSweeper subclass: #SpurSelectiveCompactor
+ 	instanceVariableNames: 'regionsWithOccupationPercentage regionsToReclaim regionToFill'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
+ 
+ !SpurSelectiveCompactor commentStamp: 'cb 10/1/2017 10:54' prior: 0!
+ SpurSelectiveCompactor compacts memory by selecting the memory regions 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 regions that the one compacted.
+ 
+ The algorithm works as follow. First, a global sweep pass iterates over the memory linearly, changing unmarked objects to free space. During the global sweep phase, the heap is analysed in the form of variable sized regions and the percentage of occupation of each region is computed. Second, the least occupied regions are compacted by copying the remaining live objects into an entirely free region, called regionToFill (we detail later in the paragraph where regionToFill comes from) and changing their values to forwarding objects. The rest of each region being freed is temporarily marked as used with hidden word objects. Third, the next marking phase removes all forwarders. Fourth, at the beginning of the next compaction phase the compacted regions from the previous GC can be entirely marked as free space (No need to check anything inside, there were only forwarders that were removed and hidden word objects). One of the freed region is then selected as the regionToFill, others are j
 ust marked as free space. The compaction is effectively partial, compacting only the most critical regions of the heap to limit fragmentation. 
+ 
+ Now this works well when biasForGC is true, but when performing a snapshot, the compactor instead frees the regions held and then calls a more aggressive compactor to decrease the image size.
+ 
+ regionsWithOccupationPercentage <> list of regions with the occupation rate
+ regionsToReclaim <> regions that will be freed at the beginning of next compaction (After next marking phase)
+ biasForGC <> if false this is a compaction for snapshot, else normal GC
+ regionToFill <> the region that will be filled through the copying algorithm
+ 
+ !

Item was added:
+ ----- Method: SpurSelectiveCompactor>>compact (in category 'api') -----
+ compact
+ 	<inline: #never> "for profiling"
+ 	biasForGC
+ 		ifTrue: [self internalCompact]
+ 		ifFalse: [aggressiveCompactor compact]
+ 	!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>freeRegionsFromPastCompactionsAndSetRegionToFill (in category 'freeing regions') -----
+ freeRegionsFromPastCompactionsAndSetRegionToFill
+ 	"regionsToReclaim is likely a word object with an index and a list of range of regions to reclaim. Sets the regionToFill"!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>globalSweepAndRegionAnalysis (in category 'sweep phase') -----
+ globalSweepAndRegionAnalysis
+ 	"Iterate over the whole memory, free unmarked objects, figure out regions based on the current size of the heap (regions are variable sized based on an estimate, segments and where objects end) and save them in regionsWithOccupationPercentage"!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>internalCompact (in category 'api') -----
+ internalCompact
+ 	self freeRegionsFromPastCompactionsAndSetRegionToFill.
+ 	self globalSweepAndRegionAnalysis.
+ 	self selectiveCompaction.!

Item was added:
+ ----- Method: SpurSelectiveCompactor>>selectiveCompaction (in category 'compaction') -----
+ selectiveCompaction
+ 	"Iterate over regionsWithOccupationPercentage, compact regions from the least occupied to the most occupied, stops when the next region to compact is filled with more than MinFreeForCompaction or when the segment to fill is full"!

Item was changed:
+ SpurCompactor subclass: #SpurSlidingCompactor
+ 	instanceVariableNames: 'compactedCopySpace'
- CogClass subclass: #SpurSlidingCompactor
- 	instanceVariableNames: 'manager scavenger coInterpreter compactedCopySpace'
  	classVariableNames: ''
+ 	poolDictionaries: ''
- 	poolDictionaries: 'SpurMemoryManagementConstants VMBasicConstants VMSpurObjectRepresentationConstants'
  	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 added:
+ SpurCompactor subclass: #SpurSweeper
+ 	instanceVariableNames: 'biasForGC aggressiveCompactor'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
+ 
+ !SpurSweeper commentStamp: 'cb 10/2/2017 11:34' prior: 0!
+ SpurSweeper is a sweep-only algorithm, setting the compactor to SpurSweeper effectively changes the fullGC to a mark-sweep non-moving algorithm. 
+ 
+ SpurSweeper has two main purposes:
+ 1. SpurSelectiveCompactor includes a sweep algorithm, inherited from SpurSweeper, and SpurSweeper allows to debug it separatedly.
+ 2. SpurSweeper is a non-moving GC which can be convenient in some cases (For example when accessing objects from C in a concurrent thread called with ThreadedFFI, the C code can access the objects during fullGC since there won't be conflict with object fields being updated while being read).
+ 
+ For snapshots a non-compacting algortihm does not make sense, hence a more aggressive compactor is called instead (see #compact).!

Item was added:
+ ----- Method: SpurSweeper>>biasForGC (in category 'api') -----
+ biasForGC
+ 	biasForGC := true.!

Item was added:
+ ----- Method: SpurSweeper>>biasForSnapshot (in category 'api') -----
+ biasForSnapshot
+ 	biasForGC := false.!

Item was added:
+ ----- Method: SpurSweeper>>bulkFreeChunkFrom: (in category 'sweep phase') -----
+ bulkFreeChunkFrom: objOop
+ 	"ObjOop is either a freeChunk or an object to free, always in old space. The old space entity before objOop is necessarily a marked object.
+ 	 Attempts to free as many byte from objOop, looking ahead for multiple freechunks / objects to free in a row"
+ 	| bytes start next currentObj |
+ 	
+ 	"Avoids pathological case, not point in dealing with non-mergeable free chunks, we would remove them and re-add them to the free list."
+ 	(self isSingleFreeObject: objOop) ifTrue: [^0].
+ 	
+ 	"We free unmarked objects and freechunks next to each others and merge them at the same time"
+ 	start := manager startOfObject: objOop.
+ 	currentObj := objOop.
+ 	bytes := 0.
+ 	[bytes := bytes + self bytesInObject: currentObj.
+ 	self freeEntity: currentObj.
+ 	next := manager objectStartingAt: start + bytes.
+ 	self canUseNextEntityAsFreeSpace: next] 
+ 		whileTrue: [currentObj := next].
+ 	
+ 	manager totalFreeOldSpace: manager totalFreeOldSpace + bytes.
+ 	^manager freeChunkWithBytes: bytes at: start!

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

Item was added:
+ ----- Method: SpurSweeper>>canUseNextEntityAsFreeSpace: (in category 'sweep phase') -----
+ canUseNextEntityAsFreeSpace: next
+ 	<inline: true>
+ 	^ (manager oop: next isLessThan: manager endOfMemory) and: [self canUseAsFreeSpace: next]!

Item was added:
+ ----- Method: SpurSweeper>>coInterpreter: (in category 'initialization') -----
+ coInterpreter: aVMSimulator
+ 	<doNotGenerate>
+ 	super coInterpreter: aVMSimulator.
+ 	aggressiveCompactor coInterpreter: aVMSimulator.!

Item was added:
+ ----- Method: SpurSweeper>>compact (in category 'api') -----
+ compact
+ 	"Unless we're snapshotting, use a non-compacting sweep algorithm"
+ 	<inline: #never> "for profiling"
+ 	biasForGC
+ 		ifTrue: [self globalSweep]
+ 		ifFalse: [aggressiveCompactor compact]!

Item was added:
+ ----- Method: SpurSweeper>>freeEntity: (in category 'sweep phase') -----
+ freeEntity: entity
+ 	<inline: true>
+ 	(manager isFreeObject: entity) 
+ 		ifFalse: "Freed old space objects are removed from remembered table"
+ 			[(manager isRemembered: entity) ifTrue:
+ 				[scavenger forgetObject: entity]]
+ 		ifTrue:  "Merged old space free chunks are removed from free list"
+ 			[manager detachFreeObject: entity]
+ 	!

Item was added:
+ ----- Method: SpurSweeper>>globalSweep (in category 'sweep phase') -----
+ globalSweep
+ 	"allOldSpaceEntitiesDo: computes the address of the next object only once the block has been evaluated,
+ 	 hence when we rewrite object iterated over as a larger free chunk, the next object is the object after the chunk"
+ 	self allOldSpaceEntitiesDo: 
+ 		[:objOop | (self canUseAsFreeSpace: objOop) ifTrue: [self bulkFreeChunkFrom: objOop]].
+ 	!

Item was added:
+ ----- Method: SpurSweeper>>initialize (in category 'initialization') -----
+ initialize
+ 	aggressiveCompactor := SpurPlanningCompactor new.!

Item was added:
+ ----- Method: SpurSweeper>>isSingleFreeObject: (in category 'sweep phase') -----
+ isSingleFreeObject: objOop
+ 	<inline: true>
+ 	| next |
+ 	^ (manager isFreeObject: objOop) and: 
+ 		[next := manager objectAfter: objOop limit: manager endOfMemory.
+ 		(manager oop: next isGreaterThanOrEqualTo: manager endOfMemory) or: [manager isMarked: next]]!

Item was added:
+ ----- Method: SpurSweeper>>manager: (in category 'initialization') -----
+ manager: aSpurNBitMMXEndianSimulator
+ 	<doNotGenerate>
+ 	super manager: aSpurNBitMMXEndianSimulator.
+ 	aggressiveCompactor manager: aSpurNBitMMXEndianSimulator!



More information about the Vm-dev mailing list