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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 23 16:44:28 UTC 2013


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

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

Name: VMMaker.oscog-eem.405
Author: eem
Time: 23 September 2013, 9:40:28.87 am
UUID: 85f4af17-796e-433f-afc4-aeecc29cfd1a
Ancestors: VMMaker.oscog-eem.404

Refactor SpurMemoryManager and the 64Bit & 32Bit subclasses in
the light of longAt:[put:] accessing 64-bits in the 64-bit system.

Fix termination condition in scavenge loop to accomodate
mapInterpreterOops (move mapInterpreterOops next to
scavengeRememberedSetStartingAt:).

Fix SpurMemMgr>>initializeOldSpaceFirstFree: for the bootstrap's
dual use (create, then launch).

Fix a slip in allocateOldSpaceChunkOfBytes:.

Add a simulator subclass to the scavenger and add a nice
pre-scavenge halt for debugging.  Also collect corpse->forwarded
info for debugging.

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

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>scavengingGC (in category 'generation scavenging') -----
+ scavengingGC
+ 	"Run the scavenger."
+ 	self halt: (statScavenges + 1) printString, (#('st' 'nd' 'rd') at: (statScavenges + 1) \\ 10 ifAbsent: 'th'), ' scavenge'.
+ 	^super scavengingGC!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>adjustFieldsAndClassOf:by: (in category 'initialization') -----
- adjustFieldsAndClassOf: oop by: offsetBytes 
- 	"Adjust all pointers in this object by the given offset."
- 	| fieldAddr fieldOop |
- 	<inline: true>
- 	<asmLabel: false>
- 	fieldAddr := oop + (self lastPointerOf: oop).
- 	[self oop: fieldAddr isGreaterThanOrEqualTo: oop + self baseHeaderSize] whileTrue:
- 		[fieldOop := self longAt: fieldAddr.
- 		 (self isImmediate: fieldOop) ifFalse:
- 			[self longAt: fieldAddr put: fieldOop + offsetBytes].
- 		 fieldAddr := fieldAddr - BytesPerOop]!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
  	| numBytes newObj |
  	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
+ 	 16 bytes otherwise (num slots in preceeding word).
- 	 16 bytes otherwise (slot size in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
  	numSlots >= self numSlotsMask
  		ifTrue:
  			[newObj := freeStart + self baseHeaderSize.
  			 numBytes := self baseHeaderSize + self baseHeaderSize "double header"
  						+ (numSlots + (numSlots bitAnd: 1) * self bytesPerSlot)] "roundTo allocationUnit"
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots <= 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots + (numSlots bitAnd: 1) * self bytesPerSlot])]. "roundTo allocationUnit"
- 	self assert: numBytes \\ self allocationUnit = 0.
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[needGCFlag ifFalse: [self scheduleScavenge].
  		 freeStart + numBytes > scavenger eden limit ifTrue:
  			[^self allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex]].
  	numSlots >= self numSlotsMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
  			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
  			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
  	self assert: numBytes \\ self allocationUnit = 0.
  	self assert: newObj \\ self allocationUnit = 0.
  	freeStart := freeStart + numBytes.
  	^newObj!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>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 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]) ifTrue:
