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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 17 20:54:18 UTC 2013


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

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

Name: VMMaker.oscog-eem.386
Author: eem
Time: 17 September 2013, 1:51:38.98 pm
UUID: baeb0345-a41a-4c3a-823e-24de21382feb
Ancestors: VMMaker.oscog-eem.385

Implement SpurGenerationScavenger>>copyToOldSpace:.
Add searching the oldSpace free tree (incomplete) to allocate space.
Fix bug that assumed start of free chunk was same as free chunk oop.

Correctly initialize freeOldSpaceStart and correct allOldSpaceObjectsDo:.

Implement objectBefore: & objectAfter:

Fix comment speeling roers

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

Item was added:
+ ----- Method: Spur32BitMemoryManager>>allocateSlotsInOldSpace:format:classIndex: (in category 'allocation') -----
+ allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex
+ 	| bytes freeChunk chunk |
+ 	bytes := self objectBytesForSlots: numSlots.
+ 	freeChunk := self allocateOldSpaceChunkOfBytes: bytes.
+ 	freeChunk ifNil:
+ 		[^nil].
+ 	chunk := self startOfFreeChunk: freeChunk.
+ 	numSlots >= self numSlotsMask ifTrue: "for header parsing we put a saturated slot count in the prepended overflow size word"
+ 		[self flag: #endianness.
+ 		 self longAt: chunk put: numSlots.
+ 		 self longAt: chunk + 4 put: self numSlotsMask << self numSlotsHalfShift.
+ 		 self longLongAt: chunk + self baseHeaderSize
+ 			put: (self headerForSlots: self numSlotsMask format: formatField classIndex: classIndex).
+ 		 ^chunk + self baseHeaderSize].
+ 	self longLongAt: chunk put: (self headerForSlots: numSlots format: formatField classIndex: classIndex).
+ 	^chunk!

Item was removed:
- ----- Method: Spur32BitMemoryManager>>objectAfter:limit: (in category 'object enumeration') -----
- objectAfter: objOop limit: limit
- 	"Object parsing.
- 	1. all objects have at least a word following the header, for a forwarding pointer.
- 	2. objects with an overflow size have a preceeing word with a saturated numSlots.  If the word
- 	   following an object doesn't have a saturated numSlots field it must be a single-header object.
- 	   If the word following does have a saturated numSlots it must be the overflow size word."
- 	| followingWordAddress followingWord |
- 	followingWordAddress := self addressAfter: objOop.
- 	followingWordAddress >= limit ifTrue:
- 		[^limit].
- 	self flag: #endianness.
- 	followingWord := self longAt: followingWordAddress + 4.
- 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
- 		ifTrue: [followingWordAddress + self baseHeaderSize]
- 		ifFalse: [followingWordAddress]!

Item was added:
+ ----- Method: Spur32BitMemoryManager>>objectBytesForSlots: (in category 'object enumeration') -----
+ objectBytesForSlots: numSlots
+ 	"Answer the total number of bytes in an object with the given
+ 	 number of slots, including header and possible overflow size header."
+ 	^numSlots + (numSlots bitAnd: 1) << self shiftForWord
+ 	+ (numSlots >= self numSlotsMask
+ 		ifTrue: [self baseHeaderSize + self baseHeaderSize]
+ 		ifFalse: [self baseHeaderSize])!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>objectAfter:limit: (in category 'object enumeration') -----
- objectAfter: objOop limit: limit
- 	"Object parsing.
- 	1. all objects have at least a word following the header, for a forwarding pointer.
- 	2. objects with an overflow size have a preceeing word with a saturated numSlots.  If the word
- 	   following an object doesn't have a saturated numSlots field it must be a single-header object.
- 	   If the word following does have a saturated numSlots it must be the overflow size word."
- 	| followingWordAddress followingWord |
- 	followingWordAddress := self addressAfter: objOop.
- 	followingWordAddress >= limit ifTrue:
- 		[^limit].
- 	self flag: #endianness.
- 	followingWord := self longAt: followingWordAddress + 4.
- 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
- 		ifTrue: [followingWordAddress + self baseHeaderSize]
- 		ifFalse: [followingWordAddress]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>objectBytesForSlots: (in category 'object enumeration') -----
+ objectBytesForSlots: numSlots
+ 	"Answer the total number of bytes in an object with the given
+ 	 number of slots, including header and possible overflow size header."
+ 	^numSlots << self shiftForWord
+ 	+ (numSlots >= self numSlotsMask
+ 		ifTrue: [self baseHeaderSize + self baseHeaderSize]
+ 		ifFalse: [self baseHeaderSize])!

