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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 31 20:47:37 UTC 2016


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

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

Name: VMMaker.oscog-eem.2062
Author: eem
Time: 31 December 2016, 12:46:31.161048 pm
UUID: f42af46e-c315-4da9-8a34-aa300763e11c
Ancestors: VMMaker.oscog-eem.2061

SpurPlanningCompactor:
Fix "continue" enumeration (enumerating over an intervening run of immobile objects within the mobile objects) for update and copyAndUnmark.

Abstract the forward operation to forwardMobileObject:to:savedFirstFieldPtr: for clarity and comment the purpose of the loop in the "continue" methods.
	
Change the return value of copyAndUnmarkObject:to:firstField: to match forwardMobileObject:to:savedFirstFieldPtr:.

The simulator successfully updated and snapshotted :-)

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

Item was changed:
  ----- Method: SpurPlanningCompactor>>continueCopyAndUnmarkMobileObjectsFrom:withTop: (in category 'compaction') -----
+ continueCopyAndUnmarkMobileObjectsFrom: anUnpinnedEntity withTop: initialTop
- continueCopyAndUnmarkMobileObjectsFrom: anUnpinnedEntity withTop: top
  	"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.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed)."
+ 	| result top savedFirstFreeObject savedFirstMobileObject nextFreeObject |
- 	| 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.
+ 	top := initialTop.
+ 	"Copy and unmark the run of immobile objects to match the enumeration in continuePlanCompactSavingForwardersFrom:toFinger:."
+ 	manager allOldSpaceEntitiesFrom: anUnpinnedEntity to: firstMobileObject do:
+ 		[:o|
+ 		 (o < firstMobileObject
+ 		  and: [manager isMarked: o]) ifTrue:
+ 			[(manager isPinned: o)
+ 				ifTrue:
+ 					[(manager isSegmentBridge: o) ifFalse:
+ 						[manager setIsMarkedOf: o to: false.
+ 						 manager segmentManager notePinned: o]]
+ 				ifFalse:
+ 					[(top := top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
+ 						[^false].
+ 					 self assert: o = (manager fetchPointer: 0 ofObject: o).
+ 					 manager
+ 						setIsMarkedOf: o to: false;
+ 						storePointerUnchecked: 0 ofObject: o withValue: (manager longAt: o)]]].
  	firstMobileObject := savedFirstMobileObject.
  	nextFreeObject ifNil:
  		[^true].
+ 	savedFirstFreeObject := firstFreeObject.
  	firstFreeObject := nextFreeObject.
  	result := self copyAndUnmarkMobileObjectsWithTop: top.
  	firstFreeObject := savedFirstFreeObject.
  	^result!

Item was changed:
  ----- Method: SpurPlanningCompactor>>continuePlanCompactSavingForwardersFrom:toFinger: (in category 'compaction') -----
  continuePlanCompactSavingForwardersFrom: anUnpinnedEntity toFinger: initialToFinger
  	"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.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed)."
+ 	| result toFinger savedFirstMobileObject savedFirstFreeObject nextFreeObject |
- 	| result toFinger savedFirstMobileObject nextFreeObject |
  	self assert: (self oop: anUnpinnedEntity isLessThan: manager endOfMemory).
  	self deny: (manager isPinned: anUnpinnedEntity).
  	toFinger := initialToFinger.
  	savedFirstMobileObject := firstMobileObject.
  	nextFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: anUnpinnedEntity.
+ 	"Forward the run of immobile objects since all unpinned objects between firstMobileObject
+ 	 and lastMobileObject must be forwarded.  Return if savedFirstFieldsSpace fills up."
  	manager allOldSpaceEntitiesFrom: anUnpinnedEntity to: firstMobileObject do:
  		[:o| | newTop |
  		 (o < firstMobileObject
  		  and: [manager isMarked: o]) ifTrue:
  			[(manager isPinned: o)
  				ifTrue: [self assert: (manager addressAfter: o) <= initialToFinger]
  				ifFalse:
  					[(newTop := savedFirstFieldsSpace top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
  						[firstMobileObject := savedFirstMobileObject.
  						 ^false]].
  					 self assert: (manager startOfObject: o) >= toFinger.
+ 					 toFinger := self forwardMobileObject: o to: toFinger savedFirstFieldPtr: newTop.
+ 					 savedFirstFieldsSpace top: newTop]].
- 					 manager
- 						longAt: newTop
- 							put: (manager fetchPointer: 0 ofObject: o);
- 						storePointerUnchecked: 0
- 							ofObject: o
- 								withValue: ((manager hasOverflowHeader: o)
- 												ifTrue: [toFinger + manager baseHeaderSize]
- 												ifFalse: [toFinger]).
- 					 savedFirstFieldsSpace top: newTop.
- 					 toFinger := toFinger + (manager bytesInObject: o).
- 					 lastMobileObject := o]].
  	firstMobileObject := savedFirstMobileObject.
  	nextFreeObject ifNil:
  		[^true].
  	self assert: nextFreeObject > lastMobileObject.
  	manager allOldSpaceEntitiesFrom: (manager objectAfter: lastMobileObject) to: nextFreeObject do:
  		[:o|
  		 self deny: ((manager isMarked: o) and: [(manager isPinned: o) not])].
