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

commits at source.squeak.org commits at source.squeak.org
Wed Sep 4 21:21:40 UTC 2013


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

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

Name: VMMaker.oscog-eem.347
Author: eem
Time: 4 September 2013, 2:13:42.682 pm
UUID: 20e17c9c-68ab-4d89-9f35-f6f0f0bf4642
Ancestors: VMMaker.oscog-eem.346

Initialize the scavenger.  Use scaenger eden limit as the allocation
limit, instead of the erroneous use of newSpaceLimit.  Rewrite the
scavenge methods to use SpurMemoryManager's api.

Implement isYoung: and use it in the store check.

Implement oldSpace and newSpace enumeration via objectAfter:limit:.

Add more protocol to SpurMemMgr (e.g. isContext: et al).

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

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
+ SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
+ SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
- SystemOrganization addCategory: #'VMMaker-MemoryManager'!
- SystemOrganization addCategory: #'VMMaker-MemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-Alien'!

Item was changed:
  VMStructType subclass: #CogObjectHeader
  	instanceVariableNames: 'classIndex unused0 isPinned isImmutable format isMarked isGrey isRemembered objHash slotSize'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
- 	category: 'VMMaker-MemoryManager'!

Item was added:
+ ----- Method: ObjectMemory>>isContextNonImm: (in category 'contexts') -----
+ isContextNonImm: oop
+ 	<inline: true>
+ 	^self isContextHeader: (self baseHeader: oop)!

Item was changed:
  Spur32BitMemoryManager subclass: #Spur32BitMMLESimulator
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManagerSimulation'!
- 	category: 'VMMaker-MemoryManagerSimulation'!

Item was changed:
  ----- Method: Spur32BitMMLESimulator>>headerForSlots:format:classIndex: (in category 'header format') -----
  headerForSlots: numSlots format: formatField classIndex: classIndex
  	"The header format in LSB is
  	 MSB:	| 2 bits				|
  			| 22: identityHash	|
  			| 8: slotSize			|
  			| 3 bits				|
  			| 5: format			|
  			| 2 bits				|
  			| 22: classIndex		| : LSB"
+ 	self assert: (numSlots bitAnd: self numSlotsMask) = numSlots.
+ 	self assert: (formatField bitAnd: self formatMask) = formatField.
+ 	self assert: (classIndex bitAnd: self classIndexMask) = classIndex.
- 	self assert: (numSlots between: 0 and: self numSlotsMask).
- 	self assert: (formatField between: 0 and: 31).
- 	self assert: (classIndex between: 0 and: 16r3fffff).
  	^super headerForSlots: numSlots format: formatField classIndex: classIndex!

Item was changed:
  SpurMemoryManager subclass: #Spur32BitMemoryManager
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
- 	category: 'VMMaker-MemoryManager'!

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 (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:
+ 		[freeStart + numBytes > scavenger eden limit ifTrue:
- 		[freeStart + numBytes > newSpaceLimit ifTrue:
  			[^self allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex].
  		 self scheduleScavenge].
  	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>>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 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 >= freeStart ifTrue:
- 		[^freeStart].
- 	self flag: #endianness.
- 	followingWord := self longAt: followingWordAddress + 4.
- 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
- 		ifTrue: [followingWordAddress + self baseHeaderSize]
- 		ifFalse: [followingWordAddress]!

Item was added:
+ ----- 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 changed:
  ----- Method: Spur32BitMemoryManager>>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 isYoung: objOop) ifFalse: "most stores into young objects"
- 	(self oop: oop isLessThan: newSpaceLimit) ifFalse: "most stores into young objects"
  		[(self isImmediate: valuePointer) ifFalse:
+ 			[(self isYoung: valuePointer) ifTrue:
+ 				[self possibleRootStoreInto: objOop value: valuePointer]]].
- 			[(self oop: valuePointer isLessThan: newSpaceLimit) ifTrue:
- 				[self possibleRootStoreInto: oop value: valuePointer]]].
  
  	^self
+ 		longAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		longAt: oop + self baseHeaderSize + (fieldIndex << self shiftForWord)
  		put: valuePointer!

