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

commits at source.squeak.org commits at source.squeak.org
Mon Sep 30 19:00:16 UTC 2013


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

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

Name: VMMaker.oscog-eem.418
Author: eem
Time: 30 September 2013, 11:57:34.417 am
UUID: d211154e-57c3-4f27-a6a2-e913d290ee2d
Ancestors: VMMaker.oscog-eem.417

Adjust scavengeLoop for the ephemeron processing condition.
No ephemerons should be fired until no new objects have been
remembered.

Change the weak & ephemeron list organization to use
allocationUnits instead of slots.  Limits newSpace to 1Gb ;-).

Write more on the algorithm in the class comment.

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

Item was changed:
  CogClass subclass: #SpurGenerationScavenger
  	instanceVariableNames: 'coInterpreter manager eden futureSpace pastSpace futureSurvivorStart rememberedSet rememberedSetSize previousRememberedSetSize weakList ephemeronList tenuringThreshold tenuringProportion numRememberedEphemerons'
  	classVariableNames: 'RememberedSetLimit RememberedSetRedZone'
  	poolDictionaries: ''
  	category: 'VMMaker-SpurMemoryManager'!
  
+ !SpurGenerationScavenger commentStamp: 'eem 9/30/2013 11:05' prior: 0!
- !SpurGenerationScavenger commentStamp: 'eem 9/27/2013 11:53' 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 
  
  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 ©1992
  and
  	Ephemerons: a new finalization mechanism
  	Barry Hayes
  	Proceedings of the 12th ACM SIGPLAN conference on Object-oriented programming, systems, languages, and applications
  	Pages 176-183 
  	ACM New York, NY, USA ©1997
  
+ See text below the variable definitions and explanation below for a full explanation of weak and ephemeron processing.
+ 
  Instance Variables
+ 	coInterpreter:					<StackInterpreterSimulator|CogVMSimulator>
+ 	eden:							<SpurNewSpaceSpace>
+ 	ephemeronList:					<Integer|nil>
+ 	futureSpace:					<SpurNewSpaceSpace>
+ 	futureSurvivorStart:				<Integer address>
+ 	manager:						<SpurMemoryManager|Spur32BitMMLESimulator et al>
+ 	numRememberedEphemerons:	<Integer>
+ 	pastSpace:						<SpurNewSpaceSpace>
+ 	previousRememberedSetSize:	<Integer>
+ 	rememberedSet:				<CArrayAccessor on: Array>
+ 	rememberedSetSize:			<Integer>
+ 	tenuringProportion:				<Float>
+ 	tenuringThreshold:				<Integer address>
+ 	weakList:						<Integer|nil>
- 	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
  
+ manager
+ 	- the Spur memory manager
+ 
  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
  
+ previousRememberedSetSize:
+ 	- the size of the remembered set before scavenging objects in future space.
+ 
+ numRememberedEphemerons
+ 	- the number of unscavenged ephemerons at the front of the rememberedSet.
+ 
+ ephemeronList
+ 	- the head of the list of corpses of unscavenged ephemerons reached in the current phase
+ 
+ weakList
+ 	- the head of the list of corpses of weak arrays reached during the scavenge.
+ 
  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
