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

commits at source.squeak.org commits at source.squeak.org
Wed Dec 28 22:08:05 UTC 2016


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

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

Name: VMMaker.oscog-eem.2055
Author: eem
Time: 28 December 2016, 2:07:51.943529 pm
UUID: 5c451a9e-3c33-4788-9e7b-37f3156e6b27
Ancestors: VMMaker.oscog-eem.2054

SpurPlanningCompactor:
Continue correctly in the update and copyAndUnmark phases by adding a top parameter to hold the initial and/or continuing value of top.

Refactor updatePointersIn:startingAt:savedFirstFieldPointer: into two separate updatePointersIn: & updatePointersIn:savedFirstFieldPointer: methods, and move updating the savedFirstField into updatePointersIn:savedFirstFieldPointer:.

Log the phases.

General:
Fix a C compiler warning.

Sim:
Delete an unused method.

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

Item was changed:
  ----- Method: CoInterpreter>>ceSendMustBeBooleanTo:interpretingAtDelta: (in category 'trampolines') -----
  ceSendMustBeBooleanTo: aNonBooleanObject interpretingAtDelta: jumpSize
  	"For RegisterAllocatingCogit we want the address following a conditional branch not to be reachable, so we
  	 don't have to generate code to reload registers.  Instead simply convert to an interpreter frame,
  	 backup the pc to the branch, reenter the interpreter and hence retry the mustBeBoolean send therein."
  	<api>
  	| cogMethod methodObj methodHeader startBcpc |
  	<var: 'cogMethod' type: #'CogBlockMethod *'>
+ 	<var: 'p' type: #'char *'>
  	self assert: (objectMemory addressCouldBeOop: aNonBooleanObject).
  	cogMethod := self mframeCogMethod: framePointer.
  	((self mframeIsBlockActivation: framePointer)
  	 and: [cogMethod cmIsFullBlock not])
  		ifTrue:
  			[methodHeader := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod cmHomeMethod to: #'CogMethod *') methodObject.
  			 startBcpc := cogMethod startpc]
  		ifFalse:
  			[methodHeader := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodHeader.
  			 methodObj := (self cCoerceSimple: cogMethod to: #'CogMethod *') methodObject.
  			 startBcpc := self startPCOfMethod: methodObj].
  
  	"Map the machine code instructionPointer to the interpreter instructionPointer of the branch."
  	instructionPointer := self popStack.
  	instructionPointer := cogit bytecodePCFor: instructionPointer startBcpc: startBcpc in: cogMethod.
  	instructionPointer := methodObj + objectMemory baseHeaderSize + instructionPointer - jumpSize - 1. "pre-decrement"
  
  	"Make space for the two extra fields in an interpreter frame"
  	stackPointer to: framePointer + FoxMFReceiver by: objectMemory wordSize do:
  		[:p| | oop |
  		 oop := objectMemory longAt: p.
  		 objectMemory
  			longAt: p - objectMemory wordSize - objectMemory wordSize
  			put: (objectMemory longAt: p)].
  	stackPointer := stackPointer - objectMemory wordSize - objectMemory wordSize.
  	self push: aNonBooleanObject.
  	"Fill in the fields"
  	objectMemory
  		longAt: framePointer + FoxIFrameFlags
  			put: (self
  					encodeFrameFieldHasContext: (self mframeHasContext: framePointer)
  					isBlock: (self mframeIsBlockActivation: framePointer)
  					numArgs: cogMethod cmNumArgs);
  		longAt: framePointer + FoxIFSavedIP
  			put: 0;
  		longAt: framePointer + FoxMethod
  			put: methodObj.
  
  	"and now reenter the interpreter..."
  	self setMethod: methodObj methodHeader: methodHeader.
  	self siglong: reenterInterpreter jmp: ReturnToInterpreter.!

Item was removed:
- ----- Method: FilePluginSimulator>>primitiveFileRename (in category 'simulation') -----
- primitiveFileRename
- 	^interpreterProxy primitiveFileRename!

Item was changed:
  ----- Method: SpurMemoryManager>>formatFieldWidthShift (in category 'header format') -----
  formatFieldWidthShift
+ 	<cmacro>
  	"The format field contains 5 bits."
  	^5!

Item was changed:
  ----- Method: SpurMemoryManager>>greyBitShift (in category 'header format') -----
  greyBitShift
+ 	<cmacro>
  	"bit 2 of 3-bit field above format (little endian)"
  	^31!

Item was changed:
  ----- Method: SpurMemoryManager>>immutableBitShift (in category 'header format') -----
  immutableBitShift
+ 	<cmacro>
  	"bit 1 of 2-bit field above classIndex (little endian)"
  	^23!

Item was changed:
  ----- Method: SpurMemoryManager>>markedBitFullShift (in category 'header format') -----
  markedBitFullShift
+ 	<cmacro>
  	"bit 1 of 2-bit field above identityHash (little endian)"
  	^55!

Item was changed:
  ----- Method: SpurMemoryManager>>markedBitHalfShift (in category 'header format') -----
  markedBitHalfShift
+ 	<cmacro>
  	"bit 1 of 2-bit field above identityHash (little endian)"
  	^23!

Item was changed:
  ----- Method: SpurMemoryManager>>pinnedBitShift (in category 'header format') -----
  pinnedBitShift
+ 	<cmacro>
  	"bit 1 of 3-bit field above format (little endian)"
  	^30!

Item was changed:
  ----- Method: SpurMemoryManager>>printEntity: (in category 'debug printing') -----
  printEntity: oop
+ 	<api>
+ 	coInterpreter printHex: oop; space.
+ 	(self addressCouldBeObj: oop) ifFalse:
+ 		[^coInterpreter print: ((self isImmediate: oop) ifTrue: ['immediate'] ifFalse: ['unknown'])].
  	coInterpreter
- 		printHex: oop; print: '/'; printNum: oop; space;
  		print: ((self isFreeObject: oop) ifTrue: ['free'] ifFalse:
  				[(self isSegmentBridge: oop) ifTrue: ['bridge'] ifFalse:
  				[(self isForwarded: oop) ifTrue: ['forwarder'] ifFalse:
+ 				[(self classIndexOf: oop) <= self lastClassIndexPun ifTrue: ['pun/obj stack'] ifFalse:
+ 				['object']]]]);
- 				['object']]]);
  		space; printHex: (self bytesInObject: oop); print: '/'; printNum: (self bytesInObject: oop); cr!