Item was changed:
  SpurMemoryManager subclass: #Spur64BitMemoryManager
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
- 	category: 'VMMaker-MemoryManager'!

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:
+ 		[freeStart + numBytes > scavenger eden limit ifTrue:
- 		[freeStart + numBytes > newSpaceLimit ifTrue:
  			[^self allocateSlotsInOldSpace: numSlots format: formatField classIndex: classIndex].
  		 self scheduleScavenge].
  	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)].
  		freeStart := freeStart + numBytes.
  	^newObj!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>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 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 >= freeStart ifTrue:
- 		[^freeStart].
- 	self flag: #endianness.
- 	followingWord := self longAt: followingWordAddress + 4.
- 	^followingWord >> self numSlotsHalfShift = self numSlotsMask
- 		ifTrue: [followingWordAddress + self baseHeaderSize]
- 		ifFalse: [followingWordAddress]!

Item was added:
+ ----- 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 changed:
  ----- Method: Spur64BitMemoryManager>>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 isYoung: objOop) ifFalse: "most stores into young objects"
- 	(self oop: oop isLessThan: newSpaceLimit) ifFalse: "most stores into young objects"
  		[(self isImmediate: valuePointer) ifFalse:
+ 			[(self isYoung: valuePointer) ifTrue:
+ 				[self possibleRootStoreInto: objOop value: valuePointer]]].
- 			[(self oop: valuePointer isLessThan: newSpaceLimit) ifTrue:
- 				[self possibleRootStoreInto: oop value: valuePointer]]].
  
  	^self
+ 		longLongAt: objOop + self baseHeaderSize + (fieldIndex << self shiftForWord)
- 		longLongAt: oop + self baseHeaderSize + (fieldIndex << self shiftForWord)
  		put: valuePointer!

Item was changed:
  VMClass subclass: #SpurGenerationScavenger
+ 	instanceVariableNames: 'coInterpreter manager memory eden futureSpace pastSpace rememberedSet rememberedSetSize'
- 	instanceVariableNames: 'coInterpreter manager memory futureSpace pastSpace rememberedSet rememberedSetSize'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!
- 	category: 'VMMaker-MemoryManager'!

Item was changed:
+ ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'scavenger') -----
- ----- Method: SpurGenerationScavenger>>copyAndForward: (in category 'api') -----
  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."
- 	<var: #survivor type: #'object *'>
  	| newLocation |
  	newLocation := (self shouldBeTenured: survivor)
  						ifTrue: [self copyToOldSpace: survivor]
  						ifFalse: [self copyToFutureSpace: survivor].
  	manager forward: survivor to: newLocation
  			!

Item was added:
+ ----- Method: SpurGenerationScavenger>>eden (in category 'accessing') -----
+ eden
+ 	<returnTypeC: #'SpurNewSpaceSpace *'>
+ 	^self addressOf: eden!

Item was added:
+ ----- Method: SpurGenerationScavenger>>futureSpace (in category 'accessing') -----
+ futureSpace
+ 	<returnTypeC: #'SpurNewSpaceSpace *'>
+ 	^self addressOf: futureSpace!

Item was added:
+ ----- Method: SpurGenerationScavenger>>initPastSpaceForObjectEnumeration (in category 'initialization') -----
+ initPastSpaceForObjectEnumeration
+ 	"For SuurMemoryManager allNewSpaceObjectsDo: fill pastSpace with
+ 	 a single empty object."
+ 	| objOop |
+ 	manager initFreeChunkWithBytes: pastSpace limit - pastSpace start at: pastSpace start.
+ 	objOop := manager objectStartingAt: pastSpace start.
+ 	self assert: (manager addressAfter: objOop) = pastSpace limit!

