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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 28 22:34:06 UTC 2019


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

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

Name: VMMaker.oscog-eem.2596
Author: eem
Time: 28 November 2019, 2:33:58.668671 pm
UUID: 8500baf3-a5ae-4594-9f3b-08cedfdf1fb3
Ancestors: VMMaker.oscog-cb.2595

Spur:
Make a minor refactoring to reinitializeScanFrom: to make it more readable (move assignment to firstMobileObject into scanForFirstFreeAndFirstMobileObjectFrom:).

Improve the ImageLeakChecker to bounds check objects while swizzling, and hence detect the damaged images produced by the issue 444 planning compactor bug as corrupted.

Refactor swizzleObj: to swizzleObj:in: so that ImageLeakChecker/SpurLeakCheckingSegmentManager can produce more informative diagnostics.

Improve the leak checker to first bounds check oops against the heap extent before probing the heap map.  This prevents ImageLeakChecker from crashing on issue 444 corrupted images.

=============== Diff against VMMaker.oscog-cb.2595 ===============

Item was added:
+ ----- Method: ImageLeakChecker class>>ancilliaryClasses (in category 'translation') -----
+ ancilliaryClasses
+ 	"Answer any extra classes to be included in the translation."
+ 	^super ancilliaryClasses, { SpurLeakCheckingSegmentManager }!

Item was changed:
  ----- Method: ImageLeakChecker class>>isAcceptableAncilliaryClass: (in category 'translation') -----
  isAcceptableAncilliaryClass: aClass
+ 	^aClass == CogStackPage
+ 	 or: [aClass == SpurLeakCheckingSegmentManager
+ 	 or: [self objectMemoryClass ancilliaryClasses includes: aClass]]!
- 	^aClass == CogStackPage or: [self objectMemoryClass ancilliaryClasses includes: aClass]!

Item was added:
+ ----- Method: ImageLeakChecker>>initializeInterpreter: (in category 'initialization') -----
+ initializeInterpreter: bytesToShift
+ 	objectMemory segmentManager noteValidHeapExtent: bytesToShift.
+ 	super initializeInterpreter: bytesToShift!

Item was changed:
  ----- Method: ImageLeakChecker>>main:_: (in category 'api') -----
  main: argc _: argv
  	<var: 'argc' type: #int>
  	<var: 'argv' declareC: 'char *argv[]'>
  	<returnTypeC: #int>
  	<api>
+ 	| forVersion argi ifh ok okSwizzle |
- 	| forVersion argi ifh ok |
  	<var: 'ifh' type: #'FILE *'>
  	argi := 1.
  	forVersion := false.
  	[argi < argc
  	 and: [((argv at: argi) at: 0) = $-]] whileTrue:
  		[(self strcmp: (self asCommandLineArgument: 'version') _: (argv at: argi)) = 0 ifTrue:
  			['%s\n' printf: (self cCode: 'interpreterVersion' inSmalltalk: ['don''t ask silly questions']).
  			 forVersion := true].
  		 (self strcmp: (self asCommandLineArgument: 'verbose') _: (argv at: argi)) = 0 ifTrue:
  			[verbose := true].
  		 argi := argi + 1].
  	(argc = argi and: [forVersion]) ifTrue:
  		[^0].
  
  	(argc ~= (argi + 1)
  	 or: [(ifh := self sqImageFileOpen: (argv at: argi) _: 'rb') = 0]) ifTrue:
  		['Usage: %s [%s] [%s] imageFileName\n' printf: {(argv at: 0). self asCommandLineArgument: 'verbose'. self asCommandLineArgument: 'version'}.
  		 ^self cCode: [1] inSmalltalk: [false]].
  
  	self readImageFromFile: ifh HeapSize: 0 StartingAt: 0.
  	self sqImageFileClose: ifh.
+ 	okSwizzle := objectMemory segmentManager detectedInvalidOop not.
  	ok := objectMemory runLeakCheckerForResult: GCModeFull.
+ 	(verbose and: [okSwizzle and: [ok]]) ifTrue:
- 	(verbose and: [ok]) ifTrue:
  		['Image %s is free of leaks\n' printf: {(argv at: argi)}].
  	^self cCode: [ok ifTrue: [0] ifFalse: [2]] inSmalltalk: [ok]!