- 						[coInterpreter print: 'object leak in '; printHex: obj; print: ' invalid class index '; printHex: classIndex; print: ' -> '; printHex: classOop; 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].
- 									 (self isYoung: fieldOop) 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.
- 		"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 rootTable @ '; printNum: i; print: ' = '; printHex: obj; cr.
- 						 self eek.
- 						 ok := false]
- 					ifFalse:
- 						[(self isYoung: obj) ifTrue:
- 							[coInterpreter print: 'non-root in rootTable @ '; 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 removed:
- ----- Method: Spur32BitMemoryManager>>classIndexOf: (in category 'header access') -----
- classIndexOf: objOop
- 	self flag: #endianness.
- 	^(self longAt: objOop) bitAnd: self classIndexMask!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>fetchPointer:ofFreeChunk: (in category 'heap management') -----
- fetchPointer: fieldIndex ofFreeChunk: objOop
- 	^self longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>fetchPointer:ofMaybeForwardedObject: (in category 'heap management') -----
- fetchPointer: fieldIndex ofMaybeForwardedObject: objOop
- 	^self longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>fetchPointer:ofObject: (in category 'object access') -----
- fetchPointer: fieldIndex ofObject: objOop
- 	self assert: (self isForwarded: objOop) not.
- 	^self longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>fillObj:numSlots:with: (in category 'allocation') -----
- fillObj: objOop numSlots: numSlots with: fillValue
- 	objOop + self baseHeaderSize
- 		to: objOop + self baseHeaderSize + (numSlots * 4) - 1
- 		by: self allocationUnit
- 		do: [:p|
- 			self assert: p < (self addressAfter: objOop).
- 			self longAt: p put: fillValue;
- 				longAt: p + 4 put: fillValue]!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>formatOf: (in category 'object access') -----
- formatOf: objOop
- 	"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?
- 	 9 (?) 64-bit indexable
- 	 10 - 11 32-bit indexable
- 	 12 - 15 16-bit indexable
- 	 16 - 23 byte indexable
- 	 24 - 31 compiled method"
- 	self flag: #endianness.
- 	^(self longAt: objOop) >> self formatShift bitAnd: self formatMask!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>initSpaceForAllocationCheck: (in category 'allocation') -----
- initSpaceForAllocationCheck: aNewSpace
- 	CheckObjectOverwrite ifTrue:
- 		[aNewSpace start
- 			to: aNewSpace limit - 1
- 			by: self wordSize
- 			do: [:p| self longAt: p put: p]]!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>printMemoryFrom:to: (in category 'debug printing') -----
- printMemoryFrom: start to: end
- 	<doNotGenerate>
- 	| address |
- 	address := start bitAnd: (BytesPerWord - 1) bitInvert.
- 	[address < end] whileTrue:
- 		[coInterpreter printHex: address; printChar: $:; space; printHex: (self longAt: address); cr.
- 		 address := address + BytesPerWord]!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>setClassIndexOf:to: (in category 'header access') -----
+ setClassIndexOf: objOop to: classIndex
+ 	self assert: (classIndex between: 0 and: self classIndexMask).
+ 	self flag: #endianness.
+ 	self longAt: objOop
+ 		put: ((self longAt: objOop) bitAnd: self classIndexMask bitInvert32)
+ 			+ classIndex!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>setFormatOf:to: (in category 'header access') -----
+ setFormatOf: objOop to: format
+ 	"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?
+ 	 9 (?) 64-bit indexable
+ 	 10 - 11 32-bit indexable
+ 	 12 - 15 16-bit indexable
+ 	 16 - 23 byte indexable
+ 	 24 - 31 compiled method"
+ 	self assert: (format between: 0 and: self formatMask).
+ 	self flag: #endianness.
+ 	self longAt: objOop
+ 		put: ((self longAt: objOop) bitAnd: (self formatMask << self formatShift) bitInvert32)
+ 			+ (format << self formatShift)!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>setHashBitsOf:to: (in category 'header access') -----
+ setHashBitsOf: objOop to: hash
+ 	self flag: #endianness.
+ 	self assert: (hash between: 0 and: self identityHashHalfWordMask).
+ 	self longAt: objOop + 4
+ 		put: ((self longAt: objOop + 4) bitClear: self identityHashHalfWordMask) + hash!

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

Item was removed:
- ----- Method: Spur32BitMemoryManager>>storePointer:ofForwarder:withValue: (in category 'heap management') -----
- storePointer: fieldIndex ofForwarder: objOop withValue: valuePointer
- 
- 	self assert: (self isForwarded: objOop).
- 	self assert: (self isOopForwarded: valuePointer) not.
- 
- 	(self isYoung: objOop) ifFalse: "most stores into young objects"
- 		[((self isNonImmediate: valuePointer) and: [self isYoung: valuePointer]) ifTrue:
- 			[self possibleRootStoreInto: objOop]].
- 
- 	^self
- 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>storePointer:ofFreeChunk:withValue: (in category 'heap management') -----
- storePointer: fieldIndex ofFreeChunk: objOop withValue: valuePointer
- 
- 	self assert: (self isFreeObject: objOop).
- 
- 	^self
- 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>storePointer:ofObject:withValue: (in category 'object access') -----
- storePointer: fieldIndex ofObject: objOop withValue: valuePointer
- 	"Note must check here for stores of young objects into old ones."
- 	self assert: (self isForwarded: objOop) not.
- 
- 	(self isYoung: objOop) ifFalse: "most stores into young objects"
- 		[(self isImmediate: valuePointer) ifFalse:
- 			[(self isYoung: valuePointer) ifTrue:
- 				[self possibleRootStoreInto: objOop]]].
- 
- 	^self
- 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>storePointerUnchecked:ofMaybeForwardedObject:withValue: (in category 'object access') -----
- storePointerUnchecked: fieldIndex ofMaybeForwardedObject: objOop withValue: valuePointer
- 	^self
- 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>storePointerUnchecked:ofObject:withValue: (in category 'object access') -----
- storePointerUnchecked: fieldIndex ofObject: objOop withValue: valuePointer
- 	self assert: (self isForwarded: objOop) not.
- 	^self
- 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>addressAfter: (in category 'object enumeration') -----
  addressAfter: objOop
  	"Answer the address immediately following an object."
  	| numSlots slotBytes |
+ 	numSlots := self numSlotsOfAny: objOop.
- 	numSlots := self numSlotsOf: objOop.
  	slotBytes := numSlots = 0
  					ifTrue: [self allocationUnit]
  					ifFalse: [numSlots << self shiftForWord].
  	^objOop + self baseHeaderSize + slotBytes!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>adjustFieldsAndClassOf:by: (in category 'initialization') -----
- adjustFieldsAndClassOf: oop by: offsetBytes 
- 	"Adjust all pointers in this object by the given offset."
- 	| fieldAddr fieldOop |
- 	<inline: true>
- 	<asmLabel: false>
- 	fieldAddr := oop + (self lastPointerOf: oop).
- 	[self oop: fieldAddr isGreaterThan: oop] whileTrue:
- 		[fieldOop := self longAt: fieldAddr.
- 		 (self isIntegerObject: fieldOop) ifFalse:
- 			[self longLongAt: fieldAddr put: fieldOop + offsetBytes].
- 		 fieldAddr := fieldAddr - BytesPerWord]!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>allocateSlots:format:classIndex: (in category 'allocation') -----
  allocateSlots: numSlots format: formatField classIndex: classIndex
  	| numBytes newObj |
  	"Object headers are 8 bytes in length if the slot size fits in the num slots field (max implies overflow),
  	 16 bytes otherwise (num slots in preceeding word).
  	 Objects always have at least one slot, for the forwarding pointer,
  	 and are multiples of 8 bytes in length."
  	numSlots >= self numSlotsMask
  		ifTrue:
  			[numSlots > 16rffffffff ifTrue:
  				[^nil].
  			 newObj := freeStart + self baseHeaderSize.
  			 numBytes := (self baseHeaderSize + self baseHeaderSize) "double header"
  						+ (numSlots * self bytesPerSlot)]
  		ifFalse:
  			[newObj := freeStart.
  			 numBytes := self baseHeaderSize "single header"
  						+ (numSlots < 1
  							ifTrue: [self allocationUnit] "at least one slot for the forwarding pointer"
  							ifFalse: [numSlots * self bytesPerSlot])].
  	
  	freeStart + numBytes > scavengeThreshold ifTrue:
  		[needGCFlag ifFalse: [self scheduleScavenge].
  		 freeStart + numBytes > scavenger eden limit ifTrue:
  			[^self allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex]].
  	numSlots >= self numSlotsMask
  		ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
  			[self flag: #endianness.
  			 self longAt: freeStart put: numSlots.
  			 self longAt: freeStart + 4 put: self numSlotsMask << self numSlotsHalfShift.
  			 self longLongAt: newObj put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex)]
  		ifFalse:
  			[self longLongAt: newObj put: (self headerForSlots: numSlots format: formatField classIndex: classIndex)].
+ 	self assert: numBytes \\ self allocationUnit = 0.
+ 	self assert: newObj \\ self allocationUnit = 0.
+ 	freeStart := freeStart + numBytes.
- 		freeStart := freeStart + numBytes.
  	^newObj!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>allocateSlotsInOldSpace:format:classIndex: (in category 'allocation') -----
+ allocateSlotsInOldSpace: numSlots 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."
+ 	| bytes chunk |
+ 	bytes := self objectBytesForSlots: numSlots.
+ 	chunk := self allocateOldSpaceChunkOfBytes: bytes.
+ 	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).
+ 		 ^chunk + self baseHeaderSize].
+ 	self longAt: chunk
+ 		put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
+ 	^chunk!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>bytesInObject: (in category 'object enumeration') -----
  bytesInObject: objOop
  	"Answer the total number of bytes in an object including header and possible overflow size header."