Item was added:
+ ----- Method: SpurGenerationScavenger>>manager:memory:newSpaceStart:newSpaceBytes:edenBytes: (in category 'initialization') -----
+ manager: aSpurMemoryManager memory: memoryArray newSpaceStart: startAddress newSpaceBytes: totalBytes edenBytes: requestedEdenBytes 
+ 	| edenBytes edenLimit edenStart survivorBytes |
+ 	manager := aSpurMemoryManager.
+ 	memory := memoryArray.
+ 	edenBytes := requestedEdenBytes.
+ 	edenStart := startAddress.
+ 	survivorBytes := totalBytes - edenBytes // 2 truncateTo: manager allocationUnit.
+ 	edenBytes := totalBytes - survivorBytes - survivorBytes truncateTo: manager allocationUnit.
+ 	edenLimit := edenStart + edenBytes roundUpTo: manager allocationUnit.
+ 	self assert: totalBytes - (edenLimit - edenStart) - survivorBytes - survivorBytes < manager allocationUnit.
+ 	eden := SpurNewSpaceSpace new.
+ 	pastSpace := SpurNewSpaceSpace new.
+ 	futureSpace := SpurNewSpaceSpace new.
+ 	eden start: edenStart limit: edenLimit.
+ 	pastSpace start: edenLimit limit: edenLimit + survivorBytes.
+ 	futureSpace start: pastSpace limit limit: pastSpace limit + survivorBytes.
+ 	self assert: futureSpace limit <= (startAddress + totalBytes).
+ 	self assert: eden start \\ manager allocationUnit
+ 				+ (eden limit \\ manager allocationUnit) = 0.
+ 	self assert: pastSpace start \\ manager allocationUnit
+ 				+ (pastSpace limit \\ manager allocationUnit) = 0.
+ 	self assert: futureSpace start \\ manager allocationUnit
+ 				+ (futureSpace limit \\ manager allocationUnit) = 0.
+ 	self initPastSpaceForObjectEnumeration!

Item was added:
+ ----- Method: SpurGenerationScavenger>>pastSpace (in category 'accessing') -----
+ pastSpace
+ 	<returnTypeC: #'SpurNewSpaceSpace *'>
+ 	^self addressOf: pastSpace!

Item was changed:
+ ----- Method: SpurGenerationScavenger>>scavenge (in category 'scavenger') -----
- ----- Method: SpurGenerationScavenger>>scavenge (in category 'api') -----
  scavenge
  	"The main routine, scavenge, scavenges young objects reachable from the roots (the stack zone
  	 and the rememberedTable).  It first scavenges the new objects immediately reachable from the
  	 stack zone, then those directly from old ones (all in the remembered table).  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 previousFutureSurvivorSpaceSize variables ensure that no object is scanned twice, as well as
  	 detecting closure.  If this were not true, some pointers might get forwarded twice."
  
  	coInterpreter scavengeStacks.
  	self scavengeLoop.
  	self exchange: pastSpace with: futureSpace!

Item was changed:
+ ----- Method: SpurGenerationScavenger>>scavengeFutureSurvivorSpaceStartingAt: (in category 'scavenger') -----
- ----- Method: SpurGenerationScavenger>>scavengeFutureSurvivorSpaceStartingAt: (in category 'api') -----
  scavengeFutureSurvivorSpaceStartingAt: initialAddress
  	"scavengeFutureSurvivorSpaceStartingAt: does a depth-first traversal of the
+ 	 new objects starting at the one at initialAddress in futureSurvivorSpace."
- 	 new objects starting at the one at the nth word of futureSurvivorSpace."
  	| ptr |