Item was changed:
  ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'scavenger') -----
  copyAndForward: survivor
  	"copyAndForward: survivor copies a survivor object either to
  	 futureSurvivorSpace or, if it is to be promoted, to oldSpace.
  	 It leaves a forwarding pointer behind."
  	<inline: true>
  	| bytesInObject newLocation |
  	bytesInObject := manager bytesInObject: survivor.
  	newLocation := ((self shouldBeTenured: survivor)
  					  or: [futureSurvivorStart + bytesInObject > futureSpace limit])
+ 						ifTrue: [self copyToOldSpace: survivor]
- 						ifTrue: [self copyToOldSpace: survivor bytes: bytesInObject]
  						ifFalse: [self copyToFutureSpace: survivor bytes: bytesInObject].
  	manager forward: survivor to: newLocation.
  	^newLocation!

Item was added:
+ ----- Method: SpurGenerationScavenger>>copyToOldSpace: (in category 'scavenger') -----
+ copyToOldSpace: survivor
+ 	"Copy survivor to oldSpace.  Answer the new oop of the object."
+ 	<inline: true>
+ 	| numSlots newOop |
+ 	self flag: 'why not just pass header??'.
+ 	numSlots := manager numSlotsOf: survivor.
+ 	newOop := manager
+ 					allocateSlotsInOldSpace: numSlots
+ 					format: (manager formatOf: survivor)
+ 					classIndex: (manager classIndexOf: survivor).
+ 	newOop ifNil:
+ 		[self error: 'out of memory'].
+ 	manager
+ 		mem: newOop + manager baseHeaderSize
+ 		cp: survivor + manager baseHeaderSize
+ 		y: numSlots * manager wordSize.
+ 	self remember: newOop.
+ 	manager setIsRememberedOf: newOop to: true.
+ 	^newOop!

Item was changed:
  ----- Method: SpurMemoryManager>>addToFreeList: (in category 'free space') -----
  addToFreeList: freeChunk
  	| chunkBytes childBytes parent child index |
  	chunkBytes := self bytesInObject: freeChunk.
+ 	index := chunkBytes / self allocationUnit.
- 	index := chunkBytes / self wordSize.
  	index < NumFreeLists ifTrue:
