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

commits at source.squeak.org commits at source.squeak.org
Tue Dec 27 20:24:32 UTC 2016


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

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

Name: VMMaker.oscog-eem.2053
Author: eem
Time: 27 December 2016, 12:23:37.587924 pm
UUID: 950c6120-20c1-45c9-a864-0abafd71fd83
Ancestors: VMMaker.oscog-eem.2052

Spur:
Move the attemptToShrink from fullGC to globalGarbageCollect so that it is included in lemming debugging.

Make checkHeapFreeSpaceIntegrity check totalFreeOldSpace and hence catch SpurPlannngCompactor not freeing a free object at the end of an already compacted heap.

Fix the free space leak checker invocations for the allocateSlots*InOldSpace:...  One cannot invoke the leak checker until the allocated object's header has been filled in.  Shows how long its been since the free space leak checker has been run :-/.

Fix a slip in the refactoring of initializeScan to use reinitializeScan.

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

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlotsForPinningInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsForPinningInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  Try and
  	 allocate in a segment that already includes pinned objects.  The header of the
  	 result will have been filled-in but not the contents."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes
  				   suchThat: [:f| (segmentManager segmentContainingObj: f) containsPinned].
  	chunk ifNil:
  		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
+ 		 chunk ifNil:
+ 			[^nil].
+ 		 (segmentManager segmentContainingObj: chunk) containsPinned: true].
- 		 chunk ifNotNil:
- 			[(segmentManager segmentContainingObj: chunk) containsPinned: true]].
- 	self checkFreeSpace: GCModeNewSpace.
- 	chunk ifNil:
- 		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self flag: #endianness.
  		 self longAt: chunk put: numSlots.
  		 self longAt: chunk + 4 put: self numSlotsMask << self numSlotsHalfShift.
  		 self long64At: chunk + self baseHeaderSize
  			 put: ((self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)
  					bitOr: 1 << self pinnedBitShift).
+ 		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self long64At: chunk
  		put: ((self headerForSlots: numSlots format: formatField classIndex: classIndex)
  					bitOr: 1 << self pinnedBitShift).
+ 	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlotsInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  The header
  	 will have been filled-in but not the contents.  If no memory is available answer nil."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
- 	self checkFreeSpace: GCModeNewSpace.
  	chunk ifNil:
  		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self flag: #endianness.
  		 self longAt: chunk put: numSlots.
  		 self longAt: chunk + 4 put: self numSlotsMask << self numSlotsHalfShift.
  		 self long64At: chunk + self baseHeaderSize
  			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
+ 		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self long64At: chunk put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
+ 	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlotsForPinningInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsForPinningInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  Try and
  	 allocate in a segment that already includes pinned objects.  The header of the
  	 result will have been filled-in but not the contents."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes
  				   suchThat: [:f| (segmentManager segmentContainingObj: f) containsPinned].
  	chunk ifNil:
+ 		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
+ 		 chunk ifNil:
+ 			[^nil].
+ 		 (segmentManager segmentContainingObj: chunk) containsPinned: true].
- 		[chunk := self allocateOldSpaceChunkOfBytes: totalBytes].
- 	self checkFreeSpace: GCModeNewSpace.
- 	chunk ifNil:
- 		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self longAt: chunk
  			put: numSlots + (self numSlotsMask << self numSlotsFullShift).
  		 self longAt: chunk + self baseHeaderSize
  			put: ((self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)
  					bitOr: 1 << self pinnedBitShift).
+ 		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self longAt: chunk
  		put: ((self headerForSlots: numSlots format: formatField classIndex: classIndex)
  				bitOr: 1 << self pinnedBitShift).
+ 	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlotsInOldSpace:bytes:format:classIndex: (in category 'allocation') -----
  allocateSlotsInOldSpace: numSlots bytes: totalBytes format: formatField classIndex: classIndex
  	"Answer the oop of a chunk of space in oldSpace with numSlots slots.  The header
  	 will have been filled-in but not the contents.  If no memory is available answer nil."
  	<var: #totalBytes type: #usqInt>
  	<inline: false>
  	| chunk |
  	chunk := self allocateOldSpaceChunkOfBytes: totalBytes.
- 	self checkFreeSpace: GCModeNewSpace.
  	chunk ifNil:
  		[^nil].
  	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  		[self longAt: chunk
  			put: numSlots + (self numSlotsMask << self numSlotsFullShift).
  		 self longAt: chunk + self baseHeaderSize
  			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
+ 		 self checkFreeSpace: GCModeNewSpace.
  		 ^chunk + self baseHeaderSize].
  	self longAt: chunk
  		put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
+ 	self checkFreeSpace: GCModeNewSpace.
  	^chunk!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapFreeSpaceIntegrity (in category 'debug support') -----
  checkHeapFreeSpaceIntegrity
  	"Perform an integrity/leak check using the heapMap.  Assume clearLeakMapAndMapAccessibleFreeSpace
  	 has set a bit at each free chunk's header.  Scan all objects in the heap checking that no pointer points
  	 to a free chunk and that all free chunks that refer to others refer to marked chunks.  Answer if all checks pass."
+ 	| ok total |
- 	| ok |
  	<inline: false>
+ 	<var: 'total' type: #usqInt>
  	ok := true.