+ 	savedFirstFreeObject := firstFreeObject.
  	firstFreeObject := nextFreeObject.
  	result := self planCompactSavingForwarders.
+ 	firstFreeObject := savedFirstFreeObject.
  	^result!

Item was changed:
  ----- Method: SpurPlanningCompactor>>continueUpdatePointersInMobileObjectsFrom:withTop: (in category 'compaction') -----
+ continueUpdatePointersInMobileObjectsFrom: anUnpinnedEntity withTop: initialTop
- continueUpdatePointersInMobileObjectsFrom: anUnpinnedEntity withTop: top
  	"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.
  	 Answer if the end of the heap was reached (savedFirstFieldsSpace has not overflowed)."
+ 	| result top savedFirstFreeObject savedFirstMobileObject nextFreeObject |
- 	| 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.
+ 	top := initialTop.
+ 	"Update the run of immobile objects to match the enumeration in continuePlanCompactSavingForwardersFrom:toFinger:."
+ 	manager allOldSpaceEntitiesFrom: anUnpinnedEntity to: firstMobileObject do:
+ 		[:o|
+ 		 (o < firstMobileObject
+ 		  and: [manager isMarked: o]) ifTrue:
+ 			[(manager isPinned: o)
+ 				ifTrue: [self updatePointersIn: o]
+ 				ifFalse:
+ 					[(top := top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
+ 						[^false].
+ 					 self updatePointersIn: o savedFirstFieldPointer: top]]].
  	firstMobileObject := savedFirstMobileObject.
  	nextFreeObject ifNil:
  		[^true].
+ 	savedFirstFreeObject := firstFreeObject.
  	firstFreeObject := nextFreeObject.
  	result := self updatePointersInMobileObjectsWithTop: top.
  	firstFreeObject := savedFirstFreeObject.
  	^result!

Item was changed:
  ----- Method: SpurPlanningCompactor>>copyAndUnmarkMobileObjectsWithTop: (in category 'compaction') -----
  copyAndUnmarkMobileObjectsWithTop: initialTop
  	"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 those in planCompactSavingForwarders and updatePointersInMobileObjects."
  
  	| toFinger top previousPin |
  	toFinger := manager startOfObject: firstFreeObject.
  	top := initialTop.
  	self deny: (manager isMarked: firstFreeObject).
  	manager allOldSpaceEntitiesForCompactingFrom: firstFreeObject do:
+ 		[:o|
- 		[:o| | availableSpace |
  		 self check: 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:
  						[| limit |
  						 limit := manager startOfObject: previousPin.
  						 manager addFreeChunkWithBytes: limit - toFinger at: toFinger.
  						 toFinger := manager addressAfter: previousPin.
  						 self assert: toFinger < (manager startOfObject: o)].
  					 previousPin := o]
  				ifFalse:
+ 					[| availableSpace bytes next |
- 					[| 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.
  						 next := manager objectStartingAt: toFinger.
  						 next >= o ifTrue:
+ 							[^self continueCopyAndUnmarkMobileObjectsFrom: o withTop: top - manager bytesPerOop].
- 							[^self continueCopyAndUnmarkMobileObjectsFrom: next withTop: top].
  						 previousPin := (manager isPinned: next) ifTrue: [next]].
+ 					 toFinger := self copyAndUnmarkObject: o to: toFinger firstField: (manager longAt: top)]]].
- 					 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>>copyAndUnmarkObject:to:firstField: (in category 'compaction') -----
  copyAndUnmarkObject: o to: toFinger firstField: firstField
  	"Copy the object to toFinger, clearing its mark bit and restoring its firstField, which was overwritten with a forwarding pointer.
  	 Answer the number of bytes in the object, including overflow header."
  	<inline: true>
  	| bytes numSlots destObj start |
  	numSlots := manager rawNumSlotsOf: o.
  	destObj := (manager objectWithRawSlotsHasOverflowHeader: numSlots)
  					ifTrue: [toFinger + manager baseHeaderSize]
  					ifFalse: [toFinger].
  	bytes := manager bytesInObject: o given: numSlots.
  	start := manager startOfObject: o given: numSlots.
  	manager
  		mem: toFinger asVoidPointer cp: start asVoidPointer y: bytes;
  		setIsMarkedOf: destObj to: false;
  		storePointerUnchecked: 0 ofObject: destObj withValue: firstField.