+ 		[self storePointer: self freeChunkNextIndex
+ 			ofForwardedOrFreeObject: freeChunk
+ 			withValue: (freeLists at: index).
- 		[self storePointer: 0 ofForwardedOrFreeObject: freeChunk withValue: (freeLists at: index).
  		 freeLists at: index put: freeChunk.
  		 ^self].
  	self
  		storePointer: self freeChunkNextIndex ofForwardedOrFreeObject: freeChunk withValue: 0;
  		storePointer: self freeChunkParentIndex ofForwardedOrFreeObject: freeChunk withValue: 0;
  		storePointer: self freeChunkSmallerIndex ofForwardedOrFreeObject: freeChunk withValue: 0;
  		storePointer: self freeChunkLargerIndex ofForwardedOrFreeObject: freeChunk withValue: 0.
  	"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:
  		[childBytes := self bytesInObject: child.
  		 childBytes = chunkBytes ifTrue: "size match; add to list at node."
  			[self storePointerUnchecked: self freeChunkNextIndex
  					ofObject: freeChunk
  						withValue: (self fetchPointer: self freeChunkNextIndex ofObject: child);
  				storePointerUnchecked: self freeChunkNextIndex
  					ofObject: child
  						withValue: freeChunk.
  			 ^self].
  		 "walk down the tree"
  		 parent := child.
  		 child := self fetchPointer: (childBytes > chunkBytes
  										ifTrue: [self freeChunkSmallerIndex]
  										ifFalse: [self freeChunkLargerIndex])
  					ofObject: child].
  	parent = 0 ifTrue:
  		[self assert: (freeLists at: 0) = 0.
  		 freeLists at: 0 put: freeChunk.
  		 ^self].
  	"insert in tree"
  	self storePointerUnchecked: self freeChunkParentIndex
  			ofObject: freeChunk
  				withValue: parent.
  	 self storePointerUnchecked: (childBytes > chunkBytes
  									ifTrue: [self freeChunkSmallerIndex]
  									ifFalse: [self freeChunkLargerIndex])
  			ofObject: parent
  				withValue: freeChunk!

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.
- 	endOfMemory := 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 := 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 added:
+ ----- 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 caler *must* fill in the header correctly."
+ 	| index chunk nextIndex nodeBytes parent child smaller larger |
+ 	index := chunkBytes / self allocationUnit.
+ 	index < NumFreeLists ifTrue:
+ 		[(chunk := freeLists at: index) ~= 0 ifTrue:
+ 			[^self unlinkFreeChunk: chunk atIndex: index].
+ 		 "first search for free chunks of a multiple of chunkBytes in size"
+ 		 nextIndex := index.
+ 		 [(nextIndex := nextIndex + index) < NumFreeLists] whileTrue:
+ 			[(chunk := freeLists at: index) ~= 0 ifTrue:
+ 				[self unlinkFreeChunk: chunk atIndex: index.
+ 				 self assert: (self bytesInObject: chunk) = index * self allocationUnit.
+ 				 self freeChunkWithBytes: index * self allocationUnit - chunkBytes
+ 					at: (self startOfFreeChunk: chunk) + chunkBytes.
+ 				^chunk]].
+ 		 "now get desperate and use the first that'll fit"
+ 		 nextIndex := index.
+ 		 [(nextIndex := nextIndex + 1) < NumFreeLists] whileTrue:
+ 			[(chunk := freeLists at: index) ~= 0 ifTrue:
+ 				[self unlinkFreeChunk: chunk atIndex: index.
+ 				 self assert: (self bytesInObject: chunk) = index * self allocationUnit.
+ 				 self freeChunkWithBytes: index * self allocationUnit - chunkBytes
+ 					at: (self startOfFreeChunk: chunk) + chunkBytes.
+ 				^chunk]]].
+ 
+ 	"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
+ 								ofForwardedOrFreeObject: child.
+ 				 chunk ~= 0 ifTrue:
+ 					[self storePointer: self freeChunkNextIndex
+ 						ofForwardedOrFreeObject: child
+ 						withValue: (self fetchPointer: self freeChunkNextIndex
+ 										ofForwardedOrFreeObject: 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])
+ 								ofObject: child]].
+ 	parent = 0 ifTrue:
+ 		[self halt].
+ 	"self printFreeChunk: parent"
+ 	self assert: (self bytesInObject: parent) = nodeBytes.
+ 	"attempt to remove from list"
+ 	chunk := self fetchPointer: self freeChunkNextIndex
+ 					ofForwardedOrFreeObject: parent.
+ 	chunk ~= 0 ifTrue:
+ 		[self storePointer: self freeChunkNextIndex
+ 			ofForwardedOrFreeObject: parent
+ 			withValue: (self fetchPointer: self freeChunkNextIndex
+ 							ofForwardedOrFreeObject: chunk).
+ 		 chunkBytes ~= nodeBytes ifTrue:
+ 			[self freeChunkWithBytes: nodeBytes - chunkBytes
+ 					at: (self startOfFreeChunk: chunk) + chunkBytes].
+ 		 ^chunk].
+ 	"no list; remove an interior node"
+ 	chunk := parent.
+ 	parent := self fetchPointer: self freeChunkParentIndex ofForwardedOrFreeObject: chunk.
+ 	"no parent; stitch the subnodes back into the root"
+ 	parent = 0 ifTrue:
+ 		[smaller := self fetchPointer: self freeChunkSmallerIndex ofForwardedOrFreeObject: chunk.
+ 		 larger := self fetchPointer: self freeChunkLargerIndex ofForwardedOrFreeObject: chunk.
+ 		 smaller = 0
+ 			ifTrue: [freeLists at: 0 put: larger]
+ 			ifFalse:
+ 				[freeLists at: 0 put: smaller.
+ 				 larger ~= 0 ifTrue:
+ 					[self addFreeSubTree: larger]].
+ 		 chunkBytes ~= nodeBytes ifTrue:
+ 			[self freeChunkWithBytes: nodeBytes - chunkBytes
+ 					at: (self startOfFreeChunk: chunk) + chunkBytes].
+ 		 ^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 added:
+ ----- Method: SpurMemoryManager>>allocateSlotsInOldSpace:format:classIndex: (in category 'allocation') -----
+ allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: SpurMemoryManager>>byteLengthOf: (in category 'object access') -----
  byteLengthOf: objOop 
  	"Answer the number of indexable bytes in the given object.
+ 	 Does not adjust contexts by stackPointer."
- 	 Does not adjuect contexts by stackPointer."
  	| fmt numBytes |
  	<inline: true>
  	<asmLabel: false>
  	fmt := self formatOf: objOop.
  	numBytes := (self numSlotsOf: objOop) << self shiftForWord.
  	fmt <= self sixtyFourBitIndexableFormat ifTrue:
  		[^numBytes].
  	fmt >= self firstByteFormat ifTrue: "bytes, including CompiledMethod"
  		[^numBytes - (fmt bitAnd: 7)].
  	fmt >= self firstShortFormat ifTrue:
  		[^numBytes - ((fmt bitAnd: 3) << 1)].
  	"fmt >= self firstLongFormat"
  	^numBytes - ((fmt bitAnd: 1) << 2)!

Item was added:
+ ----- Method: SpurMemoryManager>>freeChunkWithBytes:at: (in category 'free space') -----
+ freeChunkWithBytes: bytes at: address
+ 	<inline: true>
+ 	| freeChunk |
+ 	freeChunk := self initFreeChunkWithBytes: bytes at: address.
+ 	self addToFreeList: freeChunk.!

Item was changed:
  ----- Method: SpurMemoryManager>>initializeOldSpaceFirstFree: (in category 'free space') -----
  initializeOldSpaceFirstFree: startOfFreeOldSpace
  	<var: 'startOfFreeOldSpace' type: #usqLong>
  	| freeOldStart freeChunk |
  	<var: 'freeOldStart' type: #usqLong>
  	0 to: NumFreeLists - 1 do:
  		[:i| freeLists at: i put: 0].
  	freeOldStart := startOfFreeOldSpace.
  	[endOfMemory - freeOldStart >= (2 raisedTo: 32)] whileTrue:
  		[freeChunk := self initFreeChunkWithSlots: (2 raisedTo: 32) / self wordSize at: freeOldStart.
  		self addToFreeList: freeChunk.
  		freeOldStart := self addressAfter: freeChunk].
  	freeChunk := self initFreeChunkWithBytes: endOfMemory - freeOldStart at: freeOldStart.
  	self addToFreeList: freeChunk.
+ 	self assert: (self addressAfter: freeChunk) = endOfMemory.
+ 	freeOldSpaceStart := endOfMemory!
- 	self assert: (self addressAfter: freeChunk) = endOfMemory!

Item was changed:
  ----- Method: SpurMemoryManager>>initializePostBootstrap (in category 'simulation') -----
  initializePostBootstrap
+ 	"The heap has just been bootstrapped into a modified newSpace occupying all of memory
+ 	 above newSpace (and the codeZone). Put things back to some kind of normalcy."
- 	"The heap has just been bootstrapped into a modified newSpace occupying all of memory above newSPace (and the codeZone).
- 	 Put things back to some kind of normalicy."
  	freeOldSpaceStart := freeStart.
  	freeStart := scavenger eden start.
  	pastSpaceStart := scavenger pastSpace start.
  	scavengeThreshold := scavenger eden limit - (scavenger edenBytes / 64)!

Item was changed:
  ----- Method: SpurMemoryManager>>objectAfter: (in category 'object enumeration') -----
  objectAfter: objOop
  	"Object parsing.
  	1. all objects have at least a word following the header, for a forwarding pointer.
  	2. objects with an overflow size have a preceeing word with a saturated slotSize.  If the word following
  	    an object doesn't have a saturated size field it must be a single-header object.  If the word following
  	   does have a saturated slotSize it must be the overflow size word."
+ 	objOop < newSpaceLimit ifTrue:
+ 		[(self isInEden: objOop) ifTrue:
+ 			[^self objectAfter: objOop limit: freeStart].
+ 		 (self isInSurvivorSpace: objOop) ifTrue:
+ 			[^self objectAfter: objOop limit: pastSpaceStart].
+ 		 ^self objectAfter: objOop limit: scavenger futureSurvivorStart].
+ 	^self objectAfter: objOop limit: freeOldSpaceStart!
- 	^self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>objectAfter:limit: (in category 'object enumeration') -----
+ objectAfter: objOop limit: limit
+ 	"Object parsing.
+ 	1. all objects have at least a word following the header, for a forwarding pointer.
+ 	2. objects with an overflow size have a preceeing word with a saturated numSlots.  If the word
+ 	   following an object doesn't have a saturated numSlots field it must be a single-header object.
+ 	   If the word following does have a saturated numSlots it must be the overflow size word."
+ 	| followingWordAddress followingWord |
+ 	followingWordAddress := self addressAfter: objOop.
+ 	followingWordAddress >= limit ifTrue:
+ 		[^limit].
+ 	self flag: #endianness.
+ 	followingWord := self longAt: followingWordAddress + 4.
+ 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
+ 		ifTrue: [followingWordAddress + self baseHeaderSize]
+ 		ifFalse: [followingWordAddress]!

Item was added:
+ ----- Method: SpurMemoryManager>>objectBefore: (in category 'object enumeration') -----
+ objectBefore: objOop
+ 	| prev |
+ 	prev := nil.
+ 	objOop < newSpaceLimit ifTrue:
+ 		[self allNewSpaceObjectsDo:
+ 			[:o|
+ 			 o >= objOop ifTrue:
+ 				[^prev].
+ 			 prev := o].
+ 		 ^prev].
+ 	self allOldSpaceObjectsDo:
+ 		[:o|
+ 		 o >= objOop ifTrue:
+ 			[^prev].
+ 		 prev := o].
+ 	^prev!

Item was added:
+ ----- Method: SpurMemoryManager>>objectBytesForSlots: (in category 'object enumeration') -----
+ objectBytesForSlots: numSlots
+ 	"Answer the total number of bytes in an object with the given
+ 	 number of slots, including header and possible overflow size header."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: SpurMemoryManager>>printFreeChunk: (in category 'debug printing') -----
+ printFreeChunk: freeChunk
+ 	<doNotGenerate>
+ 	| numBytes |
+ 	numBytes := self bytesInObject: freeChunk.
+ 	coInterpreter
+ 		print: 'freeChunk @ '; printHexPtr: freeChunk;
+ 		print: ' bytes '; printNum: numBytes;
+ 		print: ' next '; print: (self fetchPointer: self freeChunkNextIndex
+ 										ofForwardedOrFreeObject: freeChunk) hex.
+ 	numBytes / self allocationUnit > NumFreeLists ifTrue:
+ 		[coInterpreter
+ 			print: ' ^ '; print: (self fetchPointer: self freeChunkParentIndex
+ 										ofForwardedOrFreeObject: freeChunk) hex;
+ 			print: ' < '; print: (self fetchPointer: self freeChunkSmallerIndex
+ 										ofForwardedOrFreeObject: freeChunk) hex;
+ 			print: ' > '; print: (self fetchPointer: self freeChunkLargerIndex
+ 										ofForwardedOrFreeObject: freeChunk) hex].
+ 	coInterpreter cr!

Item was added:
+ ----- Method: SpurMemoryManager>>startOfFreeChunk: (in category 'free space') -----
+ startOfFreeChunk: freeChunk
+ 	^freeChunk - self baseHeaderSize!

Item was changed:
  ----- Method: SpurMemoryManager>>sufficientSpaceAfterGC: (in category 'generation scavenging') -----
  sufficientSpaceAfterGC: numBytes
  	"This is ObjectMemory's funky entry-point into its incremental GC,
  	 which is a stop-the-world a young generation reclaimer.  In Spur
  	 we run the scavenger."
  	self halt.
  	self assert: numBytes = 0.
  
  	self runLeakCheckerForFullGC: false.
  	coInterpreter preGCAction: GCModeIncr.
  	needGCFlag := false.
  
  
  	gcStartUsecs := coInterpreter ioUTCMicrosecondsNow.
  
  	scavengeInProgress := true.
  	pastSpaceStart := scavenger scavenge.
  	self assert: (self
  					oop: pastSpaceStart
  					isGreaterThanOrEqualTo: scavenger pastSpace start
+ 					andLessThanOrEqualTo: scavenger pastSpace limit).
- 					andLessThan: scavenger pastSpace limit).
  	freeStart := scavenger eden start.
  	self initSpaceForAllocationCheck: scavenger eden.
  	scavengeInProgress := false.
  
  	statScavenges := statScavenges + 1.
  	statGCEndUsecs := coInterpreter ioUTCMicrosecondsNow.
  	statSGCDeltaUsecs := statGCEndUsecs - gcStartUsecs.
  	statScavengeGCUsecs := statScavengeGCUsecs + statSGCDeltaUsecs.
  
  	coInterpreter postGCAction.
  	self runLeakCheckerForFullGC: false.
  
  	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>unlinkFreeChunk:atIndex: (in category 'free space') -----
+ unlinkFreeChunk: chunk atIndex: index
+ 	<inline: true>
+ 	self assert: ((self bytesInObject: chunk) = index * self allocationUnit
+ 				and: [index > 1 "a.k.a. (self bytesInObject: chunk) > self allocationUnit"]).
+ 	freeLists
+ 		at: index
+ 		put: (self
+ 				fetchPointer: self freeChunkNextIndex
+ 				ofForwardedOrFreeObject: chunk).
+ 	^chunk!

Item was added:
+ ----- Method: VMClass>>oop:isGreaterThanOrEqualTo:andLessThanOrEqualTo: (in category 'oop comparison') -----
+ oop: anOop isGreaterThanOrEqualTo: baseOop andLessThanOrEqualTo: limitOop
+ 	"Compare two oop values, treating them as object memory locations.
+ 	Use #cCoerce:to: to ensure comparison of unsigned magnitudes. This
+ 	method will be inlined during C translation."
+ 	<inline: true>
+ 	^(self cCoerce: anOop to: #usqInt) >= (self cCoerce: baseOop to: #usqInt)
+ 	  and: [(self cCoerce: anOop to: #usqInt) <= (self cCoerce: limitOop to: #usqInt)]!



More information about the Vm-dev mailing list