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

commits at source.squeak.org commits at source.squeak.org
Tue Jun 12 06:56:58 UTC 2018


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

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

Name: VMMaker.oscog-cb.2417
Author: cb
Time: 12 June 2018, 8:56:33.338224 am
UUID: f2094b85-27cf-4df5-a782-d48ab5845ace
Ancestors: VMMaker.oscog-eem.2416

Reworked a bit inlining for profiling.

Sweeper and Selective now rebuild the free linked lists instead of maintaining them.

Micro-optimization in sweep phases.

Compaction pause effectively decreased by -60% now on a large range of benchmarks, growing heaps from a few hundred Mb to a few Gbs.

=============== Diff against VMMaker.oscog-eem.2416 ===============

Item was changed:
  ----- Method: SpurMemoryManager>>addFreeChunkWithBytes:at: (in category 'free space') -----
  addFreeChunkWithBytes: bytes at: address
+ 	totalFreeOldSpace := totalFreeOldSpace + bytes.
+ 	^self freeChunkWithBytes: bytes at: address!
- 	self freeChunkWithBytes: bytes at: address.
- 	totalFreeOldSpace := totalFreeOldSpace + bytes!

Item was changed:
  ----- Method: SpurMemoryManager>>unlinkFreeChunk:chunkBytes: (in category 'free space') -----
  unlinkFreeChunk: freeChunk chunkBytes: chunkBytes
  	"Unlink a free object from the free lists. Do not alter totalFreeOldSpace. Used for coalescing."
+ 	| index next prev |
- 	| index node next prev |
  	index := chunkBytes / self allocationUnit.
  	
  	"Pathological 64 bits case - size 1 - single linked list"
  	(self bytesBigEnoughForPrevPointer: chunkBytes) ifFalse:
+ 		[^self unlinkSmallChunk: freeChunk index: index].
- 		[node := freeLists at: index.
- 			 prev := 0.
- 			 [node ~= 0] whileTrue:
- 				[self assert: node = (self startOfObject: node).
- 				 self assertValidFreeObject: node.
- 				 next := self fetchPointer: self freeChunkNextIndex ofFreeChunk: node.
- 				 node = freeChunk ifTrue:
- 					[prev = 0
- 						ifTrue: [self unlinkFreeChunk: freeChunk atIndex: index bytesBigEnoughForPrevPointer: false]
- 						ifFalse: [self setNextFreeChunkOf: prev withValue: next bytesBigEnoughForPrevPointer: false].
- 					 ^freeChunk].
- 				 prev := node.
- 				 node := next].
- 			 self error: 'freeChunk not found in free list of size 1'].
  	
  	prev := self fetchPointer: self freeChunkPrevIndex ofFreeChunk: freeChunk.
  	"Has prev element: update double linked list"
  	prev ~= 0 ifTrue:
  		[self 
  			setNextFreeChunkOf: prev 
  			withValue: (self fetchPointer: self freeChunkNextIndex ofFreeChunk: freeChunk) 
  			chunkBytes: chunkBytes.
  		 ^freeChunk].
  	
  	"Is the beginning of a list"
  	"Small chunk"
  	(index < self numFreeLists and: [1 << index <= freeListsMask]) ifTrue: 
  		[self unlinkFreeChunk: freeChunk atIndex: index bytesBigEnoughForPrevPointer: true.
  		 ^freeChunk].
  	"Large chunk"
  	 next := self fetchPointer: self freeChunkNextIndex ofFreeChunk: freeChunk.
  	 next = 0
  		ifTrue: "no list; remove the interior node"
  			[self unlinkSolitaryFreeTreeNode: freeChunk]
  		ifFalse: "list; replace node with it"
  			[self inFreeTreeReplace: freeChunk with: next].
  	^freeChunk
  	
  	
  
  	!

