[squeak-dev] The Trunk: Collections-ul.291.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Feb 5 04:25:02 UTC 2010


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

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

Name: Collections-ul.291
Author: ul
Time: 5 February 2010, 4:11:04.879 am
UUID: fb0d5b15-31c9-014d-960a-6a01bde21d96
Ancestors: Collections-mpe.290

- weak collection changes, part 1
- a bit faster #fixCollisionsFrom:

=============== Diff against Collections-mpe.290 ===============

Item was added:
+ ----- Method: WeakKeyDictionary>>slowSize (in category 'public') -----
+ slowSize
+ 	"Careful!! Answer the maximum amount
+ 	of elements in the receiver, not the
+ 	exact amount"
+ 
+ 	| count |
+ 	count := 0.
+ 	1 to: array size do: [ :index |
+ 		(array at: index) ifNotNil: [ :object |
+ 			object key ifNotNil: [
+ 				count := count + 1 ] ] ].
+ 	^count!

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

Item was changed:
  ----- Method: Set>>fixCollisionsFrom: (in category 'private') -----
  fixCollisionsFrom: start
  	"The element at start has been removed and replaced by nil.
  	This method moves forward from there, relocating any entries
  	that had been placed below due to collisions with this one."
  
  	| element index |
  	index := start.
  	[ (element := array at: (index := index \\ array size + 1)) == nil ] whileFalse: [
  		| newIndex |
  		(newIndex := self scanFor: element enclosedSetElement) = index ifFalse: [
+ 			array 
+ 				at: newIndex put: element;
+ 				at: index put: nil ] ]!
- 			array swap: index with: newIndex ] ]!

Item was changed:
  ----- Method: WeakSet>>fixCollisionsFrom: (in category 'private') -----
  fixCollisionsFrom: start
  	"The element at start has been removed and replaced by flag.
  	This method moves forward from there, relocating any entries
  	that had been placed below due to collisions with this one."
  
  	| element index |
  	index := start.
  	[ (element := array at: (index := index \\ array size + 1)) == flag ] whileFalse: [
+ 		element 
+ 			ifNil: [ "This object is gone"
+ 				array at: index put: flag.
+ 				tally := tally - 1 ]
+ 			ifNotNil: [
+ 				| newIndex |
+ 				(newIndex := self scanFor: element enclosedSetElement) = index ifFalse: [
+ 					array 
+ 						at: newIndex put: element;
+ 						at: index put: flag ] ] ]
- 		| newIndex |
- 		(newIndex := self scanFor: element enclosedSetElement) = index ifFalse: [
- 			array swap: index with: newIndex ] ]
  !

Item was added:
+ ----- Method: WeakKeyDictionary>>finalizer: (in category 'accessing') -----
+ finalizer: aValueable
+ 
+ 	finalizer := aValueable!

Item was changed:
  ----- Method: WeakKeyDictionary>>keysDo: (in category 'accessing') -----
  keysDo: aBlock 
  	"Evaluate aBlock for each of the receiver's keys."
  	
  	self associationsDo: [ :association |
+ 		association key ifNotNil: [ :key | "Don't let the key go away"
- 		(association key) ifNotNil: [ :key | "Don't let the key go away"
  			aBlock value: key ] ].!

Item was changed:
  ----- Method: Dictionary>>fixCollisionsFrom: (in category 'private') -----
  fixCollisionsFrom: start
  	"The element at start has been removed and replaced by nil.
  	This method moves forward from there, relocating any entries
  	that had been placed below due to collisions with this one."
  
  	| element index |
  	index := start.
  	[ (element := array at: (index := index \\ array size + 1)) == nil ] whileFalse: [
  		| newIndex |
  		(newIndex := self scanFor: element key) = index ifFalse: [
+ 			array 
+ 				at: newIndex put: element;
+ 				at: index put: nil ] ]!
- 			array swap: index with: newIndex ] ]!

Item was changed:
  ----- 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 ]!
- 	| removedObject |
- 	oldObject isNil ifTrue:[^oldObject].
- 	self protected:[
- 		removedObject := valueDictionary removeKey: oldObject ifAbsent:[nil].
- 	].
- 	^removedObject isNil
- 		ifTrue:[exceptionBlock value]
- 		ifFalse:[removedObject].
- !

Item was added:
+ ----- Method: WeakSet>>growSize (in category 'private') -----
+ growSize
+ 	"Answer what my next table size should be.
+ 	Note that, it can be less than the current."
+ 	
+ 	^self class goodPrimeAtLeast: self slowSize * 3 // 2 + 2!

Item was changed:
  Dictionary subclass: #WeakKeyDictionary
