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

commits at source.squeak.org commits at source.squeak.org
Fri Sep 27 00:23:47 UTC 2013


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

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

Name: VMMaker.oscog-eem.415
Author: eem
Time: 26 September 2013, 5:20:16.794 pm
UUID: 73fb10dc-25ce-427c-b0ad-976524bc2941
Ancestors: VMMaker.oscog-eem.414

Implement weakArray processing in the scavenger (plus a skeleton
for ephemeron processing).

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

Item was changed:
  CogClass subclass: #SpurGenerationScavenger
+ 	instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize weakList ephemeronList tenuringThreshold tenuringProportion'
- 	instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize tenuringThreshold tenuringProportion'
  	classVariableNames: 'RememberedSetLimit RememberedSetRedZone'
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!
  
  !SpurGenerationScavenger commentStamp: 'eem 9/24/2013 13:04' prior: 0!
  SpurGenerationScavenger is an implementation of David Ungar's Generation Scavenging garbage collection algorithm.  See
  	Generation Scavenging, A Non-disruptive, High-Performance Storage Reclamation Algorithm
  	David Ungar
  	Proceeding
  	SDE 1 Proceedings of the first ACM SIGSOFT/SIGPLAN software engineering symposium on Practical software development environments
  	Pages 157 - 167 
  	ACM New York, NY, USA ©1984 
  	ISBN:0-89791-131-8
  
  Also relevant are
  	An adaptive tenuring policy for generation scavengers
  	David Ungar & Frank Jackson
  	ACM Transactions on Programming Languages and Systems (TOPLAS) TOPLAS Homepage archive
  	Volume 14 Issue 1, Jan. 1992 
  	Pages 1 - 27 
  	ACM New York, NY, USA
  
  Instance Variables
  	coInterpreter:			<StackInterpreterSimulator|CogVMSimulator>
  	eden:					<SpurNewSpaceSpace>
  	futureSpace:			<SpurNewSpaceSpace>
  	futureSurvivorStart:		<Integer address>
  	manager:				<SpurMemoryManager|Spur32BitMMLESimulator et al>
  	pastSpace:				<SpurNewSpaceSpace>
  	rememberedSet:		<CArrayAccessor on: Array>
  	rememberedSetSize:	<Integer>
  	tenuringProportion:		<Float>
  	tenuringThreshold:		<Integer address>
  
  coInterpreter
  	- the interpreter/vm, in this context, the mutator
  
  eden
  	- the space containing newly created objects
  
  futureSpace
  	- the space to which surviving objects are copied during a scavenge
  
  futureSurvivorStart
  	- the allocation pointer into futureSpace
  
  manager
  	- the Spur memory manager
  
  pastSpace
  	- the space surviving objects live in until the next scavenge
  
  rememberedSet
  	- the root old space objects that refer to objects in new space; a scavenge starts form these roots and the interpreter's stack
  
  rememberedSetSize
  	- the size of the remembered set, also the first unused index in the rememberedSet
  
  tenuringProportion
  	- the amount of pastSpace below which the system will not tenure unless futureSpace fills up, and above which it will eagerly tenure
  
  tenuringThreshold
  	- the pointer into pastSpace below which objects will be tenured
  !

Item was added:
+ ----- Method: SpurGenerationScavenger>>addToWeakList: (in category 'weakness and ephemerality') -----
+ addToWeakList: weakCorpse
+ 	"weakCorpse is the corpse of a weak array that was copied and forwarded.
+ 	 Later on its surviving copy must be scanned to nil weak references.
+ 	 Thread the corpse onto the weakList.  Later, the weakList can be followed, and
+ 	 the forwarding pointer followed to locate the survivor.  Use the identityHash
+ 	 and format fields to construct a 27 bit offset through non-future newSpace and
+ 	 use this to implement the list. 27 bits is 2 ^ 27 slots, or at least 0.5Gb, big enough
+ 	 for any newSpace size for the near future."
+ 	| weakListIndex |
+ 	self assert: (manager isYoung: weakCorpse).
+ 	weakListIndex := weakList ifNil: 0.
+ 	manager
+ 		setHashBitsOf: weakCorpse
+ 			to: weakListIndex >> manager formatFieldWidthShift;
+ 		setFormatOf: weakCorpse
+ 			to: (weakListIndex bitAnd: manager formatMask).
+ 	weakList := weakCorpse - manager startOfMemory >> manager shiftForWord.
+ 	self assert: (self firstCorpse: weakList) = weakCorpse!

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.  If the object is weak
+ 	 then corpse is threaded onto the weakList for later treatment."
- 	 It leaves a forwarding pointer behind."
  	<inline: true>
