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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 27 02:05:53 UTC 2014


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

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

Name: VMMaker.oscog-eem.623
Author: eem
Time: 26 February 2014, 6:02:33.618 pm
UUID: 5d6a7bff-2bb3-4294-94d1-eaea186d01f0
Ancestors: VMMaker.oscog-eem.622

Spur:
Remember to invoke markAndTraceOrFreeMachineCode: in
the mark phase of full GC.

Add classOrNilAtIndex: and use it in places where a nil return is
unacceptable (fetchClassOf:, especially for isLKindOfClass: when
given garbage in printOop:).

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

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity: (in category 'debug support') -----
  checkHeapIntegrity: excludeUnmarkedNewSpaceObjs
  	"Perform an integrity/leak check using the heapMap.  Assume
  	 clearLeakMapAndMapAccessibleObjects has set a bit at each
  	 object's header.  Scan all objects in the heap checking that every
  	 pointer points to a header.  Scan the rootTable, remapBuffer and
  	 extraRootTable checking that every entry is a pointer to a header.
  	 Check that the number of roots is correct and that all rootTable
  	 entries have their rootBit set. Answer if all checks pass."
  	| ok numRememberedRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedRootsInHeap := 0.
  	self allHeapEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		((self isFreeObject: obj)
  		 or: [(self isYoungObject: obj) and: [(self isMarked: obj) not and: [excludeUnmarkedNewSpaceObjs]]]) ifFalse:
  			[containsYoung := false.
  			 (self isRemembered: obj) ifTrue:
  				[numRememberedRootsInHeap := numRememberedRootsInHeap + 1.
  				 (scavenger isInRememberedSet: obj) ifFalse:
  					[coInterpreter print: 'remembered object '; printHex: obj; print: ' is not in remembered table'; cr.
  					 self eek.
  					 ok := false]].
  			 (self isForwarded: obj)
  				ifTrue:
  					[fieldOop := self fetchPointer: 0 ofMaybeForwardedObject: obj.
  					 (heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  						[coInterpreter print: 'object leak in forwarder '; printHex: obj; print: ' to unmapped '; printHex: fieldOop; cr.
  						 self eek.
  						 ok := false].
  					 (self isYoung: fieldOop) ifTrue:
  						[containsYoung := true]]
  				ifFalse:
+ 					[classOop := self classOrNilAtIndex: (classIndex := self classIndexOf: obj).
+ 					 (classOop = nilObj
- 					[classOop := self classAtIndex: (classIndex := self classIndexOf: obj).
- 					 ((classOop isNil or: [classOop = nilObj])
  					  and: [(self isHiddenObj: obj) not]) ifTrue:
  						[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; print: (classOop ifNil: ['nil'] ifNotNil: ['nilObj']); cr.
  						 self eek.
  						 ok := false].
  					 self baseHeaderSize to: (self lastPointerOf: obj) by: BytesPerOop do:
  						[:ptr|
  						 fieldOop := self longAt: obj + ptr.
  						 (self isNonImmediate: fieldOop) ifTrue:
  							[| fi |
  							 fi := ptr - self baseHeaderSize / self wordSize.
  							 (fieldOop bitAnd: self wordSize - 1) ~= 0
  								ifTrue:
  									[coInterpreter print: 'misaligned oop in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  									 self eek.
  									 ok := false]
  								ifFalse:
  									[(heapMap heapMapAtWord: (self pointerForOop: fieldOop)) = 0 ifTrue:
  										[coInterpreter print: 'object leak in '; printHex: obj; print: ' @ '; printNum: fi; print: ' = '; printHex: fieldOop; cr.
  										 self eek.
  										 ok := false].
  									 "don't be misled by CogMethods; they appear to be young, but they're not"
  									 ((self isYoung: fieldOop)
  									  and: [self oop: fieldOop isGreaterThanOrEqualTo: newSpaceStart]) ifTrue:
  										[containsYoung := true]]]]].
  					(containsYoung and: [(self isYoung: obj) not]) ifTrue:
  						[(self isRemembered: obj) ifFalse:
  							[coInterpreter print: 'unremembered object '; printHex: obj; print: ' contains young oop(s)'; cr.
  							 self eek.
  							 ok := false]]]].
  	numRememberedRootsInHeap ~= scavenger rememberedSetSize ifTrue:
  		[coInterpreter
  			print: 'root count mismatch. #heap roots ';
  			printNum: numRememberedRootsInHeap;
  			print: '; #roots ';
  			printNum: scavenger rememberedSetSize;
  			cr.
  		self eek.
  		"But the system copes with overflow..."
  		self flag: 'no support for remembered set overflow yet'.
  		"ok := rootTableOverflowed and: [needGCFlag]"].
  	scavenger rememberedSetWithIndexDo:
  		[:obj :i|
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned oop in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0
  					ifTrue:
  						[coInterpreter print: 'object leak in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  						 self eek.
  						 ok := false]
  					ifFalse:
  						[(self isYoung: obj) ifTrue:
  							[coInterpreter print: 'non-root in remembered set @ '; printNum: i; print: ' = '; printHex: obj; cr.
  							 self eek.
  							 ok := false]]]].
  	1 to: remapBufferCount do:
  		[:ri| | obj |
  		obj := remapBuffer at: ri.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned remapRoot @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in remapRoots @ '; printNum: ri; print: ' = '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	1 to: extraRootCount do:
  		[:ri| | obj |
  		obj := (extraRoots at: ri) at: 0.
  		(obj bitAnd: self wordSize - 1) ~= 0
  			ifTrue:
  				[coInterpreter print: 'misaligned extraRoot @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  				 self eek.
  				 ok := false]
  			ifFalse:
  				[(heapMap heapMapAtWord: (self pointerForOop: obj)) = 0 ifTrue:
  					[coInterpreter print: 'object leak in extraRoots @ '; printNum: ri; print: ' => '; printHex: obj; cr.
  					 self eek.
  					 ok := false]]].
  	^ok!

Item was added:
+ ----- Method: SpurMemoryManager>>classOrNilAtIndex: (in category 'class table') -----
+ classOrNilAtIndex: classIndex
+ 	<api>
+ 	| classTablePage |
+ 	self assert: (classIndex <= self tagMask or: [classIndex >= self arrayClassIndexPun]).
+ 	classTablePage := self fetchPointer: classIndex >> self classTableMajorIndexShift
+ 							ofObject: hiddenRootsObj.
+ 	classTablePage = nilObj ifTrue:
+ 		[^nilObj].
+ 	^self
+ 		fetchPointer: (classIndex bitAnd: self classTableMinorIndexMask)
+ 		ofObject: classTablePage!

Item was changed:
  ----- Method: SpurMemoryManager>>fetchClassOfNonImm: (in category 'object access') -----
  fetchClassOfNonImm: objOop
  	| classIndex |
  	classIndex := self classIndexOf: objOop.
  	classIndex = self classIsItselfClassIndexPun ifTrue:
  		[^objOop].
  	self assert: classIndex >= self arrayClassIndexPun.
+ 	^self classOrNilAtIndex: classIndex!
- 	^self classAtIndex: classIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>markAccessibleObjects (in category 'gc - global') -----
  markAccessibleObjects
  	self assert: self validClassTableRootPages.
  	self assert: segmentManager allBridgesMarked.
  	self cCode: [] "for debugging markAndTrace: set (MarkStackRecord := OrderedCollection new)"
  		inSmalltalk: [MarkStackRecord ifNotNil: [MarkStackRecord resetTo: 1]].
  
  	marking := true.
  	"This must come first to enable stack page reclamation.  It clears
  	  the trace flags on stack pages and so must preceed any marking.
  	  Otherwise it will clear the trace flags of reached pages."
  	coInterpreter initStackPageGC.
  	self markAndTraceHiddenRoots.
  	self markAndTraceExtraRoots.
  	self assert: self validClassTableRootPages.
  	coInterpreter markAndTraceInterpreterOops: true.
+ 	coInterpreter markAndTraceOrFreeMachineCode: true.
  	self assert: self validObjStacks.
  	self markWeaklingsAndMarkAndFireEphemerons.
  	self assert: self validObjStacks.
  	marking := false!

Item was changed:
  ----- Method: SpurMemoryManager>>markAndTraceClassOf: (in category 'gc - global') -----
  markAndTraceClassOf: objOop
  	"Ensure the class of the argument is marked, pushing it on the markStack if not already marked.
  	 Also set the relevant bit in the classTableBitmap so that duplicate entries can be eliminated.
  	 Note that this is recursive, but the metaclass chain should terminate quickly."
  	<inline: false>
  	| classIndex classObj |
  	classIndex := self classIndexOf: objOop.
  	self inClassTableBitmapSet: classIndex.
+ 	classObj := self classOrNilAtIndex: classIndex.
- 	classObj := self classAtIndex: classIndex.
  	(self isMarked: classObj) ifFalse:
  		[self setIsMarkedOf: classObj to: true.
  		 self markAndTraceClassOf: classObj.
  		 self push: classObj onObjStack: markStack]!



More information about the Vm-dev mailing list