+ 	instanceVariableNames: 'finalizer'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Collections-Weak'!
  
  !WeakKeyDictionary commentStamp: '<historical>' prior: 0!
  I am a dictionary holding only weakly on my keys. This is a bit dangerous since at any time my keys can go away. Clients are responsible to register my instances by WeakArray such that the appropriate actions can be taken upon loss of any keys.
  
  See WeakRegistry for an example of use.
  !

Item was changed:
  Collection subclass: #WeakRegistry
+ 	instanceVariableNames: 'valueDictionary accessLock objectsToFinalize'
- 	instanceVariableNames: 'valueDictionary accessLock'
  	classVariableNames: 'Default'
  	poolDictionaries: ''
  	category: 'Collections-Weak'!
  
  !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.
  
  See also:
  	Object executor
  	Object actAsExecutor
  	Object finalize
  !

Item was changed:
  ----- Method: WeakSet>>slowSize (in category 'public') -----
  slowSize
  	"Careful!! Answer the maximum amount
  	of elements in the receiver, not the
  	exact amount"
  
  	| count |
  	count := 0.
  	1 to: array size do: [ :index |
  		(array at: index) ifNotNil: [ :object |
  			object == flag ifFalse: [
  				count := count + 1 ] ] ].
+ 	^count!
- 	^tally := count!

Item was changed:
  ----- Method: WeakKeyDictionary>>noCheckNoGrowFillFrom: (in category 'private') -----
  noCheckNoGrowFillFrom: anArray
  	"Add the elements of anArray except nils and flag to me assuming that I don't contain any of them, they are unique and I have more free space than they require."
  
  	tally := 0.
+ 	1 to: anArray size do: [ :index |
- 	1 to: anArray size do:[ :index |
  		(anArray at: index) ifNotNil: [ :association |
+ 			association key 
+ 				ifNil: [ finalizer ifNotNil: [ finalizer value: association value ] ]
+ 				ifNotNil: [ :key | "Don't let the key go away"
+ 					array
+ 						at: (self scanForEmptySlotFor: key)
+ 						put: association.
+ 					tally := tally + 1 ] ] ]!
- 			association key ifNotNil: [ :key | "Don't let the key go away"
- 				array
- 					at: (self scanForEmptySlotFor: key)
- 					put: association.
- 				tally := tally + 1 ] ] ]!

Item was changed:
  ----- Method: WeakKeyDictionary>>fixCollisionsFrom: (in category 'private') -----
+ fixCollisionsFrom: start
+ 	"The element at start has been removed and replaced by nil.
+ 	This method moves forward from there, relocating any entries
+ 	that had been placed below due to collisions with this one."
+ 
+ 	| element index |
+ 	index := start.
+ 	[ (element := array at: (index := index \\ array size + 1)) == nil ] whileFalse: [
+ 		element key
+ 			ifNil: [ 
+ 				finalizer ifNotNil: [ finalizer value: element value ].
+ 				array at: index put: nil.
+ 				tally := tally - 1 ]
+ 			ifNotNil: [ :key | "Don't let the key go away"
+ 				| newIndex |
+ 				(newIndex := self scanFor: key) = index ifFalse: [
+ 					array swap: index with: newIndex ] ] ]!
- fixCollisionsFrom: oldIndex
- 	"The element at index has been removed and replaced by nil."
- 	self rehash. "Do it the hard way - we may have any number of nil keys and #rehash deals with them"!

Item was changed:
  ----- Method: KeyedSet>>fixCollisionsFrom: (in category 'private') -----
  fixCollisionsFrom: start
  	"The element at start has been removed and replaced by nil.
  	This method moves forward from there, relocating any entries
  	that had been placed below due to collisions with this one."
  
  	| element index |
  	index := start.
  	[ (element := array at: (index := index \\ array size + 1)) == nil ] whileFalse: [
  		| newIndex |
  		(newIndex := self scanFor: (keyBlock value: element enclosedSetElement)) = index ifFalse: [
+ 			array 
+ 				at: newIndex put: element;
+ 				at: index put: nil ] ]!
- 			array swap: index with: newIndex ] ]!

Item was added:
+ ----- Method: WeakKeyDictionary>>growSize (in category 'private') -----
+ growSize
+ 	"Answer what my next table size should be.
+ 	Note that, it can be less than the current."
+ 	
+ 	^self class goodPrimeAtLeast: self slowSize * 3 // 2 + 2!

Item was removed:
- ----- Method: WeakSet>>grow (in category 'private') -----
- grow
- 	"Grow the elements array if needed.
- 	Since WeakSets just nil their slots, a lot of the occupied (in the eyes of the set) slots are usually empty. Doubling size if unneeded can lead to BAD performance, therefore we see if reassigning the <live> elements to a Set of similiar size leads to a sufficiently (50% used here) empty set first"
- 	
- 	tally // 2 < self slowSize
- 		ifTrue: [ super grow ]
- 		ifFalse: [ self rehash ]
- !




More information about the Squeak-dev mailing list