- 	<var: #ptr type: #'char *'>
  	ptr := initialAddress.
  	[ptr < futureSpace limit] whileTrue:
  		[| obj |
+ 		 obj := manager objectStartingAt: ptr.
+ 		 ptr := manager addressAfter: obj.
+ 		 self cCoerceSimple: (self scavengeReferentsOf: obj) to: #void]!
- 		 obj := manager objectAt: ptr.
- 		 ptr := ptr + (manager byteLengthOf: obj).
- 		 self cCoerceSimple: (self scavengeReferentsOf: obj)
- 			to: #void]!

Item was changed:
+ ----- Method: SpurGenerationScavenger>>scavengeLoop (in category 'scavenger') -----
- ----- Method: SpurGenerationScavenger>>scavengeLoop (in category 'api') -----
  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."
  
  	| previousRememberedSetSize previousFutureSurvivorSpaceLimit |
  	previousRememberedSetSize := 0.
  	previousFutureSurvivorSpaceLimit := futureSpace limit.
  	self assert: futureSpace limit = futureSpace start.
  	[self scavengeRememberedSetStartingAt: previousRememberedSetSize.
  	 previousFutureSurvivorSpaceLimit = futureSpace limit ifTrue:
  		[^self].
  		
  	 previousRememberedSetSize := rememberedSetSize.
  	 self scavengeFutureSurvivorSpaceStartingAt: previousFutureSurvivorSpaceLimit.
  	 previousFutureSurvivorSpaceLimit = rememberedSetSize ifTrue:
  		[^self].
  
  	 previousFutureSurvivorSpaceLimit := futureSpace size] repeat!

Item was changed:
+ ----- Method: SpurGenerationScavenger>>scavengeReferentsOf: (in category 'scavenger') -----
- ----- Method: SpurGenerationScavenger>>scavengeReferentsOf: (in category 'api') -----
  scavengeReferentsOf: referrer
  	"scavengeReferentsOf: referrer inspects all the pointers in referrer.
  	 If any are new objects, it has them moved to FutureSurvivorSpace,
  	 and returns truth. If there are no new referents, it returns falsity."
  	<var: #referrer type: #'object *'>
+ 	| foundNewReferent |
+ 	"referrer isPointers ifFalse:
+ 		[^false]."
- 	| foundNewReferent referent |
- 	referrer isPointers ifFalse:
- 		[^self].
  	foundNewReferent := false.
+ 	0 to: (manager numPointerSlotsOf: referrer) do:
+ 		[:i| | referent |
- 	0 to: (manager lengthOf: referrer) do:
- 		[:i|
  		referent := manager fetchPointer: i ofObject: referrer.
+ 		((manager isNonImmediate: referent)
+ 		 and: [manager isYoung: referent]) ifTrue:
- 		(manager isYoung: referent) ifTrue:
  			[foundNewReferent := true.
+ 			 (manager isForwarded: referent) ifFalse:
- 			 referent isForwarded ifFalse:
  				[self copyAndForward: referent].
  			 manager
  				storePointerUnchecked: i
  				ofObject: referrer
  				withValue: (manager forwardingPointerOf: referent)]].
  	^foundNewReferent!

Item was changed:
+ ----- Method: SpurGenerationScavenger>>scavengeRememberedSetStartingAt: (in category 'scavenger') -----
- ----- Method: SpurGenerationScavenger>>scavengeRememberedSetStartingAt: (in category 'api') -----
  scavengeRememberedSetStartingAt: n
  	"scavengeRememberedSetStartingAt: n traverses objects in the remembered
  	 set starting at the nth one.  If the object does not refer to any new objects, it
  	 is removed from the set. Otherwise, its new referents are scavenged."
  	| destIndex sourceIndex |
  	sourceIndex := destIndex := n.
  	[sourceIndex < rememberedSetSize] whileTrue:
  		[| referree |
  		referree := rememberedSet at: sourceIndex.
  		(self scavengeReferentsOf: referree)
  			ifTrue:
  				[rememberedSet at: destIndex put: referree.
  				 destIndex := destIndex + 1]
  			ifFalse:
  				[referree isRemembered: false].
  		 sourceIndex := sourceIndex + 1].
  	rememberedSetSize := destIndex!

Item was changed:
  CogClass subclass: #SpurMemoryManager
(excessive size, no diff calculated)

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

Item was changed:
  ----- Method: SpurMemoryManager>>adjustAllOopsBy: (in category 'initialization') -----
  adjustAllOopsBy: bytesToShift 
  	"Adjust all oop references by the given number of bytes. This 
  	is done just after reading in an image when the new base 
  	address of the object heap is different from the base address 
  	in the image."
- 	"di 11/18/2000 - return number of objects found"
  
  	| obj |
  	<inline: false>
  	bytesToShift ~= 0 ifTrue:
+ 		[self assert: self newSpaceIsEmpty.
+ 		 obj := self firstObject.
+ 		 [self oop: obj isLessThan: freeOldSpaceStart] whileTrue:
- 		[obj := self firstObject.
- 		 [self oop: obj isLessThan: freeStart] whileTrue:
  			[(self isFreeObject: obj) ifFalse:
  				[self adjustFieldsAndClassOf: obj by: bytesToShift].
  			 obj := self objectAfter: obj]]!

Item was added:
+ ----- Method: SpurMemoryManager>>allNewSpaceObjectsDo: (in category 'object enumeration') -----
+ allNewSpaceObjectsDo: aBlock
+ 	| prevObj prevPrevObj objOop limit |
+ 	prevPrevObj := prevObj := nil.
+ 	"After a scavenge eden is empty, futureSpace is empty, and all newSpace objects are
+ 	  in pastSpace.  Objects are allocated in eden.  So enumerate only eden and pastSpace."
+ 	objOop := self objectStartingAt: scavenger eden start.
+ 	[objOop < freeStart] whileTrue:
+ 		[(self isFreeObject: objOop) ifFalse:
+ 			[aBlock value: objOop].
+ 		 prevPrevObj := prevObj.
+ 		 prevObj := objOop.
+ 		 objOop := self objectAfter: objOop limit: freeStart].
+ 	objOop := self objectStartingAt: scavenger pastSpace start.
+ 	limit := scavenger pastSpace limit.
+ 	[objOop < limit] whileTrue:
+ 		[(self isFreeObject: objOop) ifFalse:
+ 			[aBlock value: objOop].
+ 		 prevPrevObj := prevObj.
+ 		 prevObj := objOop.
+ 		 objOop := self objectAfter: objOop limit: limit].
+ 	prevPrevObj class.
+ 	prevObj class!

Item was changed:
+ ----- Method: SpurMemoryManager>>allObjectsDo: (in category 'object enumeration') -----
- ----- Method: SpurMemoryManager>>allObjectsDo: (in category 'debug support') -----
  allObjectsDo: aBlock
+ 	self allOldSpaceObjectsDo: aBlock.
+ 	self allNewSpaceObjectsDo: aBlock!
- 	<doNotGenerate>
- 	| prevObj prevPrevObj objOop |
- 	prevPrevObj := prevObj := nil.
- 	objOop := self firstObject.
- 	[self assert: objOop \\ self allocationUnit = 0.
- 	 objOop < freeStart] whileTrue:
- 		[(self isFreeObject: objOop) ifFalse:
- 			[aBlock value: objOop].
- 		 prevPrevObj := prevObj.
- 		 prevObj := objOop.
- 		 objOop := self objectAfter: objOop].
- 	prevPrevObj class.
- 	prevObj class!

Item was added:
+ ----- Method: SpurMemoryManager>>allOldSpaceObjectsDo: (in category 'object enumeration') -----
+ allOldSpaceObjectsDo: aBlock
+ 	<doNotGenerate>
+ 	| prevObj prevPrevObj objOop |
+ 	prevPrevObj := prevObj := nil.
+ 	objOop := self firstObject.
+ 	[self assert: objOop \\ self allocationUnit = 0.
+ 	 objOop < freeOldSpaceStart] whileTrue:
+ 		[(self isFreeObject: objOop) ifFalse:
+ 			[aBlock value: objOop].
+ 		 prevPrevObj := prevObj.
+ 		 prevObj := objOop.
+ 		 objOop := self objectAfter: objOop limit: freeOldSpaceStart].
+ 	prevPrevObj class.
+ 	prevObj class!

Item was removed:
- ----- Method: SpurMemoryManager>>allocateMemoryOfSize: (in category 'simulation') -----
- allocateMemoryOfSize: limit
- 	<doNotGenerate>
- 	memory := (self endianness == #little
- 					ifTrue: [LittleEndianBitmap]
- 					ifFalse: [Bitmap]) new: (limit roundUpTo: 8).
- 	freeStart := startOfMemory := 0.
- 	scavengeThreshold := newSpaceLimit := memory size * 4 "Bitmap is a 4-byte per word array"!

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 := memoryBytes + newSpaceBytes + codeBytes.
  	"leave newSpace empty for the bootstrap"
  	freeStart := newSpaceBytes + startOfMemory.
  	newSpaceStart := startOfMemory.
  	newSpaceLimit := newSpaceBytes + startOfMemory.
+ 	scavengeThreshold := memory size * 4. "Bitmap is a 4-byte per word array"
+ 	scavenger := SpurGenerationScavenger new
+ 					manager: self
+ 					memory: memory
+ 					newSpaceStart: newSpaceStart
+ 					newSpaceBytes: newSpaceBytes
+ 					edenBytes: newSpaceBytes * 5 // 7 "David's paper uses 140Kb eden + 2 x 28kb survivor spaces :-)"!
- 	scavengeThreshold := memory size * 4 "Bitmap is a 4-byte per word array"!

Item was added:
+ ----- Method: SpurMemoryManager>>byteLengthOf: (in category 'object access') -----
+ byteLengthOf: objOop 
+ 	"Answer the number of indexable bytes in the given object.
+ 	 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 changed:
  ----- Method: SpurMemoryManager>>initializeObjectMemory: (in category 'initialization') -----
  initializeObjectMemory: bytesToShift
  	"Initialize object memory variables at startup time. Assume endOfMemory is initially set (by the image-reading code) to the end of the last object in the image. Initialization redefines endOfMemory to be the end of the object allocation area based on the total available memory, but reserving some space for forwarding blocks."
  	"Assume: image reader initializes the following variables:
  		memory
  		memoryLimit
  		specialObjectsOop
  		lastHash
  	"
  	<inline: false>
  	"image may be at a different address; adjust oops for new location"
  	self adjustAllOopsBy: bytesToShift.
  
+ 	self initializeOldSpaceFirstFree: freeOldSpaceStart. "initializes endOfMemory, freeStart"
- 	self initializeOldSpaceFirstFree: endOfOldSpace. "initializes endOfMemory, freeStart"
  
  	specialObjectsOop := specialObjectsOop + bytesToShift.
  
  	"heavily used special objects"
  	nilObj		:= self splObj: NilObject.
  	falseObj	:= self splObj: FalseObject.
  	trueObj		:= self splObj: TrueObject.
  
  	"rootTableCount := 0.
  	rootTableOverflowed := false.
  	lowSpaceThreshold := 0.
  	signalLowSpace := false.
  	compStart := 0.
  	compEnd := 0.
  	fwdTableNext := 0.
  	fwdTableLast := 0.
  	remapBufferCount := 0.
  	tenuringThreshold := 2000.  ""tenure all suriving objects if survivor count is over this threshold""
  	growHeadroom := 4*1024*1024. ""four megabytes of headroom when growing""
  	shrinkThreshold := 8*1024*1024. ""eight megabytes of free space before shrinking""
  
  	""garbage collection statistics""
  	statFullGCs := 0.
  	statFullGCUsecs := 0.
  	statIncrGCs := 0.
  	statIncrGCUsecs := 0.
  	statTenures := 0.
  	statRootTableOverflows := 0.
  	statGrowMemory := 0.
  	statShrinkMemory := 0.
  	forceTenureFlag := 0.
  	gcBiasToGrow := 0.
  	gcBiasToGrowGCLimit := 0.
  	extraRootCount := 0."!

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 normalicy."
+ 	freeOldSpaceStart := freeStart.
+ 	freeStart := scavenger eden start!
- 	endOfOldSpace := freeStart.
- 	freeStart := newSpaceStart!

Item was added:
+ ----- Method: SpurMemoryManager>>isContext: (in category 'object testing') -----
+ isContext: oop
+ 	<inline: true>
+ 	^(self isNonImmediate: oop)
+ 	   and: [(self classIndexOf: oop) = ClassMethodContextCompactIndex]!

Item was added:
+ ----- Method: SpurMemoryManager>>isContextNonImm: (in category 'object testing') -----
+ isContextNonImm: oop
+ 	<inline: true>
+ 	^(self classIndexOf: oop) = ClassMethodContextCompactIndex!

Item was added:
+ ----- Method: SpurMemoryManager>>isForwarded: (in category 'object testing') -----
+ isForwarded: objOop
+ 	^(self classIndexOf: objOop) = self isForwardedClassIndexPun!

Item was added:
+ ----- Method: SpurMemoryManager>>isForwardedClassIndexPun (in category 'class table') -----
+ isForwardedClassIndexPun
+ 	^1!

Item was added:
+ ----- Method: SpurMemoryManager>>isFreeClassIndexPun (in category 'class table') -----
+ isFreeClassIndexPun
+ 	^0!

Item was changed:
+ ----- Method: SpurMemoryManager>>isFreeObject: (in category 'object testing') -----
- ----- Method: SpurMemoryManager>>isFreeObject: (in category 'header access') -----
  isFreeObject: objOop
+ 	^(self classIndexOf: objOop) = self isFreeClassIndexPun!
- 	^(self classIndexOf: objOop) = 0!

Item was changed:
  ----- Method: SpurMemoryManager>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
+ 	(#(	makeBaseFrameFor:
+ 		quickFetchInteger:ofObject:
+ 		frameOfMarriedContext:) includes: thisContext sender method selector) ifFalse:
- 	(#(makeBaseFrameFor: quickFetchInteger:ofObject:) includes: thisContext sender method selector) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was added:
+ ----- Method: SpurMemoryManager>>isYoung: (in category 'object testing') -----
+ isYoung: objOop
+ 	^self oop: objOop isLessThan: newSpaceLimit!

Item was changed:
  ----- Method: SpurMemoryManager>>lastPointerOf: (in category 'object enumeration') -----
+ lastPointerOf: objOop 
- lastPointerOf: obj 
  	"Answer the byte offset of the last pointer field of the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<api>
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt contextSize numLiterals |
+ 	fmt := self formatOf: objOop.
- 	| fmt header contextSize numLiterals |
- 	<var: 'header' type: #usqLong>
- 	header := self baseHeader: obj.
- 	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
+ 		  and: [self isContextNonImm: objOop]) ifTrue:
- 		  and: [self isContextHeader: header]) ifTrue:
  			["contexts end at the stack pointer"
+ 			contextSize := coInterpreter fetchStackPointerOf: objOop.
- 			contextSize := coInterpreter fetchStackPointerOf: obj.
  			^CtxtTempFrameStart + contextSize * BytesPerOop].
+ 		^(self numSlotsOf: objOop) * BytesPerOop  "all pointers"].
- 		^(self numSlotsOf: obj) * BytesPerOop  "all pointers"].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	numLiterals := coInterpreter literalCountOf: objOop.
- 	numLiterals := coInterpreter literalCountOf: obj.
  	^numLiterals + LiteralStart * BytesPerOop!