+ 	^toFinger + bytes!
- 	^bytes!

Item was added:
+ ----- Method: SpurPlanningCompactor>>forwardMobileObject:to:savedFirstFieldPtr: (in category 'private') -----
+ forwardMobileObject: o to: toFinger savedFirstFieldPtr: savedFirstFieldPtr
+ 	"Forward a mobile object to some new location, saving its first field through savedFirstFieldPtr.
+ 	 Don't use forward:to:; we dont want to alter the object in any way other than by setting the forwarding pointer."
+ 	<inline: true>
+ 	lastMobileObject := o.
+ 	manager
+ 		longAt: savedFirstFieldPtr
+ 			put: (manager fetchPointer: 0 ofObject: o);
+ 		storePointerUnchecked: 0
+ 			ofObject: o
+ 				withValue: ((manager hasOverflowHeader: o)
+ 								ifTrue: [toFinger + manager baseHeaderSize]
+ 								ifFalse: [toFinger]).
+ 	^toFinger + (manager bytesInObject: o)!

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 those in updatePointersInMobileObjects and copyAndUnmarkMobileObjects."
  
  	| toFinger top previousPin |
  	savedFirstFieldsSpace top < savedFirstFieldsSpace start ifTrue:
  		[self logPhase: 'planning...'].
  	toFinger := manager startOfObject: firstFreeObject.
  	top := savedFirstFieldsSpace top.
  	self deny: (manager isMarked: firstFreeObject).
  	manager allOldSpaceEntitiesFrom: firstFreeObject do:
  		[:o|
  		 self check: o.
  		 self assert: (previousPin isNil or: [toFinger < previousPin]).
  		 (manager isMarked: o) ifTrue:
  			[(manager isPinned: o)
  				ifTrue: "The empty gaps between two adjacent pinned objects (when not filled below) are freed."
  					[previousPin ifNotNil:
  						[self assert: (manager startOfObject: previousPin) - toFinger >= (manager allocationUnit * 2).
  						 toFinger := manager addressAfter: previousPin.
  						 self assert: toFinger < (manager startOfObject: o)].
  					 previousPin := o]
  				ifFalse:
  					[| availableSpace bytes next |
  					 (top := top + manager bytesPerOop) >= savedFirstFieldsSpace limit ifTrue:
  						[savedFirstFieldsSpace top: top - manager bytesPerOop.
  						 ^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 - manager bytesPerOop.
  							 ^self continuePlanCompactSavingForwardersFrom: o toFinger: toFinger].
  						 previousPin := (manager isPinned: next) ifTrue: [next]].
+ 					 toFinger := self forwardMobileObject: o to: toFinger savedFirstFieldPtr: top]]].
- 					 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>>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 |
  	self logPhase: 'updating pointers...'.
  	"If savedFirstFieldsSpace is empty there is nothing to do."
  	savedFirstFieldsSpace top < savedFirstFieldsSpace start ifTrue:
  		[^self].
+ 	self assert: (manager startOfObject: firstFreeObject) = mobileStart.
  	coInterpreter mapInterpreterOops.
  	self updatePointersInManagerHeapEntities.
  	self updatePointersInSurvivingObjects.
  	self updatePointersInInitialImmobileObjects.
  	onePass := self updatePointersInMobileObjectsWithTop: savedFirstFieldsSpace start - manager bytesPerOop.
  	onePass ifFalse:
  		[self updatePointersInObjectsOverflowingSavedFirstFieldsSpace]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>updatePointersInMobileObjectsWithTop: (in category 'compaction') -----
  updatePointersInMobileObjectsWithTop: initialTop
  	"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 := initialTop.
  	self deny: (manager isMarked: firstFreeObject).
  	manager allOldSpaceEntitiesFrom: firstFreeObject do:
  		[:o|
  		 self check: o.
  		 self assert: (previousPin isNil or: [toFinger < previousPin]).
  		 (manager isMarked: o) ifTrue:
  			[(manager isPinned: o)
  				ifTrue: "The empty gaps between two adjacent pinned objects (when not filled below) are freed."
  					[self updatePointersIn: o.
  					 previousPin ifNotNil:
  						[toFinger := manager addressAfter: previousPin].
  					 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: o withTop: top - manager bytesPerOop].
- 							[^self continueUpdatePointersInMobileObjectsFrom: next withTop: top].
  						 previousPin := (manager isPinned: next) ifTrue: [next]].
  					 self updatePointersIn: o savedFirstFieldPointer: top.
  					 toFinger := toFinger + (manager bytesInObject: o)]]].
  	^true!



More information about the Vm-dev mailing list