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

commits at source.squeak.org commits at source.squeak.org
Tue Oct 15 16:31:15 UTC 2013


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

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

Name: VMMaker.oscog-eem.458
Author: eem
Time: 15 October 2013, 9:28:28.547 am
UUID: fa66f078-056e-4da5-8926-9c2bf3f64282
Ancestors: VMMaker.oscog-eem.457

Define isGrey:,isImmutable:,isMarked: bits.
Define newSpaceRefCountMask.
Rename isInRememberedTable: to isInRememberedSet:.
Implement [check]OkayOop: (with addressCouldBeObjWhileScavenging:
for support).
More missing protocol.

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

Item was added:
+ ----- Method: Spur32BitMemoryManager>>isMarked: (in category 'header access') -----
+ isMarked: objOop
+ 	self flag: #endianness.
+ 	^((self longAt: objOop + 4) >> self markedBitHalfShift bitAnd: 1) ~= 0!

Item was changed:
+ ----- Method: Spur32BitMemoryManager>>isWordsNonImm: (in category 'object testing') -----
- ----- Method: Spur32BitMemoryManager>>isWordsNonImm: (in category 'header access') -----
  isWordsNonImm: objOop
  	"Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
  
  	^(self formatOf: objOop) = self firstLongFormat!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>setIsGreyOf:to: (in category 'header access') -----
+ setIsGreyOf: objOop to: aBoolean
+ 	self flag: #endianness.
+ 	self longAt: objOop
+ 		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop) bitOr: 1 << self greyBitShift]
+ 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self greyBitShift) bitInvert32])!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>setIsImmutableOf:to: (in category 'header access') -----
+ setIsImmutableOf: objOop to: aBoolean
+ 	self flag: #endianness.
+ 	self longAt: objOop
+ 		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop) bitOr: 1 << self immutableBitShift]
+ 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self immutableBitShift) bitInvert32])!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>setIsMarkedOf:to: (in category 'header access') -----
+ setIsMarkedOf: objOop to: aBoolean
+ 	self flag: #endianness.
+ 	self longAt: objOop + 4
+ 		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop) bitOr: 1 << self markedBitHalfShift]
+ 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self markedBitHalfShift) bitInvert32])!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>isMarked: (in category 'header access') -----
+ isMarked: objOop
+ 	^((self longAt: objOop) >> self markedBitFullShift bitAnd: 1) ~= 0!

Item was changed:
+ ----- Method: Spur64BitMemoryManager>>isWordsNonImm: (in category 'object testing') -----
- ----- Method: Spur64BitMemoryManager>>isWordsNonImm: (in category 'header access') -----
  isWordsNonImm: objOop
  	"Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
  
  	^(self formatOf: objOop) between: self firstLongFormat and: self firstLongFormat + 1!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>setIsGreyOf:to: (in category 'header access') -----
+ setIsGreyOf: objOop to: aBoolean
+ 	self longAt: objOop
+ 		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop) bitOr: 1 << self greyBitShift]
+ 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self greyBitShift) bitInvert64])!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>setIsImmutableOf:to: (in category 'header access') -----
+ setIsImmutableOf: objOop to: aBoolean
+ 	self longAt: objOop
+ 		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop) bitOr: 1 << self immutableBitShift]
+ 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self immutableBitShift) bitInvert64])!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>setIsMarkedOf:to: (in category 'header access') -----
+ setIsMarkedOf: objOop to: aBoolean
+ 	self longAt: objOop
+ 		put: (aBoolean
+ 				ifTrue: [(self longAt: objOop) bitOr: 1 << self markedBitFullShift]
+ 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self markedBitFullShift) bitInvert64])!

Item was added:
+ ----- Method: SpurGenerationScavenger>>isInRememberedSet: (in category 'store check') -----
+ isInRememberedSet: objOop
+ 	0 to: rememberedSetSize - 1 do:
+ 		[:i|
+ 		(rememberedSet at: i) = objOop ifTrue:
+ 			[^true]].
+ 	^false!