Item was added:
+ ----- Method: SpurMemoryManager>>numPointerSlotsOf: (in category 'object enumeration') -----
+ numPointerSlotsOf: objOop
+ 	"Answer the number of pointer fields in the given object.
+ 	 Works with CompiledMethods, as well as ordinary objects."
+ 	<api>
+ 	<inline: true>
+ 	<asmLabel: false>
+ 	| fmt contextSize numLiterals |
+ 	fmt := self formatOf: objOop.
+ 	fmt <= self lastPointerFormat ifTrue:
+ 		[(fmt = self indexablePointersFormat
+ 		  and: [self isContextNonImm: objOop]) ifTrue:
+ 			["contexts end at the stack pointer"
+ 			contextSize := coInterpreter fetchStackPointerOf: objOop.
+ 			^CtxtTempFrameStart + contextSize].
+ 		^self numSlotsOf: objOop  "all pointers"].
+ 	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
+ 
+ 	"CompiledMethod: contains both pointers and bytes"
+ 	numLiterals := coInterpreter literalCountOf: objOop.
+ 	^numLiterals + LiteralStart!

Item was added:
+ ----- Method: SpurMemoryManager>>objectStartingAt: (in category 'object enumeration') -----
+ objectStartingAt: address
+ 	"For enumerating objects find the header of the first object in a space.
+ 	 If the object starts with an overflow size field it will start at the next allocationUnit.
+ 	 c.f. numSlotsOf:"
+ 	| halfHeader numSlots |
+ 	self flag: #endianness.
+ 	halfHeader := self longAt: address + 4.
+ 	numSlots := halfHeader >> self numSlotsHalfShift bitAnd: self numSlotsMask.
+ 	^numSlots = self numSlotsMask
+ 		ifTrue: [address + self baseHeaderSize]
+ 		ifFalse: [address]!

Item was added:
+ VMStructType subclass: #SpurNewSpaceSpace
+ 	instanceVariableNames: 'start limit'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-SpurMemoryManager'!

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

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

Item was added:
+ ----- Method: SpurNewSpaceSpace>>start:limit: (in category 'initialization') -----
+ start: startAddress limit: limitAddress
+ 	start := startAddress.
+ 	limit := limitAddress!



More information about the Vm-dev mailing list