Item was removed:
- ----- 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.
- 	 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.
- 	^result!

Item was added:
+ ----- Method: SpurPlanningCompactor>>continueCopyAndUnmarkMobileObjectsFrom:withTop: (in category 'compaction') -----
+ 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 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 copyAndUnmarkMobileObjectsWithTop: top.
+ 	firstFreeObject := savedFirstFreeObject.
+ 	^result!

Item was removed:
- ----- 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.
- 	 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.
- 	^result!

Item was added:
+ ----- Method: SpurPlanningCompactor>>continueUpdatePointersInMobileObjectsFrom:withTop: (in category 'compaction') -----
+ 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 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 updatePointersInMobileObjectsWithTop: top.
+ 	firstFreeObject := savedFirstFreeObject.
+ 	^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 logPhase: 'copying and unmarking...'.
  	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 copyAndUnmarkMobileObjectsWithTop: savedFirstFieldsSpace start - manager bytesPerOop.
- 	onePass := self copyAndUnmarkMobileObjects.
  	onePass ifFalse:
  		[self unmarkObjectsOverflowingSavedFirstFieldsSpace]!

Item was removed:
- ----- 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:
- 		[: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 added:
+ ----- 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| | availableSpace |
+ 		 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:
+ 					[| 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: next withTop: top].
+ 						 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>>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)
- 	 destObj := (manager objectWithRawSlotsHasOverflowHeader: numSlots)
  					ifTrue: [toFinger + manager baseHeaderSize]
  					ifFalse: [toFinger].
+ 	bytes := manager bytesInObject: o given: numSlots.
+ 	start := manager startOfObject: o given: numSlots.
+ 	manager
- 	 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.
  	^bytes!

Item was added:
+ ----- Method: SpurPlanningCompactor>>logPhase: (in category 'private') -----
+ logPhase: phaseName
+ 	<inline: true>
+ 	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: phaseName; flush].!

