[squeak-dev] The Trunk: Collections-ar.204.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Nov 21 03:19:39 UTC 2009


Andreas Raab uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ar.204.mcz

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

Name: Collections-ar.204
Author: ar
Time: 20 November 2009, 7:19:18 am
UUID: 87c8eab4-58f1-b845-9b98-d47c58d34302
Ancestors: Collections-ul.202, Collections-ul.203

Merging Collections-ul.200, Collections-ul.201, Collections-ul.202, Collections-ul.203:

- moved #like: from HashedCollection to Set
- HashedCollection doesn't implmenet #do: anymore, implementation is moved to Set >> #do: and Dictionary >> #associationsDo:
- Dictionary >> #do: sends #valuesDo:
- Set >> collect: sends #do: to self, instead of it's array. This enables one to change the way enumeration methods work, by reimplementing only #do: in subclasses.
- minor enhancement in #scanForEmptySlotFor: in identity based hashedcollections.
- added missing #yourself sends to #copyEmpty implementors
- removed #noCheckAdd: implementations since they were private
- other cosmetic changes, like isNil ifTrue: replaced by ifNil:, etc.
- added a class comment to WeakSet (this is required to avoid the failure of ClassTestCase)
- a fix for the bug in WeakSet >> #includes:
- removed HashedCollection >> #do: because it was the same as in Collection


=============== Diff against Collections-ul.199 ===============

Item was changed:
  ----- Method: WeakKeyDictionary>>at:put: (in category 'accessing') -----
  at: key put: anObject 
  	"Set the value at key to be anObject.  If key is not found, create a new
  	entry for key and set is value to anObject. Answer anObject."
+ 	
  	| index element |
+ 	key ifNil: [ ^anObject ].
- 	key isNil ifTrue:[^anObject].
  	index := self scanFor: key.
+ 	(element := array at: index)
+ 		ifNil: [ self atNewIndex: index put: (WeakKeyAssociation key: key value: anObject) ]
+ 		ifNotNil: [ element value: anObject ].
+ 	^anObject!
- 	element := array at: index.
- 	element == nil
- 		ifTrue: [self atNewIndex: index put: (WeakKeyAssociation key: key value: anObject)]
- 		ifFalse: [element value: anObject].
- 	^ anObject!

Item was changed:
  ----- Method: WeakSet>>add: (in category 'public') -----
  add: newObject
  	"Include newObject as one of the receiver's elements, but only if
  	not already present. Answer newObject"
  
+ 	| index element |
- 	| index |
  	newObject ifNil: [self error: 'Sets cannot meaningfully contain nil as an element'].
  	index := self scanFor: newObject.
+ 	((element := array at: index) == flag or: [ element == nil ])
- 	((array at: index) == flag or: [(array at: index) isNil])
  		ifTrue: [self atNewIndex: index put: newObject].
  	^newObject!

Item was changed:
  ----- Method: IdentitySet>>scanForEmptySlotFor: (in category 'private') -----
  scanForEmptySlotFor: anObject
  	"Scan the key array for the first slot containing an empty slot (indicated by a nil). Answer the index of that slot. This method will be overridden in various subclasses that have different interpretations for matching elements."
  	
  	| index start hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		(array at: index) ifNil: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: KeyedIdentitySet>>scanForEmptySlotFor: (in category 'private') -----
  scanForEmptySlotFor: anObject
  	"Scan the key array for the first slot containing an empty slot (indicated by a nil). Answer the index of that slot. This method will be overridden in various subclasses that have different interpretations for matching elements."
  	
  	| index start hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		(array at: index) ifNil: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: Dictionary>>add: (in category 'adding') -----
  add: anAssociation
+ 
  	| index element |
  	index := self scanFor: anAssociation key.
+ 	(element := array at: index)
+ 		ifNil: [ self atNewIndex: index put: anAssociation ]
+ 		ifNotNil: [ element value: anAssociation value ].
+ 	^anAssociation!
- 	element := array at: index.
- 	element == nil
- 		ifTrue: [self atNewIndex: index put: anAssociation]
- 		ifFalse: [element value: anAssociation value].
- 	^ anAssociation!

Item was changed:
  Set subclass: #WeakSet
  	instanceVariableNames: 'flag'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Collections-Weak'!
