[Pkg] The Trunk: Collections-ul.384.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 26 01:06:12 UTC 2010


Levente Uzonyi uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ul.384.mcz

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

Name: Collections-ul.384
Author: ul
Time: 26 September 2010, 2:52:19.252 am
UUID: 1a219312-0f50-574e-8615-bf87532a46c8
Ancestors: Collections-ul.383

- Finalization enhancements part 3

=============== Diff against Collections-ul.383 ===============

Item was removed:
- Collection subclass: #WeakFinalizationRegistry
- 	instanceVariableNames: 'list valueDictionary sema'
- 	classVariableNames: 'Default'
- 	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.!

Item was removed:
- ----- Method: WeakFinalizationRegistry classSide>>default (in category 'accessing') -----
- default
- 	^Default ifNil:[Default := self new]!

Item was removed:
- ----- Method: WeakFinalizationRegistry classSide>>migrateOldRegistries (in category 'migrating registry') -----
- migrateOldRegistries
- 	Smalltalk at: #WeakFinalizationRegistry ifAbsent: [ ^ self "already done" ].
- 	
- 	Smalltalk recreateSpecialObjectsArray.
- 	WeakArray restartFinalizationProcess.
- 	
- 	Smalltalk garbageCollect; garbageCollect.
- 	
- 	"leave no chance to interrupt migration"	
- 	Compiler evaluate: '
- 	[ | old new oldClass newClass |
- 		old := OrderedCollection new.
- 		new := OrderedCollection new.
- 		WeakRegistry allInstancesDo: [:registry | | newr |
- 			old add: registry.
- 			newr := WeakFinalizationRegistry basicNew initialize.
- 			registry migrateTo: newr.
- 			new add: newr ].
- 		old asArray elementsForwardIdentityTo: new asArray.
- 		
- 		oldClass := WeakRegistry.
- 		newClass := WeakFinalizationRegistry.
- 		
- 		Smalltalk forgetClass: newClass logged: false.
- 		newClass superclass removeSubclass: newClass.
- 		newClass setName: #WeakRegistry.
- 		oldClass becomeForward: newClass.
- 	] forkAt: Processor highestPriority.
- 	'.
- !

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

Item was removed:
- ----- Method: WeakFinalizationRegistry classSide>>new: (in category 'instance creation') -----
- new: n
- 	^ self new!

Item was removed:
- ----- 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 removed:
- ----- Method: WeakFinalizationRegistry>>add:executor: (in category 'adding') -----
- add: anObject executor: anExecutor
- 
- 	self protected: [ | finItem |
- 		finItem := valueDictionary at: anObject ifAbsentPut: [
- 			WeakFinalizerItem new list: list object: anObject ].
- 		finItem add: anExecutor ].
- 	^ anObject
- !

Item was removed:
- ----- Method: WeakFinalizationRegistry>>do: (in category 'enumerating') -----
- do: aBlock
- 	^self protected: [
- 		valueDictionary keysDo: aBlock.
- 	].
- !

Item was removed:
- ----- 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 |
- 
- 	WeakFinalizationList hasNewFinalization ifFalse: [
- 		self protected: [ valueDictionary finalizeValues ].
- 		^ self ].
- 
- 	self protected: [ finalizer := list swapWithNil ].
- 
- 	"We don't need to protect a following loop from concurrent access,
- 	because at the moment we're finalizing values, 
- 	only we can access this list of finalizers, because valueDictionary already see them
- 	as an unused slots, because they're associated with key == nil"
- 	
- 	[ finalizer notNil ] whileTrue: [
- 		| next |
- 		next := finalizer next.
- 		finalizer finalizeValues.
- 		finalizer := next
- 	].
- !

Item was removed:
- ----- Method: WeakFinalizationRegistry>>initialize (in category 'initialize-release') -----
- initialize
- 	valueDictionary := WeakIdentityKeyDictionary new.
- 	list := WeakFinalizationList new.
- 	sema := Semaphore forMutualExclusion.
- 	self installFinalizer.!

Item was removed:
- ----- Method: WeakFinalizationRegistry>>installFinalizer (in category 'initialize-release') -----
- installFinalizer
- 
- 	valueDictionary finalizer: #finalizeValues!

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

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

Item was removed:
- ----- Method: WeakFinalizationRegistry>>printElementsOn: (in category 'printing') -----
- printElementsOn: aStream
- 	sema ifNil: [^super printElementsOn: aStream].
- 	aStream nextPutAll: '(<this WeakRegistry is locked>)'!

Item was removed:
- ----- Method: WeakFinalizationRegistry>>protected: (in category 'private') -----
- protected: aBlock
- 	"Execute aBlock protected by the accessLock"
- 
- 	^ sema
- 		critical: aBlock
- 		ifError: [ :msg :rcvr |
- 		rcvr error: msg ] !

