[Vm-dev] VM Maker: VMMaker.oscog-eem.2049.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Dec 25 21:02:54 UTC 2016


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2049.mcz

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

Name: VMMaker.oscog-eem.2049
Author: eem
Time: 25 December 2016, 1:02:36.91406 pm
UUID: 82810f52-62c9-4dcf-aab4-3dfc7504f00f
Ancestors: VMMaker.oscog-eem.2048

SpurPlanningCompactor:
Solve the two GCs in a row bug by setting firstMobileObject to endOfMemory before scanning for free objects.  Its value should not be a remnant from a previous compaction.  fistFreeObject should be used as the start of each pass's enumeration, since this can ascend on each pass, whereas firstMobileObject must remain that of the first object whose first field has been saved in savedFirstFieldsSpace.  Hence firstMobileObject should be reset before continuing in each of the continueOPERATIONFrom: methods.

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

Item was changed:
  ----- Method: SpurPlanningCompactor>>continueCopyAndUnmarkMobileObjectsFrom: (in category 'compaction') -----
  continueCopyAndUnmarkMobileObjectsFrom: anUnpinnedEntity
  	"copyAndUnmarkMobileObjects has encountered a run of pinned objects around which
+ 	 it cannot compact, but savedFirstFieldsSpace is still not full.  Continue the pass with a
+ 	 new firstFreeObject, resetting it before continuing.
- 	 it cannot compact, but savedFirstFieldsSpace is still not full.  Continue the pass with new
- 	 firstFreeObject and firstMobileObject, resetting them before continuing.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed)."
  	| result savedFirstFreeObject savedFirstMobileObject nextFreeObject |
  	self assert: (self oop: anUnpinnedEntity isLessThan: manager endOfMemory).
  	self deny: (manager isPinned: anUnpinnedEntity).
  	savedFirstFreeObject := firstFreeObject.
  	savedFirstMobileObject := firstMobileObject.
  	nextFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: anUnpinnedEntity.
+ 	firstMobileObject := savedFirstMobileObject.
  	nextFreeObject ifNil:
  		[^true].
  	firstFreeObject := nextFreeObject.
  	result := self copyAndUnmarkMobileObjects.
  	firstFreeObject := savedFirstFreeObject.
- 	firstMobileObject := savedFirstMobileObject.
  	^result!

Item was changed:
  ----- Method: SpurPlanningCompactor>>continuePlanCompactSavingForwardersFrom: (in category 'compaction') -----
  continuePlanCompactSavingForwardersFrom: anUnpinnedEntity
  	"planCompactSavingForwarders has encountered a run of pinned objects around which
+ 	 it cannot compact, but savedFirstFieldsSpace is still not full.  Continue the pass with a
+ 	 new firstFreeObject, resetting it before continuing.
- 	 it cannot compact, but savedFirstFieldsSpace is still not full.  Continue the pass with new
- 	 firstFreeObject and firstMobileObject, resetting them before continuing.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed)."
  	| result savedFirstFreeObject savedFirstMobileObject nextFreeObject |
  	self assert: (self oop: anUnpinnedEntity isLessThan: manager endOfMemory).
  	self deny: (manager isPinned: anUnpinnedEntity).
  	savedFirstFreeObject := firstFreeObject.
  	savedFirstMobileObject := firstMobileObject.
  	nextFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: anUnpinnedEntity.
+ 	firstMobileObject := savedFirstMobileObject.
  	nextFreeObject ifNil:
  		[^true].
+ 	firstFreeObject := nextFreeObject.
  	result := self planCompactSavingForwarders.
  	firstFreeObject := savedFirstFreeObject.
- 	firstMobileObject := savedFirstMobileObject.
  	^result!

Item was changed:
  ----- Method: SpurPlanningCompactor>>continueUpdatePointersInMobileObjectsFrom: (in category 'compaction') -----
  continueUpdatePointersInMobileObjectsFrom: anUnpinnedEntity
  	"updatePointersInMobileObjects has encountered a run of pinned objects around which
  	 planCompactSavingForwarders cannot compact, but savedFirstFieldsSpace is still not full.
