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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 3 03:19:29 UTC 2017


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

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

Name: VMMaker.oscog-eem.2065
Author: eem
Time: 2 January 2017, 7:18:35.467191 pm
UUID: 89e981a5-b811-4530-b15c-64ca8711340a
Ancestors: VMMaker.oscog-eem.2064

SpurPlanningCompactor:
Fix slip in continueCopyAndUnmarkMobileObjectsFrom:withTop:.
In all the enumerators, strengthen the previousPin asserts and ignore unmarked objects when skipping past previousPin.

Nuke a couple of unused methods.

Habe printEntity: print the state bits such as isMarked:, isRemembered: et al.

Simulator:
Remember to update CogVMSimulator>>close also.

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

Item was changed:
  ----- Method: CogVMSimulator>>close (in category 'initialization') -----
  close  "close any files that ST may have opened, etc"
+ 	pluginList do: [:assoc| | plugin | plugin := assoc value. plugin ~~ self ifTrue: [plugin close]]!
- 	pluginList do: [:plugin| plugin ~~ self ifTrue: [plugin close]]!

Item was added:
+ ----- Method: CogVMSimulator>>printHexnpnp: (in category 'debug printing') -----
+ printHexnpnp: anInteger
+ 	"Print n in hex, in the form '1234', unpadded"
+ 	traceOn ifTrue:
+ 		[transcript nextPutAll: ((anInteger ifNil: [0]) printStringBase: 16)]!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>printHexnpnp: (in category 'printing') -----
+ printHexnpnp: anInteger
+ 	coInterpreter transcript nextPutAll: (anInteger printStringBase: 16)!

Item was changed:
  ----- Method: SpurMemoryManager>>printEntity: (in category 'debug printing') -----
  printEntity: oop
  	<api>
+ 	| isObj |
+ 	isObj := false.
  	coInterpreter printHex: oop; space.
  	(self addressCouldBeObj: oop) ifFalse:
  		[^coInterpreter print: ((self isImmediate: oop) ifTrue: ['immediate'] ifFalse: ['unknown'])].
  	coInterpreter
  		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:
+ 				[isObj := true. 'object']]]]);
+ 		space; printHex: (self bytesInObject: oop); print: '/'; printNum: (self bytesInObject: oop).
+ 	isObj ifTrue:
+ 		[coInterpreter
+ 			space;
+ 			print: ((self formatOf: oop) <= 16rF ifTrue: ['f:0'] ifFalse: ['f:']);
+ 			printHexnp: (self formatOf: oop);
+ 			print: ((self isGrey: oop) ifTrue: [' g'] ifFalse: [' .']);
+ 			print: ((self isImmutable: oop) ifTrue: ['i'] ifFalse: ['.']);
+ 			print: ((self isMarked: oop) ifTrue: ['m'] ifFalse: ['.']);
+ 			print: ((self isPinned: oop) ifTrue: ['p'] ifFalse: ['.']);
+ 			print: ((self isRemembered: oop) ifTrue: ['r'] ifFalse: ['.'])].
+ 	coInterpreter cr!
- 				['object']]]]);
- 		space; printHex: (self bytesInObject: oop); print: '/'; printNum: (self bytesInObject: oop); cr!

Item was changed:
  ----- Method: SpurPlanningCompactor>>continueCopyAndUnmarkMobileObjectsFrom:withTop: (in category 'compaction') -----
  continueCopyAndUnmarkMobileObjectsFrom: anUnpinnedEntity withTop: initialTop
  	"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 |
  	self assert: (self oop: anUnpinnedEntity isLessThan: manager endOfMemory).
  	self deny: (manager isPinned: anUnpinnedEntity).
  	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: top)]]].
- 						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>>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|
  		 self check: o.
+ 		 self assert: (previousPin isNil or: [(manager isMarked: previousPin) and: [toFinger < previousPin]]).
- 		 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 |
  					 (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].
+ 						 previousPin := ((manager isMarked: next) and: [manager isPinned: next]) ifTrue: [next]].
- 						 previousPin := (manager isPinned: next) ifTrue: [next]].
  					 toFinger := self copyAndUnmarkObject: o to: toFinger firstField: (manager longAt: top)]]].
  	self freeFrom: toFinger upTo: manager endOfMemory previousPin: previousPin.
  	^true!

Item was removed:
- ----- Method: SpurPlanningCompactor>>numPointerSlotsWhileCompactingOf:savedFirstFieldPointer: (in category 'private') -----
- numPointerSlotsWhileCompactingOf: obj 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>
- 	| fmt contextSize numLiterals header |
- 	fmt := manager formatOf: obj.
- 	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."
  
  	| 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: [(manager isMarked: previousPin) and: [toFinger < previousPin]]).
- 		 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 isMarked: next) and: [manager isPinned: next]) ifTrue: [next]].
- 						 previousPin := (manager isPinned: next) ifTrue: [next]].
  					 toFinger := self forwardMobileObject: o to: toFinger savedFirstFieldPtr: top]]].
  	savedFirstFieldsSpace top: top.
  	^true!

Item was removed:
- ----- Method: SpurPlanningCompactor>>updatePointersFrom:to:in: (in category 'compaction') -----
- updatePointersFrom: start to: finish in: obj
- 	<inline: true>
- 	start to: finish do:
- 		[:i| | oop fwd |
- 		 oop := manager fetchPointer: i ofObject: obj.
- 		 ((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 storePointerUnchecked: i ofObject: obj withValue: fwd]]!

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

Item was added:
+ ----- Method: StackInterpreter>>printHexnpnp: (in category 'debug printing') -----
+ printHexnpnp: n
+ 	"Print n in hex, in the form '1234', unpadded"
+ 	self print: '%lx' f: (self cCoerceSimple: n to: #'unsigned long')!

Item was added:
+ ----- Method: StackInterpreterSimulator>>printHexnpnp: (in category 'debug printing') -----
+ printHexnpnp: anInteger
+ 	"Print n in hex, in the form '1234', unpadded"
+ 	traceOn ifTrue:
+ 		[transcript nextPutAll: ((anInteger ifNil: [0]) printStringBase: 16)]!



More information about the Vm-dev mailing list