Item was removed:
- ----- Method: WeakFinalizationRegistry>>remove:ifAbsent: (in category 'printing') -----
- remove: oldObject ifAbsent: exceptionBlock
- 	"Remove oldObject as one of the receiver's elements."
- 	
- 	oldObject ifNil: [ ^nil ].
- 	^(self protected: [ valueDictionary removeKey: oldObject ifAbsent: nil ])
- 		ifNil: [ exceptionBlock value ]!

Item was removed:
- ----- Method: WeakFinalizationRegistry>>removeAll (in category 'printing') -----
- removeAll
- 	"See super"
- 	
- 	self protected:[
- 		valueDictionary removeAll.
- 	].!

Item was removed:
- ----- Method: WeakFinalizationRegistry>>size (in category 'accessing') -----
- size
- 	^ self protected: [valueDictionary slowSize]!

Item was removed:
- ----- Method: WeakFinalizationRegistry>>species (in category 'private') -----
- species
- 	^Set!

Item was changed:
  Collection subclass: #WeakRegistry
+ 	instanceVariableNames: 'list valueDictionary sema'
- 	instanceVariableNames: 'valueDictionary accessLock executors'
  	classVariableNames: 'Default'
  	poolDictionaries: ''
  	category: 'Collections-Weak'!
  
+ !WeakRegistry commentStamp: 'ul 9/26/2010 02:51' prior: 0!
- !WeakRegistry commentStamp: '<historical>' prior: 0!
  I am a registry for objects needing finalization. When an object is added the object as well as its executor is stored. When the object is garbage collected, the executor can take the appropriate action for any resources associated with the object.
  
+ This kind of WeakRegistry is using a new VM feature, which allows a more robust finalization support. In contrast to the old implementation, it doesn't spend linear time checking which elements became garbage.
+ 
  See also:
  	Object executor
  	Object actAsExecutor
+ 	Object finalize!
- 	Object finalize
- !

Item was changed:
  ----- Method: WeakRegistry class>>default (in category 'accessing') -----
  default
  	^Default ifNil:[Default := self new]!

Item was changed:
  ----- Method: WeakRegistry class>>new (in category 'instance creation') -----
  new
+ 	| registry |
+ 	registry := super new.
+ 	WeakArray addWeakDependent: registry.
+ 	^registry
+ !
- 	^self new: 5!

Item was changed:
  ----- Method: WeakRegistry class>>new: (in category 'instance creation') -----
  new: n
+ 	^ self new!
- 	| registry |
- 	registry := super new initialize: n.
- 	WeakArray addWeakDependent: registry.
- 	^registry!

Item was changed:
  ----- Method: WeakRegistry>>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 changed:
  ----- Method: WeakRegistry>>add:executor: (in category 'adding') -----
  add: anObject executor: anExecutor
+ 
+ 	self protected: [ | finItem |
+ 		finItem := valueDictionary at: anObject ifAbsentPut: [
+ 			WeakFinalizerItem new list: list object: anObject ].
+ 		finItem add: anExecutor ].
+ 	^ anObject
+ !
- 	"Add anObject to the receiver. Store the object as well as the associated executor."
- 	
- 	self protected: [
- 		(valueDictionary associationAt: anObject ifAbsent: nil)
- 			ifNil: [ valueDictionary at: anObject put: anExecutor ]
- 			ifNotNil: [ :association |
- 				| finalizer |
- 				(finalizer := association value) class == ObjectFinalizerCollection
- 					ifTrue: [ finalizer add: anExecutor ]
- 					ifFalse: [ 
- 						association value: (ObjectFinalizerCollection
- 							with: association value
- 							with: anExecutor) ] ] ].
- 	^anObject!

Item was changed:
  ----- Method: WeakRegistry>>do: (in category 'enumerating') -----
  do: aBlock
