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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 26 18:54:25 UTC 2018


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

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

Name: VMMaker.oscog-cb.2377
Author: cb
Time: 26 April 2018, 8:53:46.138916 pm
UUID: 94bd1cb9-5044-44d7-8e84-7e4c341f8855
Ancestors: VMMaker.oscog-cb.2376

Spur ancilliary classes includes now: 
(self compactorClass withAllSuperclasses copyUpThrough: SpurCompactor) reverse
instead of only:
self compactorClass

Removed a shit load of code duplication thanks to this change.

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

Item was changed:
  ----- Method: SpurCompactor>>postSwizzleAction (in category 'api') -----
  postSwizzleAction
+ 	"do nothing"!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurCompactor>>printTheBogons: (in category 'debugging') -----
  printTheBogons: aBogon
+ 	<inline: true>
+ 	coInterpreter
+ 		print: 'bogon '; printHexnp: aBogon; cr!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurCompactor>>remapObj: (in category 'api') -----
  remapObj: objOop
+ 	<api>
+ 	<inline: false>
+ 	^manager vanillaRemapObj: objOop!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurCompactor>>shouldRemapObj: (in category 'api') -----
  shouldRemapObj: objOop
+ 	<api>
+ 	"Answer if the obj should be scavenged (or simply followed). The method is called
+ 	 shouldRemapObj: for compatibility with ObjectMemory.  Defer to the compactor
+ 	 to choose the actual test, there being a difference between the vanilla test and
+ 	 that used with a sliding compactor where objects are not marked as forwarded."
+ 	^manager vanillaShouldRemapObj: objOop!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
  	initializationOptions ifNil: [initializationOptions := options].
+ 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo }, 
+ 		(self compactorClass withAllSuperclasses copyUpThrough: SpurCompactor) reverse,
+ 		SpurNewSpaceSpace withAllSubclasses
+ 		
+ 	!
- 	^{	SpurGenerationScavenger. SpurScavengeLogRecord. SpurSegmentManager. SpurSegmentInfo. self compactorClass },
- 		SpurNewSpaceSpace withAllSubclasses!

Item was removed:
- ----- Method: SpurPigCompactor>>postSwizzleAction (in category 'compatibility') -----
- postSwizzleAction
- 	"do nothing"
- 	!

Item was removed:
- ----- Method: SpurPigCompactor>>printTheBogons: (in category 'debug printing') -----
- printTheBogons: aBogon
- 	<inline: true>
- 	coInterpreter
- 		print: 'bogon '; printHexnp: aBogon; cr!

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

Item was removed:
- ----- Method: SpurPigCompactor>>shouldRemapObj: (in category 'gc - scavenge/compact') -----
- shouldRemapObj: objOop
- 	<api>
- 	"Answer if the obj should be scavenged (or simply followed). The method is called
- 	 shouldRemapObj: for compatibility with ObjectMemory.  Defer to the compactor
- 	 to choose the actual test, there being a difference between the vanilla test and
- 	 that used with a sliding compactor where objects are not marked as forwarded."
- 	^manager vanillaShouldRemapObj: objOop!

Item was removed:
- ----- Method: SpurPlanningCompactor>>postSwizzleAction (in category 'compatibility') -----
- postSwizzleAction
- 	"do nothing"
- 	!

Item was changed:
+ SpurSweeper subclass: #SpurSelectiveCompactor
+ 	instanceVariableNames: 'segmentToFill'
- SpurCompactor subclass: #SpurSelectiveCompactor
- 	instanceVariableNames: 'biasForGC segmentToFill'
  	classVariableNames: 'MaxOccupationForCompaction'
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!
  
  !SpurSelectiveCompactor commentStamp: 'cb 4/26/2018 13:59' 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).
  
  IMPORTANT: I could not figure out to make inheritance work so I copied methods from SpurSweeper here.
  
  segmentToFill <SegInfo> the segment that will be filled through the copying algorithm
  
  !

Item was removed:
- ----- Method: SpurSelectiveCompactor>>biasForGC (in category 'api') -----
- biasForGC
- 	biasForGC := true.!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>biasForSnapshot (in category 'api') -----
- biasForSnapshot
- 	biasForGC := false.!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>bulkFreeChunkFrom: (in category 'sweep phase - copied from SpurSweeper') -----
- 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 + (manager bytesInObject: currentObj).
- 	self freeEntity: currentObj.
- 	next := manager objectStartingAt: start + bytes.
- 	self canUseNextEntityAsFreeSpace: next] 
- 		whileTrue: [currentObj := next].
- 	
- 	manager addFreeChunkWithBytes: bytes at: start.
- 	
- 	^ next!

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

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

Item was removed:
- ----- Method: SpurSelectiveCompactor>>freeEntity: (in category 'sweep phase - copied from SpurSweeper') -----
- 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 removed:
- ----- Method: SpurSelectiveCompactor>>isSingleFreeObject: (in category 'sweep phase - copied from SpurSweeper') -----
- 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 removed:
- ----- Method: SpurSelectiveCompactor>>printTheBogons: (in category 'debugging') -----
- printTheBogons: aBogon
- 	<inline: true>
- 	coInterpreter
- 		print: 'bogon '; printHexnp: aBogon; cr!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>remapObj: (in category 'api') -----
- remapObj: objOop
- 	<api>
- 	<inline: false>
- 	^manager vanillaRemapObj: objOop!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>shouldRemapObj: (in category 'api') -----
- shouldRemapObj: objOop
- 	<api>
- 	^manager vanillaShouldRemapObj: objOop!

Item was removed:
- ----- Method: SpurSelectiveCompactor>>unmark: (in category 'sweep phase - copied from SpurSweeper') -----
- unmark: objOop
- 	self assert: ((manager isMarked: objOop) and: [(manager isFreeObject: objOop) not]).
- 	(manager isSegmentBridge: objOop) ifFalse: [manager setIsMarkedOf: objOop to: false].
- 	(manager isPinned: objOop) ifTrue: [manager segmentManager notePinned: objOop]!

Item was removed:
- ----- Method: SpurSweeper>>postSwizzleAction (in category 'api') -----
- postSwizzleAction
- 	"do nothing"
- 	!

Item was removed:
- ----- Method: SpurSweeper>>printTheBogons: (in category 'debugging') -----
- printTheBogons: aBogon
- 	<inline: true>
- 	coInterpreter
- 		print: 'bogon '; printHexnp: aBogon; cr!

Item was removed:
- ----- Method: SpurSweeper>>remapObj: (in category 'api') -----
- remapObj: objOop
- 	<api>
- 	<inline: false>
- 	^manager vanillaRemapObj: objOop!

Item was removed:
- ----- Method: SpurSweeper>>shouldRemapObj: (in category 'api') -----
- shouldRemapObj: objOop
- 	<api>
- 	^manager vanillaShouldRemapObj: objOop!



More information about the Vm-dev mailing list