+ 	 Continue the pass with a new firstFreeObject , resetting it before continuing.
- 	 Continue the pass with new firstFreeObject and firstMobileObject, resetting them before continuing.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed)."
  	| result savedFirstFreeObject savedFirstMobileObject nextFreeObject |
  	self assert: (self oop: anUnpinnedEntity isLessThan: manager endOfMemory).
  	self deny: (manager isPinned: anUnpinnedEntity).
  	savedFirstFreeObject := firstFreeObject.
  	savedFirstMobileObject := firstMobileObject.
  	nextFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: anUnpinnedEntity.
+ 	firstMobileObject := savedFirstMobileObject.
  	nextFreeObject ifNil:
  		[^true].
+ 	firstFreeObject := nextFreeObject.
  	result := self updatePointersInMobileObjects.
  	firstFreeObject := savedFirstFreeObject.
- 	firstMobileObject := savedFirstMobileObject.
  	^result!

Item was changed:
  ----- Method: SpurPlanningCompactor>>copyAndUnmark (in category 'compaction') -----
  copyAndUnmark
  	"Sweep the heap, unmarking all objects and moving mobile objects to their correct positions,
  	 restoring their savedFirstFields."
  	| onePass |
  	self unmarkInitialImmobileObjects.
+ 	"If savedFirstFieldsSpace is empty there is nothing to move, and no second pass."
+ 	savedFirstFieldsSpace top < savedFirstFieldsSpace start ifTrue:
+ 		[self assert: firstMobileObject >= manager endOfMemory.
+ 		 ^self].
  	onePass := self copyAndUnmarkMobileObjects.
  	onePass ifFalse:
  		[self unmarkObjectsOverflowingSavedFirstFieldsSpace]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>copyAndUnmarkMobileObjects (in category 'compaction') -----
  copyAndUnmarkMobileObjects
  	"Sweep the mobile portion of the heap, moving objects to their eventual locations, and clearing their marked bits.
  	 Remember to update the savedFirstFields of pointer objects, as these have been forwarded.
  	 This enumeration matches that in planCompactSavingForwarders and updatePointersInMobileObjects."
  
  	| toFinger top previousPin |
  	toFinger := manager startOfObject: firstFreeObject.
  	top := savedFirstFieldsSpace start - manager bytesPerOop.
  	self deny: (manager isMarked: firstFreeObject).