+ 	| bytesInObject newLocation hash isWeak |
- 	| bytesInObject newLocation hash |
  	bytesInObject := manager bytesInObject: survivor.
  	newLocation := ((self shouldBeTenured: survivor)
  					  or: [futureSurvivorStart + bytesInObject > futureSpace limit])
  						ifTrue: [self copyToOldSpace: survivor]
  						ifFalse: [self copyToFutureSpace: survivor bytes: bytesInObject].
  	hash := manager rawHashBitsOf: survivor.
  	hash ~= 0 ifTrue:
  		[manager setHashBitsOf: newLocation to: hash].
+ 	"Alas forward:to: smashes the format field and so destroys the weakness
+ 	 property.  Test it before forwarding."
+ 	isWeak := manager isWeakNonImm: survivor.
  	manager forward: survivor to: newLocation.
+ 	isWeak ifTrue:
+ 		[self addToWeakList: survivor].
  	^newLocation!

Item was added:
+ ----- Method: SpurGenerationScavenger>>firstCorpse: (in category 'weakness and ephemerality') -----
+ firstCorpse: headOfCorpseList
+ 	"Use the identityHash and format fields to construct a 27 bit offset through
+ 	 non-future newSpace and use this to implement lists of corpses for weak
+ 	 array and ephemeron processing. 27 bits is 2 ^ 27 slots, or at least 0.5Gb;
+ 	 big enough for any newSpace size for the near future."
+ 	^headOfCorpseList << manager shiftForWord + manager startOfMemory!

Item was added:
+ ----- Method: SpurGenerationScavenger>>isScavengeSurvivor: (in category 'weakness and ephemerality') -----
+ isScavengeSurvivor: oop
+ 	"Answer whether the oop has survived a scavenge.  This is equivalent to
+ 	 	^(manager isImmediate: oop)
+ 		  or: [((manager isInEden: oop) or: [(manager isInPastSpace: oop)]) not]"
+ 	^(manager isImmediate: oop)
+ 	  or: [(manager isYoung: oop) not
+ 	  or: [(manager isInFutureSpace: oop)]]!

Item was added:
+ ----- Method: SpurGenerationScavenger>>nextCorpseOrNil: (in category 'weakness and ephemerality') -----
+ nextCorpseOrNil: weakCorpse
+ 	"weakCorpse is the corpse of a weak array that has been added to the weakList.
+ 	 Answer the next object on the list, or nil if none.
+ 	 Use the identityHash and format fields to construct a 27 bit offset through
+ 	 non-future newSpace and use this to implement the list. 27 bits is 2 ^ 27 slots,
+ 	 or at least 0.5Gb, big enough for any newSpace size for the near future."
+ 	| weakListIndex |
+ 	self assert: (manager isYoung: weakCorpse).
+ 	weakListIndex := (manager rawHashBitsOf: weakCorpse) << manager formatFieldWidthShift
+ 						+ (manager formatOf: weakCorpse).
+ 	^weakListIndex ~= 0 ifTrue:
+ 		[weakListIndex << manager shiftForWord + manager startOfMemory]!

Item was added:
+ ----- Method: SpurGenerationScavenger>>processEphemeronList (in category 'weakness and ephemerality') -----
+ processEphemeronList
+ 	"There are ephemerons to be scavenged. Scavenge them
+ 	  and fire any whose keys are still in pastSpace and/or eden."
+ 	^self shouldBeImplemented!

Item was added:
+ ----- Method: SpurGenerationScavenger>>processWeakSurvivor: (in category 'weakness and ephemerality') -----
+ processWeakSurvivor: weakObj
+ 	"Process a weak survivor on the weakList.  Those of its fields
+ 	 which have not survived the scavenge should be nilled, and if any
+ 	 are, the coInterpreter should be informed via signalFinalization:."
+ 	| weakObjShouldMourn |
+ 	weakObjShouldMourn := false.
+ 	(manager numStrongSlotsOf: weakObj)
+ 		to: (manager numSlotsOf: weakObj) - 1
+ 		do: [:i| | referent |
+ 			referent := manager fetchPointer: i ofObject: weakObj.
+ 			"Referent could be forwarded due to scavenging or a become:, don't assume."
+ 			((manager isNonImmediate: referent)
+ 			and: [manager isForwarded: referent]) ifTrue:
+ 				[referent := manager followForwarded: referent.
+ 				 (self isScavengeSurvivor: referent) ifTrue:
+ 					[manager storePointer: i ofObject: weakObj withValue: referent]].
+ 			(self isScavengeSurvivor: referent)
+ 				ifFalse:
+ 					[weakObjShouldMourn := true.
+ 					 manager
+ 						storePointerUnchecked: i
+ 						ofObject: weakObj
+ 						withValue: manager nilObject]
+ 				ifTrue:
+ 					[self assert: referent = (manager fetchPointer: i ofObject: weakObj)]].
+ 	weakObjShouldMourn ifTrue:
+ 		[coInterpreter signalFinalization: weakObj]!

