[squeak-dev] The Inbox: Collections-cmm.360.mcz

commits at source.squeak.org commits at source.squeak.org
Thu May 20 14:58:45 UTC 2010


A new version of Collections was added to project The Inbox:
http://source.squeak.org/inbox/Collections-cmm.360.mcz

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

Name: Collections-cmm.360
Author: cmm
Time: 18 May 2010, 7:31:17.533 pm
UUID: 82061243-bfe9-4349-945c-15e696f33bee
Ancestors: Collections-ul.359

This is Igor's new WeakFinalizationList and WeakFinalizationRegistry, used in conjunction with other updates to provide major significant improvements in finalization.

=============== Diff against Collections-ul.359 ===============

Item was added:
+ ----- Method: WeakFinalizationRegistry>>keys (in category 'accessing') -----
+ keys
+ 
+ 	^ valueDictionary keys!

Item was added:
+ ----- Method: WeakFinalizationRegistry classSide>>new (in category 'instance creation') -----
+ new
+ 	| registry |
+ 	registry := super new.
+ 	WeakArray addWeakDependent: registry.
+ 	^registry
+ !

Item was added:
+ ----- Method: WeakFinalizerItem>>object (in category 'accessing') -----
+ object
+ 	^ self at: 1!

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

Item was added:
+ ----- Method: WeakFinalizationRegistry>>add: (in category 'adding') -----
+ add: anObject
+ 	"Add anObject to the receiver. Store the object as well as the associated executor."
+ 	
+ 	^self add: anObject executor: anObject executor!

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

Item was added:
+ ----- Method: WeakFinalizerItem>>clear (in category 'accessing') -----
+ clear
+ 	list := next := nil.!

Item was added:
+ ----- Method: WeakFinalizationList>>swapWithNil (in category 'accessing') -----
+ swapWithNil
+ 
+ 	| head |
+ 	head := first.
+ 	first := nil.
+ 	^ head!

Item was added:
+ ----- Method: WeakFinalizationRegistry>>species (in category 'accessing') -----
+ species
+ 	^Set!

Item was added:
+ ----- Method: WeakFinalizationRegistry>>do: (in category 'accessing') -----
+ do: aBlock
+ 	^ valueDictionary keysDo: aBlock
+ !

Item was added:
+ ----- Method: WeakFinalizationRegistry>>remove:ifAbsent: (in category 'accessing') -----
+ remove: oldObject ifAbsent: exceptionBlock
+ 	"Remove oldObject as one of the receiver's elements."
+ 	| value |
+ 	oldObject ifNil: [ ^nil ].
+ 	
+ 	value := valueDictionary removeKey: oldObject ifAbsent: [ ^ exceptionBlock value ].
+ 	value clear.
+ 	^ oldObject!

Item was added:
+ ----- Method: WeakFinalizerItem classSide>>new (in category 'as yet unclassified') -----
+ new
+ 	^ self basicNew: 1!

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

Item was added:
+ ----- Method: WeakFinalizerItem>>list:object:executor: (in category 'initialize-release') -----
+ list: weakFinalizationList object: anObject executor: anExecutor
+ 	self assert: (weakFinalizationList class == WeakFinalizationList).
+ 	list := weakFinalizationList.
+ 	self at: 1 put: anObject.
+ 	executor := anExecutor!

Item was added:
+ Object subclass: #WeakFinalizationList
+ 	instanceVariableNames: 'first'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-Weak'!
+ 
+ !WeakFinalizationList commentStamp: 'Igor.Stasenko 3/8/2010 21:50' prior: 0!
+ IMPORTANT!!!!!!
+ 
+ This class is a special object, recognized by VM.
+ Its only purpose is to 
+ a) identify a special kind of objects who usually having a weak references but
+   also having an instance of me held by first non-weak fixed slot (instance variable).
+ 
+ b) a 'first' instance variable points to the head of a list of items, reported by VM which has weak references which became garbage during last garbage collection!

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

Item was added:
+ ----- Method: WeakFinalizationRegistry>>add:executor: (in category 'adding') -----
+ add: anObject executor: anExecutor
+ 
+ 	valueDictionary at: anObject put: 
+ 		(WeakFinalizerItem new list: list object: anObject executor: anExecutor).
+ 		
+ 	^ anObject
+ !

Item was added:
+ ----- Method: WeakFinalizationRegistry>>postCopy (in category 'copying') -----
+ postCopy
+ 	"should we prohibit any attempts to copy receiver?"
+ 	| oldDict |
+ 	oldDict := valueDictionary.
+ 	list := WeakFinalizationList new.
+ 	valueDictionary := WeakIdentityKeyDictionary new.
+ 	
+ 	oldDict keysAndValuesDo: [:key :value |
+ 		valueDictionary at: key put: (value copyWithList: list)
+ 		]!

Item was added:
+ ----- Method: WeakFinalizerItem>>copyWithList: (in category 'copying') -----
+ copyWithList: aList
+ 
+ 	^ self copy list: aList!

Item was added:
+ ----- Method: WeakFinalizationRegistry>>initialize (in category 'initialize-release') -----
+ initialize
+ 	valueDictionary := WeakIdentityKeyDictionary new.
+ 	list ifNil: [ list := WeakFinalizationList new  ].!

Item was added:
+ ----- Method: WeakFinalizerItem>>list: (in category 'accessing') -----
+ list: aList
+ 	list := aList!

Item was added:
+ Object weakSubclass: #WeakFinalizerItem
+ 	instanceVariableNames: 'list next executor'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-Weak'!

Item was added:
+ ----- Method: WeakFinalizationRegistry>>removeAll (in category 'accessing') -----
+ removeAll
+ 	
+ 	valueDictionary do: [ :value | value clear ].
+ 	self initialize
+ 	
+ 
+ !

Item was added:
+ ----- Method: WeakFinalizationRegistry>>size (in category 'accessing') -----
+ size
+ 	^ valueDictionary size!

Item was added:
+ ----- Method: WeakFinalizationRegistry>>finalizeValues (in category 'finalization') -----
+ finalizeValues
+ 	"Finalize any values, which happen to stocked in our list, due to some weak references become garbage"
+ 	
+ 	| finalizer |
+ 
+ 	"We don't need to guard the next two lines with semaphore, because 
+ 	VM can change the list's 'first' instance variable only during GC, and simple assignment cannot trigger GC"
+ 	finalizer := list swapWithNil.
+ 	
+ 	[ finalizer notNil ] whileTrue: [
+ 		finalizer executor finalize.
+ 		finalizer := finalizer next
+ 	].!

Item was added:
+ Collection subclass: #WeakFinalizationRegistry
+ 	instanceVariableNames: 'list valueDictionary'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-Weak'!
+ 
+ !WeakFinalizationRegistry commentStamp: 'Igor.Stasenko 3/8/2010 23:04' prior: 0!
+ This kind of WeakRegistry using a new VM feature,
+ which allows a more robust finalization support.
+ 
+ In contrast to old implementation, it doesn't spending linear time , checking what elements became garbage.!




More information about the Squeak-dev mailing list