Item was removed:
- ----- Method: SpurGenerationScavenger>>isInRememberedTable: (in category 'store check') -----
- isInRememberedTable: objOop
- 	0 to: rememberedSetSize - 1 do:
- 		[:i|
- 		(rememberedSet at: i) = objOop ifTrue:
- 			[^true]].
- 	^false!

Item was added:
+ ----- Method: SpurMemoryManager>>addFreeSubTree: (in category 'free space') -----
+ addFreeSubTree: freeTree
+ 	"Add a freeChunk sub tree back into the large free chunk tree.
+ 	 This is for allocateOldSpaceChunkOf[Exactly]Bytes:."
+ 	<returnTypeC: #void>
+ 	| slotsInArg treeNode slotsInNode subNode |
+ 	slotsInArg := self numSlotsOfAny: freeTree.
+ 	self assert: slotsInArg / (self allocationUnit / self wordSize) >= self numFreeLists.
+ 	treeNode := freeLists at: 0.
+ 	self assert: treeNode ~= 0.
+ 	[slotsInNode := self numSlotsOfAny: treeNode.
+ 	 self assert: slotsInArg ~= slotsInNode.
+ 	 slotsInNode > slotsInArg
+ 		ifTrue:
+ 			[subNode := self fetchPointer: self freeChunkSmallerIndex ofFreeChunk: treeNode.
+ 			 subNode = 0 ifTrue:
+ 				[self storePointer: self freeChunkSmallerIndex ofFreeChunk: treeNode withValue: freeTree.
+ 				 ^self]]
+ 		ifFalse:
+ 			[subNode := self fetchPointer: self freeChunkLargerIndex ofFreeChunk: treeNode.
+ 			 subNode = 0 ifTrue:
+ 				[self storePointer: self freeChunkLargerIndex ofFreeChunk: treeNode withValue: freeTree.
+ 				 ^self]].
+ 	 treeNode := subNode] repeat!

Item was added:
+ ----- Method: SpurMemoryManager>>addressCouldBeObjWhileScavenging: (in category 'debug support') -----
+ addressCouldBeObjWhileScavenging: address
+ 	^(address bitAnd: self baseHeaderSize - 1) = 0
+ 	  and: [(self isInOldSpace: address)
+ 		or: [(self isInEden: address)
+ 		or: [(self isInSurvivorSpace: address)
+ 		or: [scavengeInProgress and: [self isInFutureSpace: address]]]]]!

Item was added:
+ ----- Method: SpurMemoryManager>>become:with: (in category 'plugin support') -----
+ become: array1 with: array2
+ 	<api>
+ 	^self become: array1 with: array2 twoWay: true copyHash: true!