+ 	manager allOldSpaceEntitiesForCompactingFrom: firstFreeObject do:
- 	manager allOldSpaceEntitiesForCompactingFrom: firstMobileObject do:
  		[:o|
  		 self assert: (previousPin isNil or: [toFinger < previousPin]).
  		 (manager isMarked: o) ifTrue:
  			[(manager isPinned: o)
  				ifTrue:
  					[(manager isSegmentBridge: o) ifFalse:
  						[manager setIsMarkedOf: o to: false.
  						 manager segmentManager notePinned: o]. 
  					 previousPin ifNotNil:
  						[self assert: previousPin > toFinger.
  						 ((manager isSegmentBridge: previousPin)
  						  and: [manager isSegmentBridge: o]) ifTrue:
  							[self halt: 'empty segment']].
  					 previousPin := o]
  				ifFalse:
  					[| availableSpace bytes next |
  					 (top := top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
  						[self freeFrom: toFinger upTo: (manager startOfObject: o) previousPin: previousPin.
  						 ^false].
  					 [previousPin notNil
  					  and: [availableSpace := (manager startOfObject: previousPin) - toFinger.
  							bytes := manager bytesInObject: o.
  							bytes ~= availableSpace
  							 and: [bytes + (2 * manager allocationUnit) < availableSpace]]] whileTrue:
  						["The object does not fit in the space between toFinger and previousPin.
  						  Move toFinger beyond previousPin and update previousPin appropriately."
  						 availableSpace > 0 ifTrue:
  							[manager addFreeChunkWithBytes: availableSpace at: toFinger].
  						 toFinger := manager addressAfter: previousPin.
  						 self assert: toFinger < manager endOfMemory.
  						 next := manager objectStartingAt: toFinger.
  						 next >= o ifTrue:
  							[^self continueCopyAndUnmarkMobileObjectsFrom: next].
  						 previousPin := (manager isPinned: next) ifTrue: [next]].
  					 bytes := self copyAndUnmarkObject: o to: toFinger firstField: (manager longAt: top).
  					 toFinger := toFinger + bytes]]].
  	self freeFrom: toFinger upTo: manager endOfMemory previousPin: previousPin.
  	^true!

Item was changed:
  ----- Method: SpurPlanningCompactor>>initializeScan (in category 'compaction') -----
  initializeScan
  	savedFirstFieldsSpace top: savedFirstFieldsSpace start - manager bytesPerOop.
+ 	self reinitializeScan!
- 	firstFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: (manager objectAfter: manager hiddenRootsObject).
- 	firstFreeObject ifNil:
- 		[self error: 'uncompactable heap; no unmarked objects found']!

Item was changed:
  ----- Method: SpurPlanningCompactor>>planCompactSavingForwarders (in category 'compaction') -----
  planCompactSavingForwarders
  	"Sweep the heap from firstFreeObject forwarding marked objects to where they
  	 can be moved to, saving their forwarding pointer in savedFirstFieldsSpace.
  	 Continue until either the end of the heap is reached or savedFirstFieldsSpace is full.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed).
  
  	 Note that this method is potentially recursive. If skipping a run of pinned objects
  	 causes the the algorithm to encounter another run of immobile objects it will
  	 recurse via continuePlanCompactSavingForwardersFrom:.
  
  	 This enumeration matches that in updatePointersInMobileObjects and copyAndUnmarkMobileObjects."
  
  	| toFinger top previousPin |
  	toFinger := manager startOfObject: firstFreeObject.
  	top := savedFirstFieldsSpace top.
  	self deny: (manager isMarked: firstFreeObject).