Item was added:
+ ----- Method: SpurGenerationScavenger>>processWeaklings (in category 'weakness and ephemerality') -----
+ processWeaklings
+ 	"Go through the remembered set and the weak list, nilling
+ 	 references to any objects that didn't survive the scavenge."
+ 	| i rootObj weakCorpse weakObj |
+ 	i := 0.
+ 	[i < rememberedSetSize] whileTrue:
+ 		[rootObj := rememberedSet at: i.
+ 		(manager isWeakNonImm: rootObj)
+ 			ifTrue:
+ 				[self processWeakSurvivor: rootObj.
+ 				 "If no more referents, remove by overwriting with the last element in the set."
+ 				 (manager hasYoungReferents: rootObj)
+ 					ifFalse:
+ 						[manager setIsRememberedOf: rootObj to: false.
+ 						 i + 1 < rememberedSetSize ifTrue:
+ 							[rememberedSet at: i put: (rememberedSet at: rememberedSetSize - 1)].
+ 						 rememberedSetSize := rememberedSetSize - 1]
+ 					ifTrue: [i := i + 1]]
+ 			ifFalse: [i := i + 1]].
+ 	weakList ifNotNil:
+ 		[weakCorpse := self firstCorpse: weakList.
+ 		 [weakCorpse notNil] whileTrue:
+ 			[self assert: (manager isForwarded: weakCorpse).
+ 			 weakObj := manager followForwarded: weakCorpse.
+ 			 self processWeakSurvivor: weakObj.
+ 			 weakCorpse := self nextCorpseOrNil: weakCorpse].
+ 		weakList := nil]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavenge (in category 'scavenger') -----
  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.
  
  	 Answer the limit of pastSpace, to allow the memory manager to bounds check survivors."
  
  	self scavengeLoop.
+ 	self processWeaklings.
  	self computeTenuringThreshold.
  	self exchangeSurvivorSpaces.
  	^self initFutureSpaceStart!

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.
- 	 detecting closure.  If this were not true, some pointers might get forwarded twice."
  
+ 	 An extension of the algorithm presented in David's original paper is to handle weak arrays and ephemerons.
+ 	 Weak arrays should not have their weak referents scavenged unless there are strong references to them.
+ 	 Ephemerons should fire if their key is not reachable other than from ephemerons and weak arrays.
+ 	 Handle this by maintaining a list for weak arrays and a list for ephemerons, which allow scavenging these
+ 	 objects once all other objects in new space have been scavenged, hence allowing the scavenger to
+ 	 detect which referents in new space of weak arrays are dead and of ephemeron keys are only live due to
+ 	 ephemerons."
+ 
  	| firstTime previousRememberedSetSize previousFutureSurvivorStart |
  	self assert: futureSurvivorStart = futureSpace start. "future space should be empty at the start"
+ 	weakList := ephemeronList := nil.
  	firstTime := true.
  	previousRememberedSetSize := 0.
  	previousFutureSurvivorStart := futureSurvivorStart.
  	[self scavengeRememberedSetStartingAt: previousRememberedSetSize.
  	 previousRememberedSetSize := rememberedSetSize.
  	 firstTime ifTrue:
  		[coInterpreter mapInterpreterOops.
  		 firstTime := false].
  	 "nothing more copied and forwarded (or remembered by mapInterpreterOops)
  	  to scavenge so scavenge is done."
  	 (previousRememberedSetSize = rememberedSetSize
+ 	  and: [previousFutureSurvivorStart = futureSurvivorStart
+ 	  and: [ephemeronList isNil]]) ifTrue:
- 	  and: [previousFutureSurvivorStart = futureSurvivorStart]) ifTrue:
  		[^self].
  
  	 self scavengeFutureSurvivorSpaceStartingAt: previousFutureSurvivorStart.
  	 "no more roots created to scavenge, so scavenge is done."
+ 	 (previousRememberedSetSize = rememberedSetSize
+ 	  and: [ephemeronList isNil]) ifTrue:
- 	 previousRememberedSetSize = rememberedSetSize ifTrue:
  		[^self].
  
+ 	 previousFutureSurvivorStart := futureSurvivorStart.
+ 	 ephemeronList notNil ifTrue:
+ 		[self processEphemeronList]] repeat!
- 	 previousFutureSurvivorStart := futureSurvivorStart] repeat!

Item was changed:
  ----- Method: SpurGenerationScavenger>>scavengeReferentsOf: (in category 'scavenger') -----
  scavengeReferentsOf: referrer
  	"scavengeReferentsOf: referrer inspects all the pointers in referrer.
  	 If any are new objects, it has them moved to FutureSurvivorSpace,