+ 
+ Weakness and Ephemerality in the Scavenger.
+ Weak arrays should not hold onto their referents (except from their strong fileds, their named inst vars).  Ephemerons are objects that implement instance-based finalization; attaching an ephemeron to an object keeps that object alive and causes the ephemeron to "fire" when the object is only reachable from the ephemeron (or other ephemerons & weak arrays).  They are a special kind of Associations that detect when their keys are about to die, i.e. when an ephemeron's key is not reachable from the roots except from weak arrays and other ephemerons with about-to-die keys.  Note that if an ephemeron's key is not about to die then references from the rest of the ephemeron can indeed prevent ephemeron keys from dying.
+ 
+ The scavenger is concerned with collecting objects in new space, therefore it ony deals with weak arrays and ephemerons that are either in the remembered set or in new space.  By deferring scanning these objects until other reachable objects have been scavenged, the scavenger can detect dead or dying references.
+ 
+ Weak Array Processing
+ In the case of weak arrays this is simple.  The scavenger refuses to scavenge the referents of weak arrays in scavengeReferentsOf: until the entire scavenge is over.  It then scans the weak arrays in the remembered set and in future space and nils all fields in them that are referring to unforwarded objects in eden and past space, because these objects have not survived the scavenge.  The root weak arrays remaining to be scavenged are in the remembered table.  Surviving weak arrays in future space are collected on a list.  The list is threaded through the corpses of weak arrays in eden and/or past space.  weakList holds the slot offset of the first weak array found in eden and/or past space.  The next offset is stored in the weak array corpse's identityHash and format fields (22 bits & 5 bits of allocationUnits, for a max new space size of 2^28 bytes, 256Mb).  The list is threaded throguh corpses, but the surviving arrays are pointed to by the corpses' forwarding pointers.
+ 
+ Ephemeron Processing
+ The case of ephemerons is a little more complicated because an ephemeron's key should survive.  The scavenger is cyclical.  It scavenges the remembered set, which may copy and forward surviving objects in past and/or eden spaces to future space.  It then scavenges those promoted objects in future space until no more are promoted, which may in turn remember more objects.  The cycles continue until no more objects get promoted to future space and no more objects get remembered.  At this point all surviving objecta are in futureSpace.
+ 
+ So if the scavenger does not scan ephemerons in the remembered set or in future space until the scavenger finishes cycling, it can detect ephemerons whose keys are about to die because these will be unforwarded objects in eden and/or past space.  Ephemerons encountered in the remembered set are either processed like ordinary objects if their keys have been promoted to futureSpace, or are moved to the front of the rememberedSet (because, dear reader, it is a sequence) if their keys have not been promoted.  Ephemerons encountered in scavengeReferentsOf: are either scanned like normal objects if their keys have been promoted, or added to the ephemeronList, organized identically to the weakList, if their keys are yet to be promoted.  Since references from other ephemerons with surviving keys to ephemeron keys can and should prevent the ephemerons whose keys they are from firing the scavenger does not fire ephemerons unless all unscavenged ephemerons have unscavenged keys.  So the unscavenged ephemerons (the will be at the beginning of the remembered set and on the ephemeronList) are scanned and any that have promoted keys are scavenged.  But if no unscavenged ephemerons have surviving keys then all the unscavenged ephemerons are fired and then scavenged.  This in turn may remember more objects and promote more objects to future space, and encounter more unscavenged ephemerons.  So the scavenger continues until no more objects are remembered, no more objects are promoted to future space and no more unscavenged ephemerons exist.!
- !

Item was changed:
  ----- Method: SpurGenerationScavenger>>addToEphemeronList: (in category 'weakness and ephemerality') -----
  addToEphemeronList: ephemeronCorpse
  	"ephemeronCorpse is the corpse of an ephemeron 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."
  	| ephemeronListOffset |
  	self assert: (manager isYoung: ephemeronCorpse).
  	self assert: (manager isForwarded: ephemeronCorpse).
  	self assert: (self isScavengeSurvivor: (manager keyOfEphemeron: (manager followForwarded: ephemeronCorpse))) not.
  
  	ephemeronListOffset := ephemeronList ifNil: 0.
  	self setCorpseOffsetOf: ephemeronCorpse to: ephemeronListOffset.
+ 	ephemeronList := self corpseOffsetOf: ephemeronCorpse.
- 	ephemeronList := ephemeronCorpse - manager startOfMemory >> manager shiftForWord.
  	self assert: (self firstCorpse: ephemeronList) = ephemeronCorpse!

Item was changed:
  ----- 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."
  	| weakListOffset |
  	self assert: (manager isYoung: weakCorpse).
  	self assert: (manager isForwarded: weakCorpse).
  
  	weakListOffset := weakList ifNil: 0.
  	self setCorpseOffsetOf: weakCorpse to: weakListOffset.
+ 	weakList := self corpseOffsetOf: weakCorpse.
- 	weakList := weakCorpse - manager startOfMemory >> manager shiftForWord.
  	self assert: (self firstCorpse: weakList) = weakCorpse!