+ 	manager allOldSpaceEntitiesFrom: firstFreeObject do:
- 	manager allOldSpaceEntitiesFrom: firstMobileObject do:
  		[:o|
  		 self assert: (previousPin isNil or: [toFinger < previousPin]).
  		 (manager isMarked: o) ifTrue:
  			[(manager isPinned: o)
  				ifTrue:
  					[previousPin ifNotNil:
  						[self assert: previousPin > toFinger.
  						 ((manager isSegmentBridge: previousPin)
  						  and: [manager isSegmentBridge: o]) ifTrue:
  							[self halt: 'empty segment']].
  					 previousPin := o]
  				ifFalse:
  					[| availableSpace bytes next |
  					 (top := top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
  						[savedFirstFieldsSpace top: top.
  						 ^false].
  					 [previousPin notNil
  					  and: [availableSpace := (manager startOfObject: previousPin) - toFinger.
  							bytes := manager bytesInObject: o.
  							bytes ~= availableSpace
  							 and: [bytes + (2 * manager allocationUnit) < availableSpace]]] whileTrue:
  						["The object does not fit in the space between toFinger and previousPin.
  						  Move toFinger beyond previousPin and update previousPin appropriately."
  						 toFinger := manager addressAfter: previousPin.
  						 next := manager objectStartingAt: toFinger.
  						 next >= o ifTrue:
  							[savedFirstFieldsSpace top: top.
  							 ^self continuePlanCompactSavingForwardersFrom: next].
  						 previousPin := (manager isPinned: next) ifTrue: [next]].
  					 lastMobileObject := o.
  					 manager
  						longAt: top put: (manager fetchPointer: 0 ofObject: o);
  					 	storePointerUnchecked: 0 "Don't use forward:to:; we dont want to alter the object in any way other than by setting the forwarding pointer"
  							ofObject: o
  								withValue: ((manager hasOverflowHeader: o)
  											ifTrue: [toFinger + manager baseHeaderSize]
  											ifFalse: [toFinger]).
  					 toFinger := toFinger + (manager bytesInObject: o)]]].
  	savedFirstFieldsSpace top: top.
  	^true!

Item was changed:
  ----- Method: SpurPlanningCompactor>>reinitializeScan (in category 'compaction') -----
  reinitializeScan
+ 	firstMobileObject := manager endOfMemory.
  	firstFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: firstFreeObject.
  	firstFreeObject ifNil:
  		[self error: 'uncompactable heap; no unmarked objects found']!

Item was changed:
  ----- Method: SpurPlanningCompactor>>updatePointers (in category 'compaction') -----
  updatePointers
  	"Sweep the heap, updating all objects to their eventual locations.
  	 Remember to update the savedFirstFields of pointer objects, as these have been forwarded."
  	| onePass |
+ 	"If savedFirstFieldsSpace is empty there is nothing to do."
+ 	savedFirstFieldsSpace top < savedFirstFieldsSpace start ifTrue:
+ 		[^self].
  	coInterpreter mapInterpreterOops.
  	self updatePointersInManagerHeapEntities.
  	self updatePointersInSurvivingObjects.
  	self updatePointersInInitialImmobileObjects.
  	onePass := self updatePointersInMobileObjects.
  	onePass ifFalse:
  		[self updatePointersInObjectsOverflowingSavedFirstFieldsSpace]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>updatePointersInMobileObjects (in category 'compaction') -----
  updatePointersInMobileObjects
  	"Sweep the mobile portion of the heap, updating all references to objects to their eventual locations.
  	 Remember to update the savedFirstFields of pointer objects, as these have been forwarded.
  	 This enumeration matches that in planCompactSavingForwarders and copyAndUnmarkMobileObjects."
  
  	| toFinger top previousPin |
  	toFinger := manager startOfObject: firstFreeObject.
  	top := savedFirstFieldsSpace start - manager bytesPerOop.
  	self deny: (manager isMarked: firstFreeObject).
+ 	manager allOldSpaceEntitiesFrom: firstFreeObject do:
- 	manager allOldSpaceEntitiesFrom: firstMobileObject do:
  		[:o|
  		 self assert: (previousPin isNil or: [toFinger < previousPin]).
  		 (manager isMarked: o) ifTrue:
  			[(manager isPinned: o)
  				ifTrue:
  					[self updatePointersIn: o startingAt: 0 savedFirstFieldPointer: nil.
  					 previousPin ifNotNil:
  						[self assert: previousPin > toFinger.
  						 ((manager isSegmentBridge: previousPin)
  						  and: [manager isSegmentBridge: o]) ifTrue:
  							[self halt: 'empty segment']].
  					 previousPin := o]
  				ifFalse:
  					[| availableSpace bytes next |
  					 (top := top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
  						[^false].
  					 [previousPin notNil
  					  and: [availableSpace := (manager startOfObject: previousPin) - toFinger.
  							bytes := manager bytesInObject: o.
  							bytes ~= availableSpace
  							 and: [bytes + (2 * manager allocationUnit) < availableSpace]]] whileTrue:
  						["The object does not fit in the space between toFinger and previousPin.
  						  Move toFinger beyond previousPin and update previousPin appropriately."
  						 toFinger := manager addressAfter: previousPin.
  						 next := manager objectStartingAt: toFinger.
  						 next >= o ifTrue:
  							[^self continueUpdatePointersInMobileObjectsFrom: next].
  						 previousPin := (manager isPinned: next) ifTrue: [next]].
  					 ((manager formatOf: o) <= manager lastPointerFormat
  					  and: [(manager numSlotsOf: o) > 0]) ifTrue:
  						[| oop fwd |
  						 "Relocate the saved first field; Note that CompiledMethods can be excluded since their
  						  first field is either a SmallInteger or a reference to a CogMethod outside of oldSpace."
  						 oop := manager longAt: top.
  						 ((manager isNonImmediate: oop) and: [self isMobile: oop]) ifTrue:
  							[self assert: (manager isMarked: oop).
  							 fwd := manager fetchPointer: 0 ofObject: oop.
  							 self assert: (self isPostMobile: fwd).
  							 manager longAt: top put: fwd]].
  					 self updatePointersIn: o startingAt: 1 savedFirstFieldPointer: top.
  					 toFinger := toFinger + (manager bytesInObject: o)]]].
  	^true!



More information about the Vm-dev mailing list