+ 	^self protected: [
- 	^self protected:[
  		valueDictionary keysDo: aBlock.
  	].
  !

Item was changed:
  ----- Method: WeakRegistry>>finalizeValues (in category 'finalization') -----
  finalizeValues
+ 	"Finalize any values, which happen to stocked in our list, due to some weak references become garbage"
- 	"Some of our elements may have gone away. Look for those and activate the associated executors."
  	
+ 	| finalizer |
+ 
+ 	WeakFinalizationList hasNewFinalization ifFalse: [
+ 		self protected: [ valueDictionary finalizeValues ].
+ 		^ self ].
+ 
+ 	self protected: [ finalizer := list swapWithNil ].
+ 
+ 	"We don't need to protect a following loop from concurrent access,
+ 	because at the moment we're finalizing values, 
+ 	only we can access this list of finalizers, because valueDictionary already see them
+ 	as an unused slots, because they're associated with key == nil"
+ 	
+ 	[ finalizer notNil ] whileTrue: [
+ 		| next |
+ 		next := finalizer next.
+ 		finalizer finalizeValues.
+ 		finalizer := next
+ 	].
+ !
- 	| collectedExecutors |
- 	self protected: [ 
- 		valueDictionary finalizeValues.
- 		collectedExecutors := executors.
- 		executors := nil ].
- 	collectedExecutors ifNotNil: [
- 		collectedExecutors do: #finalize ]!

Item was added:
+ ----- Method: WeakRegistry>>initialize (in category 'initialize-release') -----
+ initialize
+ 	valueDictionary := WeakIdentityKeyDictionary new.
+ 	list := WeakFinalizationList new.
+ 	sema := Semaphore forMutualExclusion.
+ 	self installFinalizer.!

Item was removed:
- ----- Method: WeakRegistry>>initialize: (in category 'initialize') -----
- initialize: n
- 
- 	valueDictionary := WeakIdentityKeyDictionary new: n.
- 	accessLock := Semaphore forMutualExclusion.
- 	self installFinalizer.!

Item was changed:
+ ----- Method: WeakRegistry>>installFinalizer (in category 'initialize-release') -----
- ----- Method: WeakRegistry>>installFinalizer (in category 'initialize') -----
  installFinalizer
  
+ 	valueDictionary finalizer: #finalizeValues!
- 	valueDictionary finalizer: [ :executor |
- 		(executors ifNil: [ executors := OrderedCollection new ]) add: executor ]!

Item was removed:
- ----- Method: WeakRegistry>>migrateTo: (in category 'migrating') -----
- migrateTo: newRegistry
- 
- 	self protected: [
- 		valueDictionary keysDo: [ :key |
- 			newRegistry add: key executor: (valueDictionary at: key).
- 		]].!

Item was changed:
  ----- Method: WeakRegistry>>postCopy (in category 'copying') -----
  postCopy
+ 	"should we prohibit any attempts to copy receiver?"
+ 	self protected: [ | oldDict |
+ 		sema := Semaphore forMutualExclusion.
+ 		oldDict := valueDictionary.
+ 		list := WeakFinalizationList new.
+ 		valueDictionary := WeakIdentityKeyDictionary new.
+ 		self installFinalizer.
+ 	
+ 		oldDict keysAndValuesDo: [:key :value |
+ 			valueDictionary at: key put: (value copyWithList: list)
+ 		].
+ 	]!
- 
- 	self protected: [ "Uses the original accessLock"
- 		accessLock := Semaphore forMutualExclusion.
- 		valueDictionary := valueDictionary copy.
- 		valueDictionary associationsDo: [ :each |
- 			each value class == ObjectFinalizerCollection 
- 				ifTrue: [ each value: each value copy ] ].
- 		executors := executors copy.
- 		self installFinalizer ]!

Item was changed:
  ----- Method: WeakRegistry>>printElementsOn: (in category 'printing') -----
  printElementsOn: aStream
+ 	sema ifNil: [^super printElementsOn: aStream].
- 	accessLock ifNil: [^super printElementsOn: aStream].
  	aStream nextPutAll: '(<this WeakRegistry is locked>)'!

Item was changed:
  ----- Method: WeakRegistry>>protected: (in category 'private') -----
  protected: aBlock
  	"Execute aBlock protected by the accessLock"
  
+ 	^ sema
+ 		critical: aBlock
+ 		ifError: [ :msg :rcvr |
+ 		rcvr error: msg ] !
- 	^accessLock
- 		ifNil: [ aBlock value ]
- 		ifNotNil: [
- 			accessLock
- 				critical: aBlock
- 				ifError: [ :msg :rcvr |
- 					rcvr error: msg ] ]!

Item was changed:
+ ----- Method: WeakRegistry>>remove:ifAbsent: (in category 'printing') -----
- ----- Method: WeakRegistry>>remove:ifAbsent: (in category 'removing') -----
  remove: oldObject ifAbsent: exceptionBlock
  	"Remove oldObject as one of the receiver's elements."
  	
  	oldObject ifNil: [ ^nil ].
  	^(self protected: [ valueDictionary removeKey: oldObject ifAbsent: nil ])
  		ifNil: [ exceptionBlock value ]!

Item was changed:
+ ----- Method: WeakRegistry>>removeAll (in category 'printing') -----
- ----- Method: WeakRegistry>>removeAll (in category 'removing') -----
  removeAll
  	"See super"
  	
  	self protected:[
  		valueDictionary removeAll.
  	].!

Item was changed:
  ----- Method: WeakRegistry>>size (in category 'accessing') -----
  size
+ 	^ self protected: [valueDictionary slowSize]!
- 	^ self protected: [valueDictionary size]!

Item was changed:
  ----- Method: WeakRegistry>>species (in category 'private') -----
  species
  	^Set!



More information about the Packages mailing list