Item was changed:
  ----- Method: SpurGenerationScavenger>>corpseForCorpseOffset: (in category 'weakness and ephemerality') -----
  corpseForCorpseOffset: corpseOffset
  	"Use the identityHash and format fields to construct a 27 bit offset through
+ 	 non-future newSpace and use this to implement lists for weak array and
+ 	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30 bytes
+ 	 or 1Gb, big enough for newSpace for a good few years yet."
+ 	^corpseOffset << manager shiftForAllocationUnit + manager startOfMemory!
- 	 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."
- 	^corpseOffset << manager shiftForWord + manager startOfMemory!

Item was added:
+ ----- Method: SpurGenerationScavenger>>corpseOffsetOf: (in category 'weakness and ephemerality') -----
+ corpseOffsetOf: corpse
+ 	"Answer the offset of the corpse in newSpace as a multiple of allocationUnits.
+ 	 Use the identityHash and format fields to construct a 27 bit offset through
+ 	 non-future newSpace and use this to implement lists for weak array and
+ 	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30
+ 	 bytes or 1Gb, big enough for newSpace for a good few years yet."
+ 	^corpse - manager startOfMemory >> manager shiftForAllocationUnit.!

Item was changed:
  ----- 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."
  	^self corpseForCorpseOffset: headOfCorpseList!

Item was changed:
  ----- Method: SpurGenerationScavenger>>nextCorpseOffset: (in category 'weakness and ephemerality') -----
  nextCorpseOffset: corpse
  	"Answer the offset of the next corpse to corpse, which is zero if none.
  	 Use the identityHash and format fields to construct a 27 bit offset through
+ 	 non-future newSpace and use this to implement lists for weak array and
+ 	 ephemeron processing.  27 bits of 8 byte allocationUnits units is 2 ^ 30 bytes
+ 	 or 1Gb, big enough for newSpace for a good few years yet."
- 	 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."
  	^(manager rawHashBitsOf: corpse) << manager formatFieldWidthShift
  	 + (manager formatOf: corpse)!

Item was changed:
  ----- Method: SpurGenerationScavenger>>nextCorpseOrNil: (in category 'weakness and ephemerality') -----
+ nextCorpseOrNil: corpse
+ 	"corpse is the corpse of a weak array that has been added to the weakList.
- 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."
+ 	| listOffset |
+ 	self assert: (manager isYoung: corpse).
+ 	listOffset := self nextCorpseOffset: corpse.
+ 	^listOffset ~= 0 ifTrue:
+ 		[self corpseForCorpseOffset: listOffset]!
- 	| weakListOffset |
- 	self assert: (manager isYoung: weakCorpse).
- 	weakListOffset := self nextCorpseOffset: weakCorpse.
- 	^weakListOffset ~= 0 ifTrue:
- 		[weakListOffset << manager shiftForWord + manager startOfMemory]!

Item was changed:
  ----- Method: SpurGenerationScavenger>>processEphemerons (in category 'weakness and ephemerality') -----
  processEphemerons
+ 	"There are ephemerons to be scavenged.  Scavenge them and fire any whose keys are
+ 	 still in pastSpace and/or eden.  The unscavenged ephemerons in this cycle can only be
+ 	 fired if all the unscavenged ephemerons in this cycle are firable, because references
+ 	 to ephemeron keys from unfired ephemerons should prevent the ephemerons with
+ 	 those keys from firing.  So scavenge ephemerons with surviving keys, and only if none
+ 	 are found, fire ephemerons with unreferenced keys, and scavenge them.   Read the
+ 	 class comment for a more in-depth description of the algorithm."
- 	"There are ephemerons to be scavenged. Scavenge them
- 	 and fire any whose keys are still in pastSpace and/or eden.
- 	 The ephemerons in this cycle can only be fired if all the
- 	 ephemerons in this cycle are firable, because references
- 	 to ephemeron keys from unfired ephemerons should prevent
- 	 the ephemerons with those keys from firing.  So scavenge
- 	 ephemerons with surviving keys, and only if none are found,
- 	 fire ephemerons with unreferenced keys, and scavenge them."
  	| unfiredEphemeronsScavenged |
  	unfiredEphemeronsScavenged := self scavengeUnfiredEphemeronsInRememberedSet.
  	self scavengeUnfiredEphemeronsOnEphemeronList ifTrue:
  		[unfiredEphemeronsScavenged := true].