Item was added:
+ ----- Method: SpurMemoryManager>>unlinkSmallChunk:index: (in category 'free space') -----
+ unlinkSmallChunk: freeChunk index: index
+ 	| node prev next |
+ 	<inline: #never> "for profiling"
+ 	 node := freeLists at: index.
+ 	 prev := 0.
+ 	 [node ~= 0] whileTrue:
+ 		[self assert: node = (self startOfObject: node).
+ 		 self assertValidFreeObject: node.
+ 		 next := self fetchPointer: self freeChunkNextIndex ofFreeChunk: node.
+ 		 node = freeChunk ifTrue:
+ 			[prev = 0
+ 				ifTrue: [self unlinkFreeChunk: freeChunk atIndex: index bytesBigEnoughForPrevPointer: false]
+ 				ifFalse: [self setNextFreeChunkOf: prev withValue: next bytesBigEnoughForPrevPointer: false].
+ 			 ^freeChunk].
+ 		 prev := node.
+ 		 node := next].
+ 	 self error: 'freeChunk not found in free list of size 1'
+ 	
+ 	
+ 
+ 	!

Item was changed:
  ----- Method: SpurSelectiveCompactor>>compact (in category 'api') -----
  compact
+ 	<inline: #never> "for profiling, though we profile selectiveCompaction and sweep separatly."
+ 	self resetFreeLists.
- 	<inline: #never> "for profiling"
  	self freePastSegmentsAndSetSegmentToFill.
  	self globalSweepAndSegmentOccupationAnalysis.
  	self selectiveCompaction.
  	!

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

Item was removed:
- ----- Method: SpurSelectiveCompactor>>freeSegment: (in category 'segment access') -----
- freeSegment: segInfo
- 	<var: 'segInfo' type: #'SpurSegmentInfo *'>
- 	 "self unmarkSegmentAsBeingCompacted: segInfo. 'For assertion in free chunk management'."
- 	 manager addFreeChunkWithBytes: segInfo segSize - manager bridgeSize at: segInfo segStart.!

Item was changed:
  ----- Method: SpurSelectiveCompactor>>globalSweepAndSegmentOccupationAnalysis (in category 'sweep phase') -----
  globalSweepAndSegmentOccupationAnalysis
+ 	<inline: #never> "profiling"
+ 	"Iterate over old space, free unmarked objects, annotate each segment with each occupation"
+ 	| currentEntity nextBridge segmentIndex currentUsed currentUnused |
+ 	currentEntity := manager firstObject.
+ 	nextBridge := manager segmentManager bridgeAt: 0.
+ 	segmentIndex := currentUnused := currentUsed := 0.
+ 	[self oop: currentEntity isLessThan: manager endOfMemory] whileTrue:
+ 		[currentEntity = nextBridge "End of segment, set occupation"
+ 			ifTrue: 
+ 				[self 
+ 					setOccupationAtIndex: segmentIndex
+ 					used: currentUsed 
+ 					unused: currentUnused.
+ 				  currentUnused := currentUsed := 0.
+ 				  segmentIndex := segmentIndex + 1.
+ 				  nextBridge := manager segmentManager bridgeAt: segmentIndex]
+ 			ifFalse: 
+ 				[(self canUseAsFreeSpace: currentEntity) "In-segment, sweep and compute occupation"
+ 					ifTrue: 
+ 						[currentEntity := self bulkFreeChunkFrom: currentEntity.
+ 						 currentUnused := currentUnused + (manager bytesInObject: currentEntity)]
+ 					ifFalse: 
+ 						[self unmark: currentEntity.
+ 						 currentUsed := currentUsed + (manager bytesInObject: currentEntity)]].
+ 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
+ 	self "set last segment occupation"	
+ 		setOccupationAtIndex: segmentIndex
+ 		used: currentUsed 
+ 		unused: currentUnused.
+ 		
- 	self internalGlobalSweepAndSegmentOccupationAnalysis.
  	manager checkFreeSpace: GCModeFull.
+ 	manager unmarkSurvivingObjectsForCompact.!
- 	manager unmarkSurvivingObjectsForCompact.
- 	self cCode: '' inSmalltalk: [manager freeTreeOverlapCheck].!

Item was removed:
- ----- 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 bytesInObject: currentEntity)]
- 					ifFalse: 
- 						[self unmark: currentEntity.
- 						 currentUsed := currentUsed + (manager bytesInObject: currentEntity)]].
- 		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
- 	"set last segment (last bridge = endOfMemory)"	
- 	self 
- 		setOccupationAtIndex: segmentIndex
- 		used: currentUsed 
- 		unused: currentUnused.!