+ 
+ !WeakSet commentStamp: 'ul 11/20/2009 22:51' prior: 0!
+ I'm like Set but my instances only hold weakly to their elements.
+ 
+ Instance Variables:
+ 	flag:		an Object which marks the empty slot in this instance. This object shouldn't be used anywhere else in the system. Every WeakSet has a different flag.
+ 
+ Differences from Set:
+ array is a WeakArray filled with flag initially. flag marks the empty slots, because elements which become garbage will be replaced with nil by the garbage collector. Besides nil, flag cannot be added to my instances.!

Item was changed:
  ----- Method: Dictionary>>associationAt:ifAbsent: (in category 'accessing') -----
  associationAt: key ifAbsent: aBlock 
  	"Answer the association with the given key.
  	If key is not found, return the result of evaluating aBlock."
  
+ 	^(array at: (self scanFor: key)) ifNil: [ aBlock value ]
+ !
- 	| index assoc |
- 	index := self scanFor: key.
- 	assoc := array at: index.
- 	nil == assoc ifTrue: [ ^ aBlock value ].
- 	^ assoc!

Item was changed:
  ----- Method: PluggableDictionary>>copyEmpty (in category 'copying') -----
  copyEmpty
+ 
  	^super copyEmpty
  		hashBlock: hashBlock;
+ 		equalBlock: equalBlock;
+ 		yourself!
- 		equalBlock: equalBlock!

Item was changed:
  ----- Method: IdentityDictionary>>scanForEmptySlotFor: (in category 'private') -----
  scanForEmptySlotFor: anObject
  	"Scan the key array for the first slot containing an empty slot (indicated by a nil). Answer the index of that slot. This method will be overridden in various subclasses that have different interpretations for matching elements."
  	
  	| index start hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		(array at: index) ifNil: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: WeakKeyDictionary>>finalizeValues (in category 'finalization') -----
  finalizeValues
  	"remove all nil keys and rehash the receiver afterwards"
+ 	
  	| assoc |
+ 	1 to: array size do: [ :index |
+ 		(assoc := array at: index) ifNotNil: [
+ 			assoc key ifNil: [ array at: index put: nil ] ] ].
+ 	self rehash!
- 	1 to: array size do:[:i|
- 		assoc := array at: i.
- 		(assoc notNil and:[assoc key == nil]) ifTrue:[array at: i put: nil].
- 	].
- 	self rehash.!

Item was changed:
  ----- Method: PluggableSet>>copyEmpty (in category 'copying') -----
  copyEmpty
+ 
  	^super copyEmpty
  		hashBlock: hashBlock;
+ 		equalBlock: equalBlock;
+ 		yourself!
- 		equalBlock: equalBlock!

Item was changed:
  ----- Method: Set>>collect: (in category 'enumerating') -----
  collect: aBlock 
  	"Evaluate aBlock with each of the receiver's elements as the argument.  
  	Collect the resulting values into a collection like the receiver. Answer  
  	the new collection."
  
  	| newSet |
  	newSet := Set new: self size.
+ 	self do: [ :each | newSet add: (aBlock value: each) ].
+ 	^newSet!
- 	array do: [:each | each ifNotNil: [newSet add: (aBlock value: each)]].
- 	^ newSet!

Item was added:
+ ----- Method: Set>>like: (in category 'accessing') -----
+ like: anObject
+ 	"Answer an object in the receiver that is equal to anObject,
+ 	nil if no such object is found. Relies heavily on hash properties"
+ 
+ 	^array at: (self scanFor: anObject)!

Item was changed:
  ----- Method: KeyedSet>>copyEmpty (in category 'copying') -----
  copyEmpty
+ 
  	^super copyEmpty
+ 		keyBlock: keyBlock;
+ 		yourself!
- 		keyBlock: keyBlock!

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

Item was changed:
  ----- Method: Dictionary>>do: (in category 'enumerating') -----
  do: aBlock
  
+ 	self valuesDo: aBlock!
- 	super do: [:assoc | aBlock value: assoc value]!

Item was changed:
  ----- Method: Dictionary>>associationsDo: (in category 'enumerating') -----
  associationsDo: aBlock 
  	"Evaluate aBlock for each of the receiver's elements (key/value 
  	associations)."
  