- 	"If no unfired ephemerons were scavenged, then all ephemerons in this cycle can be fired."
  	unfiredEphemeronsScavenged ifFalse:
  		[self fireEphemeronsInRememberedSet.
  		 self fireEphemeronsOnEphemeronList]!

Item was changed:
  ----- 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. Read the class comment
+ 	 for a more in-depth description of the algorithm."
- 	"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 old
+ 	 ones (all in the remembered table), then the stack zone.  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.  Then any sdurviving weakArrays and
+ 	 weakArrays in the remembered set can be processed and their dead elements nilled.
- 	 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.
  
  	 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.  Read the class comment for a more in-depth description of the algorithm."
- 	 ephemerons."
  
  	| previousFutureSurvivorStart firstTime |
  	self assert: futureSurvivorStart = futureSpace start. "future space should be empty at the start"
  
  	weakList := ephemeronList := nil.
  	numRememberedEphemerons := 0.
  	firstTime := true.
  	previousRememberedSetSize := 0.
  	previousFutureSurvivorStart := futureSurvivorStart.
  
  	[self scavengeRememberedSetStartingAt: previousRememberedSetSize.
  	 previousRememberedSetSize := rememberedSetSize.
  	 firstTime ifTrue:
  		[coInterpreter mapInterpreterOops.
  		 firstTime := false].
  	 "if nothing more copied and forwarded (or remembered by mapInterpreterOops)
  	  to scavenge, and no ephemerons to process, scavenge is done."
  	 (previousRememberedSetSize = rememberedSetSize
  	  and: [previousFutureSurvivorStart = futureSurvivorStart
  	  and: [numRememberedEphemerons = 0
  	  and: [ephemeronList isNil]]]) ifTrue:
  		[^self].
  
  	 self scavengeFutureSurvivorSpaceStartingAt: previousFutureSurvivorStart.
- 	 "if no more roots created to scavenge, and no ephemerons to process, scavenge is done."
- 	 (previousRememberedSetSize = rememberedSetSize
- 	  and: [numRememberedEphemerons = 0
- 	  and: [ephemeronList isNil]]) ifTrue:
- 		[^self].
- 
  	 previousFutureSurvivorStart := futureSurvivorStart.
+ 
+ 	 "no more roots created to scavenge..."
+ 	 previousRememberedSetSize = rememberedSetSize ifTrue:
+ 		[(numRememberedEphemerons = 0
+ 		  and: [ephemeronList isNil]) ifTrue:
+ 			[^self]. "no ephemerons to process, scavenge is done."
+ 
+ 		 "all reachable objects in this cycle have been promoted to futureSpace.
+ 		  ephemerons can now be processed."
+ 		 self processEphemerons]] repeat!
- 	 (numRememberedEphemerons > 0
- 	  or: [ephemeronList notNil]) ifTrue:
- 		[self processEphemerons]] repeat!

Item was changed:
  ----- Method: SpurGenerationScavenger>>setCorpseOffsetOf:to: (in category 'weakness and ephemerality') -----
  setCorpseOffsetOf: corpse to: offset
  	"Set the offset of the corpse's next corpse to offset.  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 of 8 byte allocationUnits units is
+ 	 2 ^ 30 bytes or 1Gb, big enough for newSpace for a good few years yet."
- 	 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."
  	manager
  		setHashBitsOf: corpse
  			to: offset >> manager formatFieldWidthShift;
  		setFormatOf: corpse
  			to: (offset bitAnd: manager formatMask)!

Item was added:
+ ----- Method: SpurMemoryManager>>shiftForAllocationUnit (in category 'word size') -----
+ shiftForAllocationUnit
+ 	^3!



More information about the Vm-dev mailing list