Item was changed:
  ----- Method: SpurMemoryManager>>checkHeapIntegrity (in category 'debug support') -----
  checkHeapIntegrity
  	"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."
  	| prevObj prevPrevObj ok numRememberedRootsInHeap |
  	<inline: false>
  	ok := true.
  	numRememberedRootsInHeap := 0.
  	self allHeapEntitiesDo:
  		[:obj| | containsYoung fieldOop classIndex classOop |
  		(self isFreeObject: obj) ifFalse:
  			[containsYoung := false.
  			 (self isRemembered: obj) ifTrue:
  				[numRememberedRootsInHeap := numRememberedRootsInHeap + 1.
+ 				 (scavenger isInRememberedSet: obj) ifFalse:
- 				 (scavenger isInRememberedTable: 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 classAtIndex: (classIndex := self classIndexOf: obj).
  					 ((classOop isNil or: [classOop = nilObj])
  					  and: [obj ~= self freeListsObject]) 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: [fieldOop >= startOfMemory]) 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]]].
  		prevPrevObj := prevObj.
  		prevObj := obj].
  	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 rootTable @ '; 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]]]].
  	self flag: 'no support for remap buffer yet'.
  	"1 to: remapBufferCount do:
  		[:ri|
  		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]]]."
  	self flag: 'no support for extraRoots yet'.
  	"1 to: extraRootCount do:
  		[:ri|
  		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>>checkOkayOop: (in category 'debug support') -----
+ checkOkayOop: oop
+ 	"Verify that the given oop is legitimate. Check address, header, and size but not class.
+ 	 Answer true if OK.  Otherwise print reason and answer false."
+ 	<api>
+ 	<var: #oop type: #usqInt>
+ 	| classIndex fmt unusedBits unusedBitsInYoungObjects |
+ 
+ 	"address and size checks"
+ 	(self isImmediate: oop) ifTrue: [^true].
+ 	(self addressCouldBeObjWhileScavenging: oop) ifFalse:
+ 		[self print: 'oop '; printHex: oop; print: ' is not a valid address'. ^false].
+ 
+ 	(self addressAfter: oop) <= freeOldSpaceStart ifFalse:
+ 		[self print: 'oop '; printHex: oop; print: ' size would make it extend beyond the end of memory'. ^false].
+ 
+ 	"header type checks"
+ 	(classIndex := self classIndexOf: oop) >= self firstClassIndexPun ifFalse:
+ 		[self print: 'oop '; printHex: oop; print: ' is a free chunk, or bridge, not an object'. ^false].
+ 	((self rawNumSlotsOf: oop) = self numSlotsMask
+ 	 and: [(self rawNumSlotsOf: oop) - self baseHeaderSize ~= self numSlotsMask]) ifTrue:
+ 		[self print: 'oop '; printHex: oop; print: ' header has overflow header word, but overflow word does not have a saturated numSlots field'. ^false].
+ 
+ 	"format check"
+ 	fmt := self formatOf: oop.
+ 	(fmt = 6) | (fmt = 8) ifTrue:
+ 		[self print: 'oop '; printHex: oop; print: ' has an unknown format type'. ^false].
+ 	(fmt = self forwardedFormat) ~= (classIndex = self isForwardedObjectClassIndexPun) ifTrue:
+ 		[self print: 'oop '; printHex: oop; print: ' has mismached format/classIndex fields; only one of them is the isForwarded value'. ^false].
+ 
+ 	"specific header bit checks"
+ 	unusedBits := (1 << self classIndexFieldWidth)
+ 				   | (1 << (self identityHashFieldWidth + 32)).
+ 	((self longLongAt: oop) bitAnd: unusedBits) ~= 0 ifTrue:
+ 		[self print: 'oop '; printHex: oop; print: ' has some unused header bits set; should be zero'. ^false].
+ 
+ 	unusedBitsInYoungObjects := self newSpaceRefCountMask.
+ 	((self longAt: oop) bitAnd: unusedBitsInYoungObjects) ~= 0 ifTrue:
+ 		[self print: 'oop '; printHex: oop; print: ' has some header bits unused in young objects set; should be zero'. ^false].
+ 	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>checkOkayYoungReferrer: (in category 'debug support') -----
+ checkOkayYoungReferrer: obj
+ 	"Verify that the given obj is a valid youngReferrer. Check remembered is set and
+ 	 is in remembered set.  Answer true if OK.  Otherwise print reason and answer false.
+ 	 Assumes the object contains young references."
+ 
+ 	(self oop: obj isLessThan: newSpaceLimit) ifTrue:
+ 		[^true].
+ 
+ 	(self isRemembered: obj) ifFalse:
+ 		[ self print: 'remembered bit is not set in '; printHex: obj; cr. ^false ].
+ 
+ 	(scavenger isInRememberedSet: obj) ifTrue: [^true].
+ 
+ 	self printHex: obj; print: ' has remembered bit set but is not in remembered set'; cr.
+ 
+ 	^false
+ !

Item was added:
+ ----- Method: SpurMemoryManager>>checkedLongAt: (in category 'memory access') -----
+ checkedLongAt: byteAddress
+ 	"Assumes zero-based array indexing."
+ 	<api>
+ 	(self addressCouldBeObj: byteAddress) ifFalse:
+ 		[self warning: 'checkedLongAt bad address'.
+ 		 coInterpreter primitiveFail].
+ 	^self longAt: byteAddress!

Item was added:
+ ----- Method: SpurMemoryManager>>firstClassIndexPun (in category 'class table puns') -----
+ firstClassIndexPun
+ 	"Class puns are class indices not used by any class.  There is an entry
+ 	 for the pun that refers to the notional class of objects with this class
+ 	 index.  But because the index doesn't match the class it won't show up
+ 	 in allInstances, hence hiding the object with a pun as its class index.
+ 	 The puns occupy indices 16 through 31."
+ 	^16!

Item was changed:
  ----- Method: SpurMemoryManager>>formatOfHeader: (in category 'object access') -----
  formatOfHeader: header
- 	<var: 'header' type: #usqLong>
  	"0 = 0 sized objects (UndefinedObject True False et al)
  	 1 = non-indexable objects with inst vars (Point et al)
  	 2 = indexable objects with no inst vars (Array et al)
  	 3 = indexable objects with inst vars (MethodContext AdditionalMethodState et al)
  	 4 = weak indexable objects with inst vars (WeakArray et al)
  	 5 = weak non-indexable objects with inst vars (ephemerons) (Ephemeron)
+ 	 6 unused, reserved for exotic pointer objects?
+ 	 7 Forwarded Object, 1st field is pointer, rest of fields are ignored
+ 	 8 unused, reserved for exotic non-pointer objects?
- 	 6,7,8 unused
  	 9 (?) 64-bit indexable
  	 10 - 11 32-bit indexable
  	 12 - 15 16-bit indexable
  	 16 - 23 byte indexable
  	 24 - 31 compiled method"
+ 	<var: 'header' type: #usqLong>
  	^header >> self formatShift bitAnd: self formatMask!

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

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

Item was changed:
  ----- Method: SpurMemoryManager>>headerForSlots:format:classIndex: (in category 'header format') -----
  headerForSlots: numSlots format: formatField classIndex: classIndex
  	"The header format in LSB is
  	 MSB:	| 8: numSlots		| (on a byte boundary)
+ 			| 2 bits				|	(msb,lsb = {isMarked,?})
- 			| 2 bits				|
  			| 22: identityHash	| (on a word boundary)
+ 			| 3 bits				|	(msb <-> lsb = {isGrey,isPinned,isRemembered}
- 			| 3 bits				|	(msb <-> lsb = ?,isPinned,isRemembered
  			| 5: format			| (on a byte boundary)
+ 			| 2 bits				|	(msb,lsb = {isImmutable,?})
- 			| 2 bits				|
  			| 22: classIndex		| (on a word boundary) : LSB
+ 	 The remaining bits (7) are used for
+ 		isImmutable	(bit 23)
- 	 The remaining bits (7) need to be used for
- 		isGrey
- 		isMarked
  		isRemembered	(bit 29)
  		isPinned		(bit 30)
+ 		isGrey			(bit 31)
+ 		isMarked		(bit 55)
+ 	 leaving 2 unused bits, each next to a 22-bit field, allowing those fields to be
+ 	 expanded to 23 bits..  The three bit field { isGrey, isPinned, isRemembered }
- 		isImmutable
- 	 leaving 2 unused bits.  The three bit field containing isPinned, isRemembered
  	 is for bits that are never set in young objects.  This allows the remembered
  	 table to be pruned when full by using these bits as a reference count of
  	 newSpace objects from the remembered table. Objects with a high count
  	 should be tenured to prune the remembered table."
  	<returnTypeC: #usqLong>
  	^ (numSlots << self numSlotsFullShift)
  	+ (formatField << self formatShift)
  	+ classIndex!

Item was added:
+ ----- Method: SpurMemoryManager>>identityHashFieldWidth (in category 'header format') -----
+ identityHashFieldWidth
+ 	^22!

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

Item was added:
+ ----- Method: SpurMemoryManager>>isGrey: (in category 'header access') -----
+ isGrey: objOop
+ 	^((self longAt: objOop) >> self greyBitShift bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isImmutable: (in category 'header access') -----
+ isImmutable: objOop
+ 	^((self longAt: objOop) >> self immutableBitShift bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isMarked: (in category 'header access') -----
+ isMarked: objOop
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>isOopImmutable: (in category 'object testing') -----
+ isOopImmutable: oop
+ 	<api>
+ 	^(self isImmediate: oop)
+ 	  or: [self isImmutable: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>isOopMutable: (in category 'object testing') -----
+ isOopMutable: oop
+ 	<api>
+ 	^(self isNonImmediate: oop)
+ 	  and: [(self isImmutable: oop) not]!

Item was changed:
+ ----- Method: SpurMemoryManager>>isWordsNonImm: (in category 'object testing') -----
- ----- Method: SpurMemoryManager>>isWordsNonImm: (in category 'header access') -----
  isWordsNonImm: objOop
  	"Answer if the argument contains only indexable words (no oops). See comment in formatOf:"
  
  	^self subclassResponsibility!

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

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

Item was added:
+ ----- Method: SpurMemoryManager>>newSpaceRefCountMask (in category 'generation scavenging') -----
+ newSpaceRefCountMask
+ 	"The three bit field { isGrey, isPinned, isRemembered } is for bits
+ 	 that are never set in young objects.  This allows the remembered
+ 	 table to be pruned when full by using these bits as a reference
+ 	 count of newSpace objects from the remembered table. Objects
+ 	 with a high count should be tenured to prune the remembered table."
+ 	^ (1 << self greyBitShift)
+ 	 | (1 << self pinnedBitShift)
+ 	 | (1 << self rememberedBitShift)!

Item was added:
+ ----- Method: SpurMemoryManager>>okayOop: (in category 'debug support') -----
+ okayOop: signedOop
+ 	"Verify that the given oop is legitimate. Check address, header, and size but not class."
+ 
+ 	| oop classIndex fmt unusedBits unusedBitsInYoungObjects |
+ 	<var: #oop type: #usqInt>
+ 	oop := self cCoerce: signedOop to: #usqInt.
+ 
+ 	"address and size checks"
+ 	(self isImmediate: oop) ifTrue: [^true].
+ 	(self addressCouldBeObjWhileScavenging: oop) ifFalse:
+ 		[self error: 'oop is not a valid address'. ^false].
+ 
+ 	(self addressAfter: oop) <= freeOldSpaceStart ifFalse:
+ 		[self error: 'oop size would make it extend beyond the end of memory'. ^false].
+ 
+ 	"header type checks"
+ 	(classIndex := self classIndexOf: oop) >= self firstClassIndexPun ifFalse:
+ 		[self error: 'oop is a free chunk, or bridge, not an object'. ^false].
+ 	((self rawNumSlotsOf: oop) = self numSlotsMask
+ 	 and: [(self rawNumSlotsOf: oop) - self baseHeaderSize ~= self numSlotsMask]) ifTrue:
+ 		[self error: 'oop header has overflow header word, but overflow word does not have a saturated numSlots field'. ^false].
+ 
+ 	"format check"
+ 	fmt := self formatOf: oop.
+ 	(fmt = 6) | (fmt = 8) ifTrue:
+ 		[self error: 'oop has an unknown format type'. ^false].
+ 	(fmt = self forwardedFormat) ~= (classIndex = self isForwardedObjectClassIndexPun) ifTrue:
+ 		[self error: 'oop has mismached format/classIndex fields; only one of them is the isForwarded value'. ^false].
+ 
+ 	"specific header bit checks"
+ 	unusedBits := (1 << self classIndexFieldWidth)
+ 				   | (1 << (self identityHashFieldWidth + 32)).
+ 	((self longLongAt: oop) bitAnd: unusedBits) ~= 0 ifTrue:
+ 		[self error: 'some unused header bits are set; should be zero'. ^false].
+ 
+ 	unusedBitsInYoungObjects := (1 << self greyBitShift)
+ 								   | (1 << self pinnedBitShift)
+ 								   | (1 << self rememberedBitShift).
+ 	((self longAt: oop) bitAnd: unusedBitsInYoungObjects) ~= 0 ifTrue:
+ 		[self error: 'some header bits unused in young objects are set; should be zero'. ^false].
+ 	^true
+ !

Item was added:
+ ----- Method: SpurMemoryManager>>setIsGreyOf:to: (in category 'header access') -----
+ setIsGreyOf: objOop to: aBoolean
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>setIsImmutableOf:to: (in category 'header access') -----
+ setIsImmutableOf: objOop to: aBoolean
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>setIsMarkedOf:to: (in category 'header access') -----
+ setIsMarkedOf: objOop to: aBoolean
+ 	self subclassResponsibility!



More information about the Vm-dev mailing list