+ 	| header headerNumSlots numSlots |
- 	| halfHeader headerNumSlots numSlots |
  	self flag: #endianness.
+ 	header := self longAt: objOop.
+ 	headerNumSlots := header >> self numSlotsFullShift bitAnd: self numSlotsMask.
- 	"numSlotsOf: should not be applied to free or forwarded objects."
- 	self assert: (self classIndexOf: objOop) > self isForwardedObjectClassIndexPun.
- 	halfHeader := self longAt: objOop + 4.
- 	headerNumSlots := halfHeader >> self numSlotsHalfShift bitAnd: self numSlotsMask.
  	numSlots := headerNumSlots = self numSlotsMask
+ 					ifTrue: [header bitAnd: 16rFFFFFFFFFFFFFF]
+ 					ifFalse: [headerNumSlots = 0 ifTrue: [1] ifFalse: [headerNumSlots]].
- 					ifTrue: [self longAt: objOop - self baseHeaderSize]
- 					ifFalse: [numSlots = 0 ifTrue: [1] ifFalse: [numSlots]].
  	^numSlots << self shiftForWord
  	+ (headerNumSlots = self numSlotsMask
  		ifTrue: [self baseHeaderSize + self baseHeaderSize]
  		ifFalse: [self baseHeaderSize])!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>classIndexOf: (in category 'header access') -----
- classIndexOf: objOop
- 	^(self longLongAt: objOop) bitAnd: self classIndexMask!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>fetchPointer:ofObject: (in category 'object access') -----
- fetchPointer: fieldIndex ofObject: objOop
- 	self assert: (self isForwarded: objOop) not.
- 	^self longLongAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>formatOf: (in category 'object access') -----
- formatOf: objOop
- 	"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?
- 	 9 (?) 64-bit indexable
- 	 10 - 11 32-bit indexable
- 	 12 - 15 16-bit indexable
- 	 16 - 23 byte indexable
- 	 24 - 31 compiled method"
- 	^(self longLongAt: objOop) >> self formatShift bitAnd: self formatMask!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>initFreeChunkWithBytes:at: (in category 'garbage collection') -----
  initFreeChunkWithBytes: numBytes at: address
  	<var: #numBytes type: #usqLong>
  	| numSlots |
  	"must have room for a header (single or double) plus the next free pointer"
  	self assert: (numBytes \\ self allocationUnit = 0
  				 and: [numBytes >= (self baseHeaderSize + self wordSize)]).