Item was changed:
  ----- Method: SpurSelectiveCompactor>>selectiveCompaction (in category 'compaction') -----
  selectiveCompaction
  	"Figures out which segments to compact and compact them into segmentToFill"
  	| atLeastOneSegmentToCompact |
+ 	<inline: #never> "profiling"
  	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].
- 		 	 self compactSegmentsToCompact.
- 			 self cCode: '' inSmalltalk: [manager freeTreeOverlapCheck].].
  	manager checkFreeSpace: GCModeFull.!

Item was changed:
  ----- Method: SpurSweeper>>bulkFreeChunkFrom: (in category 'sweep phase') -----
  bulkFreeChunkFrom: objOop
+ 	"The old space entity before objOop is necessarily a marked object. Attempts to free as many bytes 
+ 	from objOop start as possible, looking ahead to free contiguous freechunks / unmarked objects"
- 	"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 |
+ 	self assert: ((manager isMarked: objOop) not or: [manager isFreeObject: objOop]).
- 	
- 	"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).
+ 	(manager isRemembered: currentObj)
+ 		ifTrue: 
+ 			[self assert: (manager isFreeObject: currentObj) not.
+ 			 scavenger forgetObject: currentObj].
- 	self freeEntity: currentObj.
  	next := manager objectStartingAt: start + bytes.
+ 	self assert: ((manager oop: next isLessThan: manager endOfMemory)
+ 		or: [next = manager endOfMemory and: [(self canUseAsFreeSpace: next) not]]).
+ 	self canUseAsFreeSpace: next] 
- 	self canUseNextEntityAsFreeSpace: next] 
  		whileTrue: [currentObj := next].
  	
+ 	^manager addFreeChunkWithBytes: bytes at: start!
- 	manager addFreeChunkWithBytes: bytes at: start.
- 	
- 	^ next!

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

Item was changed:
  ----- Method: SpurSweeper>>compact (in category 'api') -----
  compact
  	<inline: #never> "for profiling"
+ 	self resetFreeLists.
  	self globalSweep!

Item was removed:
- ----- 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 changed:
  ----- Method: SpurSweeper>>globalSweep (in category 'sweep phase') -----
  globalSweep
+ 	"Iterate over all entities, in order, making large free chunks from free chunks and unmarked objects, 
+ 	unmarking live objects and rebuilding the free lists."
- 	"Iterate over all entities, in order, if the entity is a free chunk or unmarked object, 
- 	 make a new big piece of free chunk, else unmark the object which stay live."
  
+ 	| currentEntity |
- 	| currentEntity start |
  	currentEntity := manager firstObject.
  	[self oop: currentEntity isLessThan: manager endOfMemory] whileTrue:
  		[(self canUseAsFreeSpace: currentEntity) 
+ 			ifTrue: [currentEntity := self bulkFreeChunkFrom: 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]
  			ifFalse: [self unmark: currentEntity].
  		 currentEntity := manager objectAfter: currentEntity limit: manager endOfMemory].
  			
  	manager checkFreeSpace: GCModeFull.
- 		
  	manager unmarkSurvivingObjectsForCompact.
+ 
- 	
- 	self cCode: '' inSmalltalk: [manager freeTreeOverlapCheck].
  	!

Item was removed:
- ----- 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>>resetFreeLists (in category 'api') -----
+ resetFreeLists
+ 	manager resetFreeListHeads.
+ 	manager totalFreeOldSpace: 0.!



More information about the Vm-dev mailing list