+ 	 and answers truth. If there are no new referents, it answers falsity.
+ 	 To handle weak arrays only scavenge string slots and answer true
+ 	 if the referrer is weak, so that it won't be removed from the
+ 	 remembered set until later."
- 	 and answers truth. If there are no new referents, it answers falsity."
  	| foundNewReferent |
  	"forwarding objects should be followed by callers,
  	 unless the forwarder is a root in the remembered table."
  	self assert: ((manager isForwarded: referrer) not
  				or: [manager isRemembered: referrer]).
  	foundNewReferent := false.
+ 	0 to: (manager numStrongSlotsOf: referrer) - 1 do:
- 	0 to: (manager numPointerSlotsOf: referrer) - 1 do:
  		[:i| | referent newLocation |
  		referent := manager fetchPointer: i ofMaybeForwardedObject: referrer.
  		(manager isNonImmediate: referent) ifTrue:
  			["a forwarding pointer could be because of become: or scavenging."
  			 referent := (manager isForwarded: referent)
  								ifTrue: [manager followForwarded: referent]
  								ifFalse: [referent].
  			 (manager isYoung: referent)
  				ifTrue:
  					["if target is already in future space forwarding pointer was due to a become:."
  					 (manager isInFutureSpace: referent)
  						ifTrue: [newLocation := referent]
  						ifFalse:
  							[(manager isForwarded: referent)
  								ifTrue: [self halt. "can this even happen?"
  									newLocation := manager followForwarded: referent]
  								ifFalse: [newLocation := self copyAndForward: referent]].
  					 (manager isYoung: newLocation) ifTrue:
  						[foundNewReferent := true].
  					 manager storePointerUnchecked: i ofMaybeForwardedObject: referrer withValue: newLocation]
  				ifFalse:
  					[manager storePointerUnchecked: i ofMaybeForwardedObject: referrer withValue: referent]]].
+ 	^foundNewReferent or: [manager isWeakNonImm: referrer]!
- 	^foundNewReferent!

Item was changed:
  ----- Method: SpurGenerationScavengerSimulator>>copyAndForward: (in category 'scavenger') -----
  copyAndForward: survivor
  	| newLocation |
+ 	"(#(16r167280 16r19A670) includes: survivor) ifTrue: [self halt]."
  	true ifTrue: [^super copyAndForward: survivor.].
- 	"(#(16r13BC78 16r13BD68 16r1ED780 16r1FC558) includes: survivor) ifTrue: [self halt]."
  	newLocation := super copyAndForward: survivor.
  	comeFroms at: newLocation put: survivor.
  	"((manager isContextNonImm: newLocation)
  	 and: [#(16r11D6988 16r11D6A48 16r11D6AC0 16r11D6B80) includes: newLocation]) ifTrue:
  		[self halt]."
  	^newLocation!

Item was added:
+ ----- Method: SpurMemoryManager>>fixedFieldsOfClass: (in category 'object format') -----
+ fixedFieldsOfClass: objOop
+ 	^self fixedFieldsOfClassFormat: (self formatOfClass: objOop)!

Item was added:
+ ----- Method: SpurMemoryManager>>formatFieldWidthShift (in category 'header format') -----
+ formatFieldWidthShift
+ 	"The format field contains 5 bits."
+ 	^5!

Item was added:
+ ----- Method: SpurMemoryManager>>hasYoungReferents: (in category 'object testing') -----
+ hasYoungReferents: objOop
+ 	0 to: (self numPointerSlotsOf: objOop) - 1 do:
+ 		[:i| | oop |
+ 		oop := self fetchPointer: i ofObject: objOop.
+ 		((self isNonImmediate: oop)
+ 		 and: [self isYoung: oop]) ifTrue:
+ 			[^true]].
+ 	^false!

Item was added:
+ ----- Method: SpurMemoryManager>>isWeakNonImm: (in category 'object testing') -----
+ isWeakNonImm: objOop
+ 	^(self formatOf: objOop) = self weakArrayFormat!

Item was changed:
+ ----- Method: SpurMemoryManager>>numPointerSlotsOf: (in category 'object access') -----
- ----- 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 forwardedFormat ifTrue: [^1].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
  	numLiterals := coInterpreter literalCountOf: objOop.
  	^numLiterals + LiteralStart!

Item was added:
+ ----- Method: SpurMemoryManager>>numStrongSlotsOf: (in category 'object access') -----
+ numStrongSlotsOf: objOop
+ 	"Answer the number of strong 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 weakArrayFormat ifTrue:
+ 			[^self fixedFieldsOfClass: (self fetchClassOfNonImm: objOop)].
+ 		 (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 forwardedFormat ifTrue: [^1].
+ 	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
+ 
+ 	"CompiledMethod: contains both pointers and bytes"
+ 	numLiterals := coInterpreter literalCountOf: objOop.
+ 	^numLiterals + LiteralStart!



More information about the Vm-dev mailing list