- 	self flag: #endianness.
  	"double header"
  	numBytes >= (self numSlotsMask << self shiftForWord) ifTrue:
  		[numSlots := numBytes - self baseHeaderSize - self baseHeaderSize >> self shiftForWord.
+ 		 self longAt: address put: self numSlotsMask << self numSlotsFullShift + numSlots;
+ 			longAt: address + 8 put: self numSlotsMask << self numSlotsFullShift. "0's classIndex; 0 = classIndex of free chunks"
- 		 self longLongAt: address put: self numSlotsMask << self numSlotsFullShift + numSlots;
- 			longLongAt: address + 8 put: self numSlotsMask << self numSlotsFullShift. "0's classIndex; 0 = classIndex of free chunks"
  		^address + 8].
  	"single header"
  	numSlots := numBytes - self baseHeaderSize >> self shiftForWord.
+ 	self longAt: address put: numSlots << self numSlotsFullShift. "0's classIndex; 0 = classIndex of free chunks"
- 	self longLongAt: address put: numSlots << self numSlotsFullShift. "0's classIndex; 0 = classIndex of free chunks"
  	^address!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>longFormatForNumBytes: (in category 'header format') -----
- longFormatForNumBytes: numBytes
- 	"Answer firstLongFormat with the odd bit set if numBytes is an odd number of 4-byte units."
- 	^self firstLongFormat + (numBytes >> 2 bitAnd: 1)!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>setClassIndexOf:to: (in category 'header access') -----
+ setClassIndexOf: objOop to: classIndex
+ 	self assert: (classIndex between: 0 and: self classIndexMask).
+ 	self longAt: objOop
+ 		put: ((self longAt: objOop) bitAnd: self classIndexMask bitInvert64)
+ 			+ classIndex!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>setFormatOf:to: (in category 'header access') -----
+ setFormatOf: objOop to: format
+ 	"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?
+ 	 9 (?) 64-bit indexable
+ 	 10 - 11 32-bit indexable
+ 	 12 - 15 16-bit indexable
+ 	 16 - 23 byte indexable
+ 	 24 - 31 compiled method"
+ 	self assert: (format between: 0 and: self formatMask).
+ 	objOop
+ 		put: ((self longAt: objOop) bitAnd: (self formatMask << self formatShift) bitInvert64)
+ 			+ (format << self formatShift)!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>setHashBitsOf:to: (in category 'header access') -----
+ setHashBitsOf: objOop to: hash
+ 	self assert: (hash between: 0 and: self identityHashFullWordMask).
+ 	self longAt: objOop
+ 		put: ((self longAt: objOop) bitClear: self identityHashFullWordMask) + hash!

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

Item was removed:
- ----- Method: Spur64BitMemoryManager>>storePointer:ofObject:withValue: (in category 'object access') -----
- storePointer: fieldIndex ofObject: objOop withValue: valuePointer
- 	"Note must check here for stores of young objects into old ones."
- 	self assert: (self isForwarded: objOop) not.
- 
- 	(self isYoung: objOop) ifFalse: "most stores into young objects"
- 		[(self isImmediate: valuePointer) ifFalse:
- 			[(self isYoung: valuePointer) ifTrue:
- 				[self possibleRootStoreInto: objOop]]].
- 
- 	^self
- 		longLongAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>storePointerUnchecked:ofObject:withValue: (in category 'object access') -----
- storePointerUnchecked: fieldIndex ofObject: objOop withValue: valuePointer
- 	self assert: (self isForwarded: objOop) not.
- 	^self
- 		longLongAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		put: valuePointer!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavengeLoop (in category 'scavenger') -----
  scavengeLoop
  	"This is the inner loop of the main routine, scavenge.  It first scavenges the new objects immediately
  	 reachable from old ones. Then it scavenges those that are transitively reachable.  If this results in a
  	 promotion, the promotee gets remembered, and it first scavenges objects adjacent to the promotee,
  	 then scavenges the ones reachable from the promoted.  This loop continues until no more reachable
  	 objects are left.  At that point, pastSurvivorSpace is exchanged with futureSurvivorSpace.
  
  	 Notice that each pointer in a live object is inspected once and only once.  The previousRememberedSetSize
  	 and previousFutureSurvivorSpaceLimit variables ensure that no object is scanned twice, as well as
  	 detecting closure.  If this were not true, some pointers might get forwarded twice."
  
  	| firstTime previousRememberedSetSize previousFutureSurvivorStart |
  	self assert: futureSurvivorStart = futureSpace start. "future space should be empty at the start"
  	firstTime := true.
  	previousRememberedSetSize := 0.
  	previousFutureSurvivorStart := futureSurvivorStart.
  	[self scavengeRememberedSetStartingAt: previousRememberedSetSize.
+ 	 firstTime ifTrue:
+ 		[coInterpreter mapInterpreterOops.
+ 		 firstTime := false].
+ 	 "northing more copied and forwarded to scavenge so scavenge is done."
  	 previousFutureSurvivorStart = futureSurvivorStart ifTrue:
  		[^self].
  	 previousRememberedSetSize := rememberedSetSize.
  
- 	 firstTime ifTrue:
- 		[coInterpreter mapInterpreterOops.
- 		 firstTime := false].
- 
  	 self scavengeFutureSurvivorSpaceStartingAt: previousFutureSurvivorStart.
+ 	 "no more roots created to scavenge, so scavenge is done."
  	 previousRememberedSetSize = rememberedSetSize ifTrue:
  		[^self].
  
  	 previousFutureSurvivorStart := futureSurvivorStart] repeat!