+ 	total := 0.
- 
  	0 to: self numFreeLists - 1 do:
  		[:i|
  		(freeLists at: i) ~= 0 ifTrue:
  			[(heapMap heapMapAtWord: (self pointerForOop: (freeLists at: i))) = 0 ifTrue:
  				[coInterpreter print: 'leak in free list '; printNum: i; print: ' to non-free '; printHex: (freeLists at: i); cr.
  				 self eek.
  				 ok := false]]].
  
  	"Excuse the duplication but performance is at a premium and we avoid
  	 some tests by splitting the newSpace and oldSpace enumerations."
  	self allNewSpaceEntitiesDo:
  		[:obj| | fieldOop |
  		 (self isFreeObject: obj)
  			ifTrue:
  				[coInterpreter print: 'young object '; printHex: obj; print: ' is free'; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[0 to: (self numPointerSlotsOf: obj) - 1 do:
  					[:fi|
  					 fieldOop := self fetchPointer: fi ofObject: obj.
  					 (self isNonImmediate: fieldOop) ifTrue:
  						[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) ~= 0 ifTrue:
  							[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is free'; cr.
  							 self eek.
  							 ok := false]]]]].
  	self allOldSpaceEntitiesDo:
  		[:obj| | fieldOop |
  		(self isFreeObject: obj)
  			ifTrue:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' is unmapped?!! '; cr.
  					 self eek.
  					 ok := false].
  				 fieldOop := self fetchPointer: self freeChunkNextIndex ofFreeChunk: obj.
  				 (fieldOop ~= 0
  				 and: [(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0]) ifTrue:
  					[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ 0 = '; printHex: fieldOop; print: ' is unmapped'; cr.
  					 self eek.
  					 ok := false].
  				(self isLargeFreeObject: obj) ifTrue:
  					[self freeChunkParentIndex to: self freeChunkLargerIndex do:
  						[:fi|
  						 fieldOop := self fetchPointer: fi ofFreeChunk: obj.
  						 (fieldOop ~= 0
  						 and: [(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0]) ifTrue:
  							[coInterpreter print: 'leak in free chunk '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is unmapped'; cr.
  							 self eek.
+ 							 ok := false]]].
+ 				total := total + (self bytesInObject: obj)]
- 							 ok := false].]]]
  			ifFalse:
  				[0 to: (self numPointerSlotsOf: obj) - 1 do:
  					[:fi|
  					 fieldOop := self fetchPointer: fi ofObject: obj.
  					 (self isNonImmediate: fieldOop) ifTrue:
  						[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) ~= 0 ifTrue:
  							[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; print: ' is free'; cr.
  							 self eek.
  							 ok := false]]]]].
+ 	total ~= totalFreeOldSpace ifTrue:
+ 		[coInterpreter print: 'incorrect totalFreeOldSpace; expected '; printNum: totalFreeOldSpace; print: ' found '; printNum: total; cr.
+ 		 self eek.
+ 		 ok := false].
  	^ok!

Item was changed:
  ----- Method: SpurMemoryManager>>fullGC (in category 'gc - global') -----
  fullGC
  	"Perform a full lazy compacting GC.  Answer the size of the largest free chunk."
  	<returnTypeC: #usqLong>
  	<inline: #never> "for profiling"
  	needGCFlag := false.
  	gcStartUsecs := self ioUTCMicrosecondsNow.
  	statMarkCount := 0.
  	coInterpreter preGCAction: GCModeFull.
  	self globalGarbageCollect.
- 	self attemptToShrink.
  	coInterpreter postGCAction: GCModeFull.
  	statFullGCs := statFullGCs + 1.
  	statGCEndUsecs := self ioUTCMicrosecondsNow.
  	statFullGCUsecs := statFullGCUsecs + (statGCEndUsecs - gcStartUsecs).
  	^(freeLists at: 0) ~= 0
  		ifTrue: [self bytesInObject: self findLargestFreeChunk]
  		ifFalse: [0]!

Item was changed:
  ----- Method: SpurMemoryManager>>globalGarbageCollect (in category 'gc - global') -----
  globalGarbageCollect
  	<inline: true> "inline into fullGC"
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  
  	"Mark objects /before/ scavenging, to empty the rememberedTable of unmarked roots."
  	self markObjects: true.
  
  	scavenger forgetUnmarkedRememberedObjects.
  	self doScavenge: MarkOnTenure.
  
  	"Mid-way the leak check must be more lenient.  Unmarked classes will have been
  	 expunged from the table, but unmarked instances will not yet have been reclaimed."
  	self runLeakCheckerFor: GCModeFull
  		excludeUnmarkedObjs: true
  		classIndicesShouldBeValid: true.
  
  	segmentManager prepareForGlobalSweep. "for notePinned:"
  	compactor compact.
+ 	self attemptToShrink.
  	self setHeapSizeAtPreviousGC.
  
  	self assert: self validObjStacks.
  	self assert: (self isEmptyObjStack: markStack).
  	self assert: (self isEmptyObjStack: weaklingStack).
  	self assert: self allObjectsUnmarked.
  	self runLeakCheckerFor: GCModeFull!

Item was changed:
  ----- Method: SpurPlanningCompactor>>initializeScan (in category 'compaction') -----
  initializeScan
  	savedFirstFieldsSpace top: savedFirstFieldsSpace start - manager bytesPerOop.
+ 	firstFreeObject := manager hiddenRootsObject.
  	self reinitializeScan!



More information about the Vm-dev mailing list