Item was added:
+ ----- Method: ImageLeakChecker>>verbose (in category 'accessing') -----
+ verbose
+ 	^verbose!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>isInHeapBounds: (in category 'plugin support') -----
+ isInHeapBounds: address 
+ 	"Answer if the given address is within the entire range ST object memory.
+ 	 For quick checking during leak checking only!!"
+ 	^(self oop: address isGreaterThanOrEqualTo: memory)
+ 	  and: [self oop: address isLessThan: endOfMemory]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>isInHeapBounds: (in category 'plugin support') -----
+ isInHeapBounds: address 
+ 	"Answer if the given address is within the entire range ST object memory.
+ 	 For quick checking during leak checking only!!"
+ 	^(self oop: address isGreaterThanOrEqualTo: memory)
+ 	  and: [self oop: address isLessThan: endOfMemory]!

Item was added:
+ SpurSegmentManager subclass: #SpurLeakCheckingSegmentManager
+ 	instanceVariableNames: 'oldHeapBase oldHeapLimit detectedInvalidOop subsequentReport'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Utilities'!

Item was added:
+ ----- Method: SpurLeakCheckingSegmentManager>>detectedInvalidOop (in category 'accessing') -----
+ detectedInvalidOop
+ 	^detectedInvalidOop!

Item was added:
+ ----- Method: SpurLeakCheckingSegmentManager>>initialize (in category 'initialization') -----
+ initialize
+ 	super initialize.
+ 	detectedInvalidOop := false.
+ 	subsequentReport := false!

Item was added:
+ ----- Method: SpurLeakCheckingSegmentManager>>noteValidHeapExtent: (in category 'initialization') -----
+ noteValidHeapExtent: bytesToShift
+ 	oldHeapBase :=  manager memoryBaseForImageRead - bytesToShift.
+ 	oldHeapLimit := self lastSegment segStart + self lastSegment segSize - self lastSegment swizzle!

Item was added:
+ ----- Method: SpurLeakCheckingSegmentManager>>swizzleObj:in: (in category 'snapshot') -----
+ swizzleObj: objOop in: containerOopOrNil
+ 	<inline: false>
+ 	"Override to check that objOop is in bounds."
+ 	(self oop: objOop isGreaterThanOrEqualTo: oldHeapBase andLessThan: oldHeapLimit) ifFalse:
+ 		[manager coInterpreter verbose ifTrue:
+ 			[subsequentReport ifFalse:
+ 				['Swizzling:\n' printf.
+ 				 subsequentReport := true].
+ 			 containerOopOrNil
+ 				ifNil: ['Oop %p is out of bounds\n' printf: { objOop }]
+ 				ifNotNil: ['Oop %p is out of bounds at/in %p\n' printf: { objOop. containerOopOrNil - manager nilObject }]].
+ 		 detectedInvalidOop := true].
+ 	"And now swizzle inline"
+ 	numSegments - 1 to: 1 by: -1 do:
+ 		[:i|
+ 		objOop >= (segments at: i) segStart ifTrue:
+ 			[^objOop + (segments at: i) swizzle]].
+ 	^objOop + (segments at: 0) swizzle!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity:classIndicesShouldBeValid: (in category 'debug support') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: SpurMemoryManager>>checkOopIntegrity:named: (in category 'debug support') -----
  checkOopIntegrity: obj named: name
  	<inline: false>
  	<var: #name type: #'char *'>
+ 	((self oop: obj isLessThan: endOfMemory)
+ 	 and: [(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0]) ifTrue:
- 	(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0 ifTrue:
  		[^true].
  	coInterpreter print: name; print: ' leak '; printHex: obj; cr.
  	^false!

Item was changed:
  ----- Method: SpurMemoryManager>>checkOopIntegrity:named:index: (in category 'debug support') -----
  checkOopIntegrity: obj named: name index: i
  	<inline: false>
  	<var: #name type: #'char *'>
+ 	((self oop: obj isLessThan: endOfMemory)
+ 	 and: [(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0]) ifTrue:
- 	(heapMap heapMapAtWord: (self pointerForOop: obj)) ~= 0 ifTrue:
  		[^true].
  	coInterpreter print: name; print: ' leak @ '; printNum: i; print: ' = '; printHex: obj; cr.
  	^false!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeFreeSpacePostLoad: (in category 'snapshot') -----
  initializeFreeSpacePostLoad: freeListObj
  	"Reinitialize the free list info.  The freeLists object needs to be swizzled
  	 because its neither a free, nor a pointer object.  Free objects have already
  	 been swizzled in adjustAllOopsBy:"
  	
  	self assert: (self numSlotsOf: freeListObj) = self numFreeLists.
  	self assert: (self formatOf: freeListObj) = self wordIndexableFormat.
  	freeLists := self firstIndexableField: freeListObj.
  	freeListsMask := 0.
  	0 to: self numFreeLists - 1 do:
  		[:i|
  		(freeLists at: i) ~= 0 ifTrue:
  			[freeListsMask := freeListsMask bitOr: (1 << i).
+ 			 freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i) in: freeListObj)]]!
- 			 freeLists at: i put: (segmentManager swizzleObj: (freeLists at: i))]]!