Item was added:
+ SpurGenerationScavenger subclass: #SpurGenerationScavengerSimulator
+ 	instanceVariableNames: 'comeFroms'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManagerSimulation'!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>copyAndForward: (in category 'scavenger') -----
+ copyAndForward: survivor
+ 	| newLocation |
+ 	survivor = 16r19BC60 ifTrue: [self halt].
+ 	newLocation := super copyAndForward: survivor.
+ 	comeFroms at: newLocation put: survivor.
+ 	^newLocation!

Item was added:
+ ----- Method: SpurGenerationScavengerSimulator>>scavenge (in category 'scavenger') -----
+ scavenge
+ 	comeFroms := Dictionary new.
+ 	^super scavenge!

Item was changed:
  ----- Method: SpurMemoryManager>>adjustFieldsAndClassOf:by: (in category 'initialization') -----
  adjustFieldsAndClassOf: oop by: offsetBytes 
  	"Adjust all pointers in this object by the given offset."
+ 	| fieldAddr fieldOop |
+ 	<inline: true>
+ 	<asmLabel: false>
+ 	fieldAddr := oop + (self lastPointerOf: oop).
+ 	[self oop: fieldAddr isGreaterThanOrEqualTo: oop + self baseHeaderSize] whileTrue:
+ 		[fieldOop := self longAt: fieldAddr.
+ 		 (self isNonImmediate: fieldOop) ifTrue:
+ 			[self longAt: fieldAddr put: fieldOop + offsetBytes].
+ 		 fieldAddr := fieldAddr - BytesPerOop]!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateMemoryOfSize:newSpaceSize:codeSize: (in category 'simulation') -----
  allocateMemoryOfSize: memoryBytes newSpaceSize: newSpaceBytes codeSize: codeBytes
  	"Intialize the receiver for bootsraping an image.
  	 Set up a large oldSpace and an empty newSpace and set-up freeStart and scavengeThreshold
  	 to allocate in oldSpace.  Later on (in initializePostBootstrap) freeStart and scavengeThreshold
  	 will be set to sane values."
  	<doNotGenerate>
  	self assert: (memoryBytes \\ self allocationUnit = 0
  				and: [newSpaceBytes \\ self allocationUnit = 0
  				and: [codeBytes \\ self allocationUnit = 0]]).
  	memory := (self endianness == #little
  					ifTrue: [LittleEndianBitmap]
  					ifFalse: [Bitmap]) new: (memoryBytes + newSpaceBytes + codeBytes) // 4.
  	startOfMemory := codeBytes.
  	endOfMemory := freeOldSpaceStart := memoryBytes + newSpaceBytes + codeBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + startOfMemory.
  	newSpaceLimit := newSpaceBytes + startOfMemory.
  	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
+ 	scavenger := SpurGenerationScavengerSimulator new
- 	scavenger := SpurGenerationScavenger new
  					manager: self
  					newSpaceStart: startOfMemory
  					newSpaceBytes: newSpaceBytes
  					edenBytes: newSpaceBytes * 5 // 7 "David's paper uses 140Kb eden + 2 x 28kb survivor spaces :-)"!