Item was added:
+ ----- Method: SpurPlanningCompactor>>numPointerSlotsWhileCompactingOf:withFormat:savedFirstFieldPointer: (in category 'private') -----
+ numPointerSlotsWhileCompactingOf: obj withFormat: fmt savedFirstFieldPointer: firstFieldPtrOrNil
+ 	"This is a version of SpurMemoryManager>>numPointerSlotsOf: that deals with the
+ 	 possibility of obj being a CompiledMethod whose header is in savedFirstFieldsSpace.
+ 	 Answer the number of pointer fields in the given object.
+ 	 Works with CompiledMethods, as well as ordinary objects."
+ 	<inline: true>
+ 	| contextSize numLiterals header |
+ 	fmt <= manager lastPointerFormat ifTrue:
+ 		[(fmt = manager indexablePointersFormat
+ 		  and: [manager isContextNonImm: obj]) ifTrue:
+ 			["contexts end at the stack pointer"
+ 			contextSize := coInterpreter fetchStackPointerOf: obj.
+ 			^CtxtTempFrameStart + contextSize].
+ 		^manager numSlotsOf: obj  "all pointers"].
+ 	self deny: fmt = manager forwardedFormat.
+ 	fmt < manager firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
+ 
+ 	"CompiledMethod: contains both pointers and bytes"
+ 	self assert: firstFieldPtrOrNil notNil == (self isMobile: obj).
+ 	header := firstFieldPtrOrNil
+ 				ifNil: [manager methodHeaderOf: obj]
+ 				ifNotNil: [manager methodHeaderFromSavedFirstField: (manager longAt: firstFieldPtrOrNil)].
+ 	numLiterals := manager literalCountOfMethodHeader: header.
+ 	^numLiterals + LiteralStart!

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."
- 	 This enumeration matches that 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 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."
- 				ifTrue:
  					[previousPin ifNotNil:
+ 						[self assert: (manager startOfObject: previousPin) - toFinger >= (manager allocationUnit * 2).
+ 						 toFinger := manager addressAfter: previousPin.
+ 						 self assert: toFinger < (manager startOfObject: o)].
- 						[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>>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].
  	coInterpreter mapInterpreterOops.
  	self updatePointersInManagerHeapEntities.
  	self updatePointersInSurvivingObjects.
  	self updatePointersInInitialImmobileObjects.
+ 	onePass := self updatePointersInMobileObjectsWithTop: savedFirstFieldsSpace start - manager bytesPerOop.
- 	onePass := self updatePointersInMobileObjects.
  	onePass ifFalse:
  		[self updatePointersInObjectsOverflowingSavedFirstFieldsSpace]!

Item was added:
+ ----- Method: SpurPlanningCompactor>>updatePointersIn: (in category 'compaction') -----
+ updatePointersIn: obj
+ 	"Sweep the pointer fields in obj, updating all references to mobile objects to their eventual locations."
+ 	<inline: true>
+ 	| numPointerSlots |
+ 	numPointerSlots := manager numPointerSlotsOf: obj.
+ 	0 to: numPointerSlots - 1 do:
+ 		[:i| | oop fwd |
+ 		 oop := manager fetchPointer: i ofObject: obj.
+ 		 ((manager isNonImmediate: oop) and: [self isMobile: oop]) ifTrue:
+ 			[self assert: ((manager isMarked: oop) or: [obj = manager hiddenRootsObject]).
+ 			 fwd := manager fetchPointer: 0 ofObject: oop.
+ 			 self assert: (self isPostMobile: fwd).
+ 			 manager storePointerUnchecked: i ofObject: obj withValue: fwd]]!

Item was added:
+ ----- Method: SpurPlanningCompactor>>updatePointersIn:savedFirstFieldPointer: (in category 'compaction') -----
+ updatePointersIn: obj savedFirstFieldPointer: firstFieldPtrOrNil
+ 	"Sweep the pointer fields in obj, updating all references to mobile objects to their eventual locations.
+ 	 firstFieldPtrOrNil is supplied for mobile objects so that the saved first field can be updated, and so that
+ 	 the first field of a compiled method (which is its header, or reference to a CogMethod holding its header)
+ 	 can be retrieved."
+ 	<inline: false>
+ 	| fmt numPointerSlots |
+ 	fmt := manager formatOf: obj.
+ 	numPointerSlots := self numPointerSlotsWhileCompactingOf: obj withFormat: fmt savedFirstFieldPointer: firstFieldPtrOrNil.
+ 	(fmt <= manager lastPointerFormat "excludes CompiledMethod"
+ 	 and: [numPointerSlots > 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: firstFieldPtrOrNil.
+ 		 ((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: firstFieldPtrOrNil put: fwd]].
+ 	1 to: numPointerSlots - 1 do:
+ 		[:i| | oop fwd |
+ 		 oop := manager fetchPointer: i ofObject: obj.
+ 		 ((manager isNonImmediate: oop) and: [self isMobile: oop]) ifTrue:
+ 			[self assert: ((manager isMarked: oop) or: [obj = manager hiddenRootsObject]).
+ 			 fwd := manager fetchPointer: 0 ofObject: oop.
+ 			 self assert: (self isPostMobile: fwd).
+ 			 manager storePointerUnchecked: i ofObject: obj withValue: fwd]]!

Item was removed:
- ----- Method: SpurPlanningCompactor>>updatePointersIn:startingAt:savedFirstFieldPointer: (in category 'compaction') -----
- updatePointersIn: obj startingAt: startIndex savedFirstFieldPointer: firstFieldPtrOrNil
- 	"Sweep the pointer fields in obj, updating all references to mobile objects to their eventual locations.
- 	 firstFieldPtrOrNil is supplied for mobile objects so that the first field of a compiled method (which is
- 	 its header, or reference to a CogMethod holding its header) can be retrieved."
- 	<inline: true>
- 	startIndex to: (self numPointerSlotsWhileCompactingOf: obj savedFirstFieldPointer: firstFieldPtrOrNil) - 1 do:
- 		[:i| | oop fwd |
- 		 oop := manager fetchPointer: i ofObject: obj.
- 		 ((manager isNonImmediate: oop) and: [self isMobile: oop]) ifTrue:
- 			[self assert: ((manager isMarked: oop) or: [obj = manager hiddenRootsObject]).
- 			 fwd := manager fetchPointer: 0 ofObject: oop.
- 			 self assert: (self isPostMobile: fwd).
- 			 manager storePointerUnchecked: i ofObject: obj withValue: fwd]]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>updatePointersInInitialImmobileObjects (in category 'compaction') -----
  updatePointersInInitialImmobileObjects
  	"Sweep the initial immobile heap, updating all references to mobile objects to their eventual locations."
  	manager allOldSpaceObjectsFrom: manager firstObject do:
  		[:o|
  		o >= firstFreeObject ifTrue:
  			[^self].
  		self assert: (manager isMarked: o).
+ 		self updatePointersIn: o]!
- 		self updatePointersIn: o startingAt: 0 savedFirstFieldPointer: nil]!

Item was removed:
- ----- 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:
- 		[: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!

Item was added:
+ ----- 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 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: next withTop: top].
+ 						 previousPin := (manager isPinned: next) ifTrue: [next]].
+ 					 self updatePointersIn: o savedFirstFieldPointer: top.
+ 					 toFinger := toFinger + (manager bytesInObject: o)]]].
+ 	^true!

Item was added:
+ ----- Method: SpurPlanningCompactor>>updatePointersInObjectsOverflowingSavedFirstFieldsSpace (in category 'compaction') -----
+ updatePointersInObjectsOverflowingSavedFirstFieldsSpace
+ 	"Sweep the final immobile heap, is any (those objects with no room in savedFirstFieldsSpace
+ 	 in the current pass) updating all references to mobile objects to their eventual locations."
+ 	manager allOldSpaceObjectsFrom: (manager objectAfter: lastMobileObject) do:
+ 		[:o|
+ 		self assert: (manager isMarked: o).
+ 		self updatePointersIn: o]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>updatePointersInSurvivingObjects (in category 'compaction') -----
  updatePointersInSurvivingObjects
  	"Sweep pastSpace, updating all references to mobile objects to their eventual locations."
  	manager allPastSpaceObjectsDo:
  		[:o|
  		self assert: (manager isMarked: o).
+ 		self updatePointersIn: o]!
- 		self updatePointersIn: o startingAt: 0 savedFirstFieldPointer: nil]!



More information about the Vm-dev mailing list