Item was added:
+ ----- Method: SpurMemoryManager>>isInHeapBounds: (in category 'plugin support') -----
+ isInHeapBounds: address 
+ 	"Answer if the given address is within the entire range ST object memory.
+ 	 For quick checking during leak checking only!!"
+ 	^(self oop: address isGreaterThanOrEqualTo: newSpaceStart)
+ 	  and: [self oop: address isLessThan: endOfMemory]!

Item was changed:
  ----- Method: SpurMemoryManager>>swizzleFieldsOfFreeChunk: (in category 'snapshot') -----
  swizzleFieldsOfFreeChunk: chunk
  	<inline: true>
  	| field chunkBytes |
  	field := self fetchPointer: self freeChunkNextIndex ofFreeChunk: chunk.
  	field ~= 0 ifTrue:
  		[self storePointerNoAssert: self freeChunkNextIndex
  			ofFreeChunk: chunk
+ 			withValue: (segmentManager swizzleObj: field in: chunk)].
- 			withValue: (segmentManager swizzleObj: field)].
  	chunkBytes := self bytesInObject: chunk.
  	false ifTrue: "The prevPointer is not guaranteed to be valid in older images.
  				 updateListStartingAt: via updateFreeLists does restore the prev pointer
  				 in all small free lists, so simply avoid swizzling it now."
  		[(self isLilliputianSize: chunkBytes) ifFalse:
  			[field := self fetchPointer: self freeChunkPrevIndex ofFreeChunk: chunk.
  			 field ~= 0 ifTrue:
  				[self storePointerNoAssert: self freeChunkPrevIndex
  					ofFreeChunk: chunk
+ 					withValue: (segmentManager swizzleObj: field in: chunk)]]].
- 					withValue: (segmentManager swizzleObj: field)]]].
  	chunkBytes >= (self numFreeLists * self allocationUnit) ifTrue:
  		[self freeChunkParentIndex to: self freeChunkLargerIndex do:
  			[:index|
  			 field := self fetchPointer: index ofFreeChunk: chunk.
  			 field ~= 0 ifTrue:
  				[self storePointerNoAssert: index
  					ofFreeChunk: chunk
+ 					withValue: (segmentManager swizzleObj: field in: chunk)]]]!
- 					withValue: (segmentManager swizzleObj: field)]]]!

Item was changed:
  ----- Method: SpurMemoryManager>>swizzleFieldsOfObject: (in category 'snapshot') -----
  swizzleFieldsOfObject: oop
  	| fieldAddr fieldOop |
  	<inline: true>
  	fieldAddr := oop + (self lastPointerOfWhileSwizzling: oop).
  	[self oop: fieldAddr isGreaterThanOrEqualTo: oop + self baseHeaderSize] whileTrue:
  		[fieldOop := self longAt: fieldAddr.
  		 (self isNonImmediate: fieldOop) ifTrue:
+ 			[self longAt: fieldAddr put: (segmentManager swizzleObj: fieldOop in: oop)].
- 			[self longAt: fieldAddr put: (segmentManager swizzleObj: fieldOop)].
  		 fieldAddr := fieldAddr - self bytesPerOop]!

Item was changed:
  ----- Method: SpurMemoryManager>>swizzleObjStackAt: (in category 'obj stacks') -----
  swizzleObjStackAt: objStackRootIndex
  	"On load, swizzle the pointers in an obj stack. Answer the obj stack's oop."
  	| firstPage page stackOrNil index field |
  	firstPage := stackOrNil := self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj.
  	stackOrNil = nilObj ifTrue:
  		[^stackOrNil].
  	[self assert: (self numSlotsOfAny: stackOrNil) = ObjStackPageSlots.
  	 self assert: (self fetchPointer: ObjStackMyx ofObject: stackOrNil) = objStackRootIndex.
  	 "There are four fixed slots in an obj stack, and a Topx of 0 indicates empty, so
  	   if there were 5 slots in an oop stack, full would be 2, and the last 0-rel index is 4.
  	   Hence the last index is topx + fixed slots - 1, or topx + ObjStackNextx"
  	 index := (self fetchPointer: ObjStackTopx ofObject: stackOrNil) + ObjStackNextx.
  	 "swizzle fields including ObjStackNextx, excluding ObjStackFreex and leave field containing the next link."
  	 [field := self fetchPointer: index ofObject: stackOrNil.
  	  (field = 0 or: [self isImmediate: field]) ifFalse:
+ 		[field := segmentManager swizzleObj: field in: stackOrNil.
- 		[field := segmentManager swizzleObj: field.
  		 self storePointer: index ofObjStack: stackOrNil withValue: field].
  	  (index := index - 1) >= ObjStackNextx] whileTrue.
  	 (stackOrNil := field) ~= 0] whileTrue.
  	(stackOrNil := self fetchPointer: ObjStackFreex ofObject: firstPage) ~=  0 ifTrue:
  		[page := firstPage.
+ 		 [stackOrNil := segmentManager swizzleObj: stackOrNil in: firstPage.
- 		 [stackOrNil := segmentManager swizzleObj: stackOrNil.
  		  self storePointer: ObjStackFreex ofObjStack: page withValue: stackOrNil.
  		  page := stackOrNil.
  		  (stackOrNil := self fetchPointer: ObjStackFreex ofObject: page) ~=  0] whileTrue].
  	self assert: (self isValidObjStackAt: objStackRootIndex).
  	^self fetchPointer: objStackRootIndex ofObject: hiddenRootsObj!

Item was changed:
  ----- Method: SpurPlanningCompactor>>reinitializeScanFrom: (in category 'compaction') -----
  reinitializeScanFrom: initialObject
  	"Search for firstFreeObject and firstMobileObject from initialObject, which is the
  	 hiddenRootsObject on the first pass, and the objectAfterLastMobileObject on
  	 subsequent passes)."
- 	firstMobileObject := manager endOfMemory.
  	firstFreeObject := self scanForFirstFreeAndFirstMobileObjectFrom: initialObject.
  	firstFreeObject ifNotNil:
  		[mobileStart := manager startOfObject: firstFreeObject].
  	objectAfterLastMobileObject ifNotNil:
  		[manager allOldSpaceEntitiesFrom: firstFreeObject to: objectAfterLastMobileObject do:
  			[:o|
  			 ((manager isPinned: o)
  			  or: [(manager isMarked: o) not
  			  or: [objectAfterLastMobileObject = o]]) ifFalse:
  				[manager setIsMarkedOf: o to: false]].
  		 firstMobileObject := objectAfterLastMobileObject]!

Item was changed:
  ----- Method: SpurPlanningCompactor>>scanForFirstFreeAndFirstMobileObjectFrom: (in category 'compaction') -----
  scanForFirstFreeAndFirstMobileObjectFrom: initialObject
+ 	"Scan from initialObject, setting firstMobileObject to the first marked
+ 	 object after the first free object found, or endOfMemory if none is found.
+ 	 Answer the first free object found, or nil if none."
- 	"Scan from initialObject, setting firstMobileObject to the first marked object after
- 	 the first free object found. Answer the first free object found, or nil if none."
  	<inline: false>
  	| firstFree |
+ 	firstMobileObject := manager endOfMemory.
  	manager allOldSpaceEntitiesFrom: initialObject do:
  		[:o|
  		(manager isMarked: o)
  			ifTrue:
  				[firstFree ifNotNil:
  					[firstMobileObject := o.
  					 ^firstFree]]
  			ifFalse:
  				[firstFree ifNil:
  					[firstFree := o]]].
  	^firstFree!

Item was added:
+ ----- Method: SpurSegmentManager>>swizzleObj:in: (in category 'snapshot') -----
+ swizzleObj: objOop in: containerOrNil
+ 	"Hook for error reporting in SpurLeakCheckingSegmentManager"
+ 	<inline: #always>
+ 	^self swizzleObj: objOop!



More information about the Vm-dev mailing list