Item was changed:
  ----- Method: SpurMemoryManager>>allocateOldSpaceChunkOfBytes: (in category 'free space') -----
  allocateOldSpaceChunkOfBytes: chunkBytes
  	"Answer a chunk of oldSpace from the free lists, if available,
  	 otherwise answer nil.  N.B.  the chunk is simply a pointer, it has
  	 no valid header.  The caller *must* fill in the header correctly."
  	| index chunk nextIndex nodeBytes parent child smaller larger |
  	totalFreeOldSpace := totalFreeOldSpace - chunkBytes. "be optimistic (& don't wait for the write)"
  	index := chunkBytes / self allocationUnit.
  	(index < NumFreeLists and: [1 << index >= freeListsMask]) ifTrue:
  		[(chunk := freeLists at: index) ~= 0 ifTrue:
  			[self assert: chunk = (self startOfObject: chunk).
  			^self unlinkFreeChunk: chunk atIndex: index].
  		 "first search for free chunks of a multiple of chunkBytes in size"
  		 nextIndex := index.
  		 [1 << index >= freeListsMask
  		  and: [(nextIndex := nextIndex + index) < NumFreeLists]] whileTrue:
  			[((freeListsMask anyMask: 1 << index)
  			 and: [(chunk := freeLists at: index) ~= 0]) ifTrue:
  				[self assert: chunk = (self startOfObject: chunk).
  				 self unlinkFreeChunk: chunk atIndex: index.
  				 self assert: (self bytesInObject: chunk) = index * self allocationUnit.
  				 self freeChunkWithBytes: index * self allocationUnit - chunkBytes
  					at: (self startOfObject: chunk) + chunkBytes.
  				^chunk]].
  		 "now get desperate and use the first that'll fit"
  		 nextIndex := index.
  		 [1 << index >= freeListsMask
  		  and: [(nextIndex := nextIndex + 1) < NumFreeLists]] whileTrue:
  			[(freeListsMask anyMask: 1 << index) ifTrue:
  				[(chunk := freeLists at: index) ~= 0 ifTrue:
  					[self assert: chunk = (self startOfObject: chunk).
  					 self unlinkFreeChunk: chunk atIndex: index.
  					 self assert: (self bytesInObject: chunk) = index * self allocationUnit.
  					 self freeChunkWithBytes: index * self allocationUnit - chunkBytes
  						at: (self startOfObject: chunk) + chunkBytes.
  					^chunk].
  				 freeListsMask := freeListsMask - (1 << index)]]].
  
  	"Large chunk, or no space on small free lists.  Search the large chunk list.
  	 Large chunk list organized as a tree, each node of which is a list of chunks
  	 of the same size. Beneath the node are smaller and larger blocks."
  	parent := 0.
  	child := freeLists at: 0.
  	[child ~= 0] whileTrue:
  		[nodeBytes := self bytesInObject: child.
  		 parent := child.
  		 nodeBytes = chunkBytes
  			ifTrue: "size match; try to remove from list at node."
  				[chunk := self fetchPointer: self freeChunkNextIndex
  								ofFreeChunk: child.
  				 chunk ~= 0 ifTrue:
  					[self storePointer: self freeChunkNextIndex
  						ofFreeChunk: child
  						withValue: (self fetchPointer: self freeChunkNextIndex
  										ofFreeChunk: chunk).
+ 					 ^self startOfObject: chunk].
- 					 ^chunk].
  				 child := 0] "break out of loop to remove interior node"
  			ifFalse:"walk down the tree"
  				[child := self fetchPointer: (nodeBytes > chunkBytes
  												ifTrue: [self freeChunkSmallerIndex]
  												ifFalse: [self freeChunkLargerIndex])
  								ofFreeChunk: child]].
  	parent = 0 ifTrue:
  		[totalFreeOldSpace := totalFreeOldSpace + chunkBytes. "optimism was unfounded"
  		 self halt].
  
  	"self printFreeChunk: parent"
  	self assert: (self bytesInObject: parent) = nodeBytes.
  	"attempt to remove from list"
  	chunk := self fetchPointer: self freeChunkNextIndex
  					ofFreeChunk: parent.
  	chunk ~= 0 ifTrue:
  		[self storePointer: self freeChunkNextIndex
  			ofFreeChunk: parent
  			withValue: (self fetchPointer: self freeChunkNextIndex
  							ofFreeChunk: chunk).
  		 chunkBytes ~= nodeBytes ifTrue:
  			[self freeChunkWithBytes: nodeBytes - chunkBytes
  					at: (self startOfObject: chunk) + chunkBytes].
  		 ^self startOfObject: chunk].
  	"no list; remove an interior node"
  	chunk := parent.
  	parent := self fetchPointer: self freeChunkParentIndex ofFreeChunk: chunk.
  	"no parent; stitch the subnodes back into the root"
  	parent = 0 ifTrue:
  		[smaller := self fetchPointer: self freeChunkSmallerIndex ofFreeChunk: chunk.
  		 larger := self fetchPointer: self freeChunkLargerIndex ofFreeChunk: chunk.
  		 smaller = 0
  			ifTrue: [freeLists at: 0 put: larger]
  			ifFalse:
  				[freeLists at: 0 put: smaller.
  				 larger ~= 0 ifTrue:
  					[self addFreeSubTree: larger]].
  		"coInterpreter transcript ensureCr.
  		 coInterpreter print: 'new free tree root '.
  		 (freeLists at: 0) = 0 ifTrue: [coInterpreter print: '0'] ifFalse: [self printFreeChunk: (freeLists at: 0)].
  		 coInterpreter cr."
  		 chunkBytes ~= nodeBytes ifTrue:
  			[self freeChunkWithBytes: nodeBytes - chunkBytes
  					at: (self startOfObject: chunk) + chunkBytes].
  		 ^self startOfObject: chunk].
  	"remove node from tree; reorder tree simply.  two cases (which have mirrors, for four total):
  	 case 1. interior node has one child, P = parent, N = node, S = subtree (mirrored for large vs small)
  			___				  ___
  			| P |				  | P |
  		    _/_				_/_
  		    | N |		=>		| S |
  		 _/_
  		 | S |"
  	self halt.
  	"case 2: interior node has two children, , P = parent, N = node, L = smaller, left subtree, R = larger, right subtree.
  	 add the left subtree to the bottom left of the right subtree (mirrored for large vs small) 
  			___				  ___
  			| P |				  | P |
  		    _/_				_/_
  		    | N |		=>		| R |
  		 _/_  _\_		    _/_
  		 | L | | R |		    | L |"
  	self halt!

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 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]) 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].
+ 									 (self isYoung: fieldOop) 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.
+ 		"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 rootTable @ '; printNum: i; print: ' = '; printHex: obj; cr.
+ 						 self eek.
+ 						 ok := false]
+ 					ifFalse:
+ 						[(self isYoung: obj) ifTrue:
+ 							[coInterpreter print: 'non-root in rootTable @ '; 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!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>classIndexOf: (in category 'header access') -----
  classIndexOf: objOop
+ 	^(self longAt: objOop) bitAnd: self classIndexMask!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>fetchPointer:ofFreeChunk: (in category 'heap management') -----
  fetchPointer: fieldIndex ofFreeChunk: objOop
+ 	^self longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>fetchPointer:ofMaybeForwardedObject: (in category 'heap management') -----
  fetchPointer: fieldIndex ofMaybeForwardedObject: objOop
+ 	^self longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>fetchPointer:ofObject: (in category 'object access') -----
  fetchPointer: fieldIndex ofObject: objOop
+ 	self assert: (self isForwarded: objOop) not.
+ 	^self longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>fillObj:numSlots:with: (in category 'allocation') -----
  fillObj: objOop numSlots: numSlots with: fillValue
+ 	objOop + self baseHeaderSize
+ 		to: objOop + self baseHeaderSize + (numSlots * self bytesPerOop) - 1
+ 		by: self allocationUnit
+ 		do: [:p|
+ 			self assert: p < (self addressAfter: objOop).
+ 			self longAt: p put: fillValue;
+ 				longAt: p + 4 put: fillValue]!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>formatOf: (in category 'object access') -----
  formatOf: objOop
  	"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?
  	 9 (?) 64-bit indexable
  	 10 - 11 32-bit indexable
  	 12 - 15 16-bit indexable
  	 16 - 23 byte indexable
  	 24 - 31 compiled method"
+ 	^(self longAt: objOop) >> self formatShift bitAnd: self formatMask!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>initSpaceForAllocationCheck: (in category 'allocation') -----
  initSpaceForAllocationCheck: aNewSpace
+ 	CheckObjectOverwrite ifTrue:
+ 		[aNewSpace start
+ 			to: aNewSpace limit - 1
+ 			by: self wordSize
+ 			do: [:p| self longAt: p put: p]]!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeOldSpaceFirstFree: (in category 'free space') -----
  initializeOldSpaceFirstFree: startOfFreeOldSpace
  	<var: 'startOfFreeOldSpace' type: #usqLong>
  	| freeOldStart freeChunk |
  	<var: 'freeOldStart' type: #usqLong>
+ 	
+ 	endOfMemory > startOfFreeOldSpace ifTrue:
+ 		[totalFreeOldSpace := totalFreeOldSpace + (endOfMemory - startOfFreeOldSpace).
+ 		 freeOldStart := startOfFreeOldSpace.
+ 		 [endOfMemory - freeOldStart >= (2 raisedTo: 32)] whileTrue:
+ 			[freeChunk := self freeChunkWithBytes: (2 raisedTo: 32) at: freeOldStart.
+ 			 freeOldStart := freeOldStart + (2 raisedTo: 32).
+ 			 self assert: freeOldStart = (self addressAfter: freeChunk)].
+ 		freeOldStart < endOfMemory ifTrue:
+ 			[freeChunk := self freeChunkWithBytes: endOfMemory - freeOldStart at: freeOldStart.
+ 			 self assert: (self addressAfter: freeChunk) = endOfMemory]].
- 	freeOldStart := startOfFreeOldSpace.
- 	[endOfMemory - freeOldStart >= (2 raisedTo: 32)] whileTrue:
- 		[freeChunk := self freeChunkWithBytes: (2 raisedTo: 32) at: freeOldStart.
- 		freeOldStart := freeOldStart + (2 raisedTo: 32).
- 		self assert: freeOldStart = (self addressAfter: freeChunk)].
- 	freeOldStart < endOfMemory ifTrue:
- 		[freeChunk := self freeChunkWithBytes: endOfMemory - freeOldStart at: freeOldStart.
- 		 self assert: (self addressAfter: freeChunk) = endOfMemory].
  	freeOldSpaceStart := endOfMemory.
  	self assert: totalFreeOldSpace = self totalFreeListBytes!

Item was changed:
  ----- Method: SpurMemoryManager>>isRemembered: (in category 'header access') -----
  isRemembered: objOop
- 	self flag: #endianness.
  	^((self longAt: objOop) >> self rememberedBitShift bitAnd: 1) ~= 0!

Item was removed:
- ----- Method: SpurMemoryManager>>longFormatForNumBytes: (in category 'header format') -----
- longFormatForNumBytes: numBytes
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>printMemoryFrom:to: (in category 'debug printing') -----
  printMemoryFrom: start to: end
+ 	<doNotGenerate>
+ 	| address |
+ 	address := start bitAnd: (self wordSize - 1) bitInvert.
+ 	[address < end] whileTrue:
+ 		[coInterpreter printHex: address; printChar: $:; space; printHex: (self longAt: address); cr.
+ 		 address := address + BytesPerWord]!
- 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>setClassIndexOf:to: (in category 'header access') -----
  setClassIndexOf: objOop to: classIndex
+ 	self subclassResponsibility!
- 	self flag: #endianness.
- 	self longAt: objOop
- 		put: ((self longAt: objOop) bitAnd: self classIndexMask bitInvert32)
- 			+ classIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>setFormatOf:to: (in category 'header access') -----
  setFormatOf: objOop to: format
  	"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?
  	 9 (?) 64-bit indexable
  	 10 - 11 32-bit indexable
  	 12 - 15 16-bit indexable
  	 16 - 23 byte indexable
  	 24 - 31 compiled method"
+ 	self subclassResponsibility!
- 	self flag: #endianness.
- 	self longAt: objOop
- 		put: ((self longAt: objOop) bitAnd: (self formatMask << self formatShift) bitInvert32)
- 			+ (format << self formatShift)!

Item was changed:
  ----- Method: SpurMemoryManager>>setHashBitsOf:to: (in category 'header access') -----
  setHashBitsOf: objOop to: hash
+ 	self subclassResponsibility!
- 	self flag: #endianness.
- 	self assert: (hash between: 0 and: self identityHashHalfWordMask).
- 	self longAt: objOop + 4
- 		put: ((self longAt: objOop + 4) bitClear: self identityHashHalfWordMask) + hash!

Item was changed:
  ----- Method: SpurMemoryManager>>setIsRememberedOf:to: (in category 'header access') -----
  setIsRememberedOf: objOop to: aBoolean
+ 	self subclassResponsibility!
- 	self flag: #endianness.
- 	self longAt: objOop
- 		put: (aBoolean
- 				ifTrue: [(self longAt: objOop) bitOr: 1 << self rememberedBitShift]
- 				ifFalse: [(self longAt: objOop) bitAnd: (1 << self rememberedBitShift) bitInvert32])!

Item was added:
+ ----- Method: SpurMemoryManager>>shiftForWord (in category 'word size') -----
+ shiftForWord
+ 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>storeByte:ofObject:withValue: (in category 'object access') -----
  storeByte: byteIndex ofObject: oop withValue: valueByte
+ 	^self byteAt: oop + self baseHeaderSize + byteIndex put: valueByte!
- 	^self byteAt: oop + BaseHeaderSize + byteIndex put: valueByte!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofForwarder:withValue: (in category 'heap management') -----
  storePointer: fieldIndex ofForwarder: objOop withValue: valuePointer
  
+ 	self assert: (self isForwarded: objOop).
+ 	self assert: (self isOopForwarded: valuePointer) not.
+ 
+ 	(self isYoung: objOop) ifFalse: "most stores into young objects"
+ 		[((self isNonImmediate: valuePointer) and: [self isYoung: valuePointer]) ifTrue:
+ 			[self possibleRootStoreInto: objOop]].
+ 
+ 	^self
+ 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
+ 		put: valuePointer!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofFreeChunk:withValue: (in category 'heap management') -----
  storePointer: fieldIndex ofFreeChunk: objOop withValue: valuePointer
  
+ 	self assert: (self isFreeObject: objOop).
+ 
+ 	^self
+ 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
+ 		put: valuePointer!
- 	^self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointer:ofObject:withValue: (in category 'object access') -----
+ storePointer: fieldIndex ofObject: objOop withValue: valuePointer
- storePointer: fieldIndex ofObject: oop withValue: valuePointer
  	"Note must check here for stores of young objects into old ones."
+ 	self assert: (self isForwarded: objOop) not.
+ 
+ 	(self isYoung: objOop) ifFalse: "most stores into young objects"
+ 		[(self isImmediate: valuePointer) ifFalse:
+ 			[(self isYoung: valuePointer) ifTrue:
+ 				[self possibleRootStoreInto: objOop]]].
+ 
+ 	^self
+ 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
+ 		put: valuePointer!
- 	^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>storePointerUnchecked:ofMaybeForwardedObject:withValue: (in category 'object access') -----
+ storePointerUnchecked: fieldIndex ofMaybeForwardedObject: objOop withValue: valuePointer
+ 	^self
+ 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
+ 		put: valuePointer!

Item was changed:
  ----- Method: SpurMemoryManager>>storePointerUnchecked:ofObject:withValue: (in category 'object access') -----
  storePointerUnchecked: fieldIndex ofObject: objOop withValue: valuePointer
+ 	self assert: (self isForwarded: objOop) not.
+ 	^self
+ 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
+ 		put: valuePointer!
- 	^self subclassResponsibility!



More information about the Vm-dev mailing list