+ 	tally = 0 ifTrue: [ ^self].
+ 	1 to: array size do: [ :index |
+ 		| each |
+ 		(each := array at: index)
+ 			ifNotNil: [ aBlock value: each ] ]!
- 	super do: aBlock!

Item was changed:
  ----- Method: WeakSet>>includes: (in category 'public') -----
  includes: anObject 
+ 	
+ 	| element |
+ 	^((element := array at: (self scanFor: anObject)) == flag or: [ element == nil ]) not!
- 	^(array at: (self scanFor: anObject)) ~~ flag!

Item was changed:
  ----- Method: WeakIdentityKeyDictionary>>scanForEmptySlotFor: (in category 'private') -----
  scanForEmptySlotFor: anObject
  	"Scan the key array for the first slot containing an empty slot (indicated by a nil). Answer the index of that slot. This method will be overridden in various subclasses that have different interpretations for matching elements."
  	
  	| index start hash |
+ 	array size >= 8192
- 	array size > 4096
  		ifTrue: [ hash := anObject identityHash * (array size // 4096) ]
  		ifFalse: [ hash := anObject identityHash ].
  	index := start := hash \\ array size + 1.
  	[ 
  		(array at: index) ifNil: [ ^index ].
  		(index := index \\ array size + 1) = start ] whileFalse.
  	self errorNoFreeSpace!

Item was changed:
  ----- Method: Dictionary>>removeKey:ifAbsent: (in category 'removing') -----
  removeKey: key ifAbsent: aBlock 
  	"Remove key (and its associated value) from the receiver. If key is not in 
  	the receiver, answer the result of evaluating aBlock. Otherwise, answer 
  	the value externally named by key."
  
  	| index association |
  	index := self scanFor: key.
+ 	association := (array at: index) ifNil: [ ^aBlock value ].
- 	(association := array at: index) ifNil: [ ^ aBlock value ].
  	array at: index put: nil.
  	tally := tally - 1.
  	self fixCollisionsFrom: index.
  	^association value!

Item was changed:
  ----- Method: Dictionary>>at:ifAbsent: (in category 'accessing') -----
  at: key ifAbsent: aBlock 
  	"Answer the value associated with the key or, if key isn't found,
  	answer the result of evaluating aBlock."
  
+ 	^((array at: (self scanFor: key)) ifNil: [ aBlock ]) value "Blocks and Associations expect #value"!
- 	| assoc |
- 	assoc := array at: (self scanFor: key).
- 	assoc ifNil: [^ aBlock value].
- 	^ assoc value!

Item was added:
+ ----- Method: Set>>do: (in category 'enumerating') -----
+ do: aBlock 
+ 
+ 	tally = 0 ifTrue: [ ^self ].
+ 	1 to: array size do: [ :index |
+ 		| each |
+ 		(each := array at: index)
+ 			ifNotNil: [ aBlock value: each ] ]!

Item was removed:
- ----- Method: Set>>noCheckAdd: (in category 'private') -----
- noCheckAdd: anObject
- 
- 	self deprecated: 'This method should not be used anymore.'.
- 	array at: (self scanFor: anObject) put: anObject.
- 	tally := tally + 1!

Item was removed:
- ----- Method: Dictionary>>noCheckAdd: (in category 'private') -----
- noCheckAdd: anObject
- 	"Must be defined separately for Dictionary because (self scanFor:) expects a key,
- 	not an association.  9/7/96 tk"
- 
- 	self deprecated: 'This method should not be used anymore.'.
- 	array at: (self scanFor: anObject key) put: anObject.
- 	tally := tally + 1!

Item was removed:
- ----- Method: HashedCollection>>do: (in category 'enumerating') -----
- do: aBlock 
- 	tally = 0 ifTrue: [^ self].
- 	1 to: array size do:
- 		[:index |
- 		| each |
- 		(each := array at: index) ifNotNil: [aBlock value: each]]!

Item was removed:
- ----- Method: HashedCollection>>like: (in category 'accessing') -----
- like: anObject
- 	"Answer an object in the receiver that is equal to anObject,
- 	nil if no such object is found. Relies heavily on hash properties"
- 
- 	^array at: (self scanFor: anObject)!

Item was removed:
- ----- Method: Dictionary>>remove: (in category 'removing') -----
- remove: anObject
- 
- 	self shouldNotImplement!




More information about the Squeak-dev mailing list