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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 19 06:13:24 UTC 2009


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

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

Name: Collections-ul.198
Author: ul
Time: 19 November 2009, 1:22:03 am
UUID: cc9f8c67-d812-ee42-8eeb-7c2d59037a32
Ancestors: Collections-nice.197

Introduced a new abstract collection class: HashedCollection.
- Moved methods common with Dictionary from Set to HashedCollection.
- Set is now a subclass of HashedCollection.
- Added necessary stub methods to HashedCollection with #subclassResponsibility sends.
- Deprecated Set >> #rehashAllSets, replaced it with HashedCollection rehashAll.
- Moved deprecation of #someElement from comment to code.

=============== Diff against Collections-nice.197 ===============

Item was added:
+ ----- Method: HashedCollection>>growSize (in category 'private') -----
+ growSize
+ 	^ array size max: 2!

Item was added:
+ ----- Method: HashedCollection>>copyEmpty (in category 'copying') -----
+ copyEmpty
+ 	"Answer an empty copy of this collection"
+ 	
+ 	"Note: this code could be moved to super"
+ 	
+ 	^self species new!

Item was added:
+ ----- Method: HashedCollection>>initialize: (in category 'private') -----
+ initialize: n
+ 	"Initialize array to an array size of n"
+ 	array := Array new: n.
+ 	tally := 0!

Item was added:
+ ----- Method: HashedCollection>>someElement (in category 'accessing') -----
+ someElement
+ 
+ 	self deprecated: 'Use #anyOne'.
+ 	^self anyOne!

Item was added:
+ ----- Method: HashedCollection>>findElementOrNil: (in category 'private') -----
+ findElementOrNil: anObject
+ 	"Answer the index of a first slot containing either a nil (indicating an empty slot) or an element that matches the given object. Answer the index of that slot or zero. Fail if neither a match nor an empty slot is found."
+ 
+ 	| index |
+ 	self deprecated: 'Use #scanFor:.'.
+ 	index := self scanFor: anObject.
+ 	index > 0 ifTrue: [^index].
+ 
+ 	"Bad scene.  Neither have we found a matching element
+ 	nor even an empty slot.  No hashed set is ever supposed to get
+ 	completely full."
+ 	self error: 'There is no free space in this set!!'.!

Item was added:
+ ----- Method: HashedCollection>>doWithIndex: (in category 'enumerating') -----
+ doWithIndex: aBlock2
+ 	"Support Set enumeration with a counter, even though not ordered"
+ 	| index |
+ 	index := 0.
+ 	self do: [:item | aBlock2 value: item value: (index := index+1)]!

Item was added:
+ ----- Method: HashedCollection class>>sizeFor: (in category 'instance creation') -----
+ sizeFor: nElements
+ 	"Large enough size to hold nElements with some slop (see fullCheck)"
+ 	nElements <= 0 ifTrue: [^ 1].
+ 	^ nElements+1*4//3!

Item was added:
+ ----- Method: HashedCollection>>errorNoFreeSpace (in category 'private') -----
+ errorNoFreeSpace
+ 
+ 	self error: 'There is no free space in this collection!!'!

Item was added:
+ ----- Method: HashedCollection>>noCheckNoGrowFillFrom: (in category 'private') -----
+ noCheckNoGrowFillFrom: anArray
+ 	"Add the elements of anArray except nils to me assuming that I don't contain any of them, they are unique and I have more free space than they require."
+ 	
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: HashedCollection>>union: (in category 'enumerating') -----
+ union: aCollection
+ 	"Answer the set theoretic union of the receiver and aCollection, using the receiver's notion of equality and not side effecting the receiver at all."
+ 
+ 	^ self copy addAll: aCollection; yourself
+ 
+ !

Item was changed:
+ HashedCollection subclass: #Set
+ 	instanceVariableNames: ''
- Collection subclass: #Set
- 	instanceVariableNames: 'tally array'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Collections-Unordered'!
  
  !Set commentStamp: '<historical>' prior: 0!
  I represent a set of objects without duplicates.  I can hold anything that responds to
  #hash and #=, except for nil.  My instances will automatically grow, if necessary,
  Note that I rely on #=, not #==.  If you want a set using #==, use IdentitySet.
  
  Instance structure:
  
    array	An array whose non-nil elements are the elements of the set,
  		and whose nil elements are empty slots.  There is always at least one nil.
  		In fact I try to keep my "load" at 75% or less so that hashing will work well.
  
    tally	The number of elements in the set.  The array size is always greater than this.
  
  The core operation is #findElementOrNil:, which either finds the position where an
  object is stored in array, if it is present, or finds a suitable position holding nil, if
  its argument is not present in array,!

Item was added:
+ ----- Method: HashedCollection>>add:withOccurrences: (in category 'adding') -----
+ add: newObject withOccurrences: anInteger
+ 	^ self add: newObject!

Item was added:
+ Collection subclass: #HashedCollection
+ 	instanceVariableNames: 'tally array'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-Abstract'!

Item was added:
+ ----- Method: HashedCollection>>fullCheck (in category 'private') -----
+ fullCheck
+ 	"Keep array at least 1/4 free for decent hash behavior"
+ 	array size - tally < (array size // 4 max: 1)
+ 		ifTrue: [self grow]!

Item was added:
+ ----- Method: HashedCollection class>>new (in category 'instance creation') -----
+ new
+ 	^ self basicNew initialize: 5!

Item was added:
+ ----- Method: HashedCollection class>>rehashAll (in category 'initialization') -----
+ rehashAll
+ 	"HashedCollection rehashAll"	
+ 		
+ 	self allSubclassesDo: [ :each | each rehashAllInstances ]!

Item was added:
+ ----- 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 added:
+ ----- Method: HashedCollection>>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 |
+ 	index := start := anObject hash \\ array size + 1.
+ 	[ 
+ 		(array at: index) ifNil: [ ^index ].
+ 		(index := index \\ array size + 1) = start ] whileFalse.
+ 	self errorNoFreeSpace!

Item was added:
+ ----- Method: HashedCollection>>atRandom: (in category 'accessing') -----
+ atRandom: aGenerator
+ 	"Answer a random element of the receiver. Uses aGenerator which
+     should be kept by the user in a variable and used every time. Use
+     this instead of #atRandom for better uniformity of random numbers because 
+ 	only you use the generator. Causes an error if self has no elements."
+ 	| rand |
+ 
+ 	self emptyCheck.
+ 	rand := aGenerator nextInt: self size.
+ 	self doWithIndex:[:each :ind |
+ 		ind = rand ifTrue:[^each]].
+ 	^ self errorEmptyCollection
+ !

Item was added:
+ ----- Method: HashedCollection>>grow (in category 'private') -----
+ grow
+ 	"Grow the elements array and reinsert the old elements"
+ 	
+ 	self growTo: array size + self growSize!

Item was added:
+ ----- Method: HashedCollection class>>rehashAllInstances (in category 'initialization') -----
+ rehashAllInstances
+ 	"Do not use #allInstancesDo: because rehash may create new instances."
+ 
+ 	self allInstances do: [ :each | each rehash ] !

Item was added:
+ ----- 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 added:
+ ----- Method: HashedCollection>>array (in category 'private') -----
+ array
+ 	^ array!

Item was changed:
  ----- Method: Set class>>quickRehashAllSets (in category 'initialization') -----
  quickRehashAllSets
+ 	
+ 	self deprecated: 'Use HashedCollection >> #rehashAll'.	
+ 	HashedCollection rehashAll!
- 
- 	self deprecated: 'Use #rehashAllSets'.
- 	self rehashAllSets!

Item was added:
+ ----- Method: HashedCollection>>comeFullyUpOnReload: (in category 'objects from disk') -----
+ comeFullyUpOnReload: smartRefStream
+ 	"Symbols have new hashes in this image."
+ 
+ 	self rehash.
+ 	"^ self"
+ !

Item was added:
+ ----- Method: HashedCollection>>postCopy (in category 'copying') -----
+ postCopy
+ 	super postCopy.
+ 	array := array copy!

Item was added:
+ ----- Method: HashedCollection>>atNewIndex:put: (in category 'private') -----
+ atNewIndex: index put: anObject
+ 	array at: index put: anObject.
+ 	tally := tally + 1.
+ 	self fullCheck!

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

Item was added:
+ ----- Method: HashedCollection>>occurrencesOf: (in category 'testing') -----
+ occurrencesOf: anObject 
+ 	^ (self includes: anObject) ifTrue: [1] ifFalse: [0]!

Item was added:
+ ----- Method: HashedCollection>>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."
+ 	
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: HashedCollection class>>new: (in category 'instance creation') -----
+ new: nElements
+ 	"Create a Set large enough to hold nElements without growing"
+ 	^ self basicNew initialize: (self sizeFor: nElements)!

Item was added:
+ ----- Method: HashedCollection>>capacity (in category 'accessing') -----
+ capacity
+ 	"Answer the current capacity of the receiver."
+ 
+ 	^ array size!

Item was added:
+ ----- Method: HashedCollection>>growTo: (in category 'private') -----
+ growTo: anInteger
+ 	"Grow the elements array and reinsert the old elements"
+ 	
+ 	| oldElements |
+ 	oldElements := array.
+ 	array := Array new: anInteger.
+ 	self noCheckNoGrowFillFrom: oldElements!

Item was added:
+ ----- Method: HashedCollection>>rehash (in category 'private') -----
+ rehash
+ 	
+ 	self growTo: array size!

Item was changed:
  ----- Method: Set class>>rehashAllSets (in category 'initialization') -----
  rehashAllSets
+ 	
+ 	self deprecated: 'Use HashedCollection >> #rehashAll'.	
+ 	HashedCollection rehashAll!
- 	"Set rehashAllSets"	
- 		
- 	self withAllSubclassesDo: [ :each | each rehashAllInstances ]!

Item was added:
+ ----- Method: HashedCollection>>scanFor: (in category 'private') -----
+ scanFor: anObject
+ 	"Scan the key array for the first slot containing either a nil (indicating an empty slot) or an element that matches anObject. Answer the index of that slot or raise an error if no slot is found. This method will be overridden in various subclasses that have different interpretations for matching elements."
+ 
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: HashedCollection>>removeAll (in category 'removing') -----
+ removeAll
+ 	"remove all elements from this collection.
+ 	Preserve the capacity"
+ 	
+ 	self initialize: self capacity!

Item was removed:
- ----- Method: Set>>removeAll (in category 'removing') -----
- removeAll
- 	"remove all elements from this collection.
- 	Preserve the capacity"
- 	
- 	self initialize: self capacity!

Item was removed:
- ----- Method: Set>>growSize (in category 'private') -----
- growSize
- 	^ array size max: 2!

Item was removed:
- ----- Method: Set>>copyEmpty (in category 'copying') -----
- copyEmpty
- 	"Answer an empty copy of this collection"
- 	
- 	"Note: this code could be moved to super"
- 	
- 	^self species new!

Item was removed:
- ----- Method: Set>>initialize: (in category 'private') -----
- initialize: n
- 	"Initialize array to an array size of n"
- 	array := Array new: n.
- 	tally := 0!

Item was removed:
- ----- Method: Set>>someElement (in category 'accessing') -----
- someElement
- 	"Deprecated. Use anyOne."
- 
- 	^ self anyOne!

Item was removed:
- ----- Method: Set>>findElementOrNil: (in category 'private') -----
- findElementOrNil: anObject
- 	"Answer the index of a first slot containing either a nil (indicating an empty slot) or an element that matches the given object. Answer the index of that slot or zero. Fail if neither a match nor an empty slot is found."
- 
- 	| index |
- 	self deprecated: 'Use #scanFor:.'.
- 	index := self scanFor: anObject.
- 	index > 0 ifTrue: [^index].
- 
- 	"Bad scene.  Neither have we found a matching element
- 	nor even an empty slot.  No hashed set is ever supposed to get
- 	completely full."
- 	self error: 'There is no free space in this set!!'.!

Item was removed:
- ----- Method: Set>>doWithIndex: (in category 'enumerating') -----
- doWithIndex: aBlock2
- 	"Support Set enumeration with a counter, even though not ordered"
- 	| index |
- 	index := 0.
- 	self do: [:item | aBlock2 value: item value: (index := index+1)]!

Item was removed:
- ----- Method: Set class>>sizeFor: (in category 'instance creation') -----
- sizeFor: nElements
- 	"Large enough size to hold nElements with some slop (see fullCheck)"
- 	nElements <= 0 ifTrue: [^ 1].
- 	^ nElements+1*4//3!

Item was removed:
- ----- Method: Set>>union: (in category 'enumerating') -----
- union: aCollection
- 	"Answer the set theoretic union of the receiver and aCollection, using the receiver's notion of equality and not side effecting the receiver at all."
- 
- 	^ self copy addAll: aCollection; yourself
- 
- !

Item was removed:
- ----- Method: Set>>add:withOccurrences: (in category 'adding') -----
- add: newObject withOccurrences: anInteger
- 	^ self add: newObject!

Item was removed:
- ----- Method: Set>>fullCheck (in category 'private') -----
- fullCheck
- 	"Keep array at least 1/4 free for decent hash behavior"
- 	array size - tally < (array size // 4 max: 1)
- 		ifTrue: [self grow]!

Item was removed:
- ----- Method: Set class>>new (in category 'instance creation') -----
- new
- 	^ self basicNew initialize: 5!

Item was removed:
- ----- Method: Set>>errorNoFreeSpace (in category 'private') -----
- errorNoFreeSpace
- 
- 	self error: 'There is no free space in this collection!!'!

Item was removed:
- ----- Method: Set>>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 |
- 	index := start := anObject hash \\ array size + 1.
- 	[ 
- 		(array at: index) ifNil: [ ^index ].
- 		(index := index \\ array size + 1) = start ] whileFalse.
- 	self errorNoFreeSpace!

Item was removed:
- ----- Method: Set>>atRandom: (in category 'accessing') -----
- atRandom: aGenerator
- 	"Answer a random element of the receiver. Uses aGenerator which
-     should be kept by the user in a variable and used every time. Use
-     this instead of #atRandom for better uniformity of random numbers because 
- 	only you use the generator. Causes an error if self has no elements."
- 	| rand |
- 
- 	self emptyCheck.
- 	rand := aGenerator nextInt: self size.
- 	self doWithIndex:[:each :ind |
- 		ind = rand ifTrue:[^each]].
- 	^ self errorEmptyCollection
- !

Item was removed:
- ----- Method: Set>>grow (in category 'private') -----
- grow
- 	"Grow the elements array and reinsert the old elements"
- 	
- 	self growTo: array size + self growSize!

Item was removed:
- ----- Method: Set class>>rehashAllInstances (in category 'initialization') -----
- rehashAllInstances
- 	"Do not use #allInstancesDo: because rehash may create new instances."
- 
- 	self allInstances do: [ :each | each rehash ] !

Item was removed:
- ----- 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 removed:
- ----- Method: Set>>array (in category 'private') -----
- array
- 	^ array!

Item was removed:
- ----- Method: Set>>comeFullyUpOnReload: (in category 'objects from disk') -----
- comeFullyUpOnReload: smartRefStream
- 	"Symbols have new hashes in this image."
- 
- 	self rehash.
- 	"^ self"
- !

Item was removed:
- ----- Method: Set>>postCopy (in category 'copying') -----
- postCopy
- 	super postCopy.
- 	array := array copy!

Item was removed:
- ----- Method: Set>>atNewIndex:put: (in category 'private') -----
- atNewIndex: index put: anObject
- 	array at: index put: anObject.
- 	tally := tally + 1.
- 	self fullCheck!

Item was removed:
- ----- Method: Set>>size (in category 'accessing') -----
- size
- 	^ tally!

Item was removed:
- ----- Method: Set>>occurrencesOf: (in category 'testing') -----
- occurrencesOf: anObject 
- 	^ (self includes: anObject) ifTrue: [1] ifFalse: [0]!

Item was removed:
- ----- Method: Set class>>new: (in category 'instance creation') -----
- new: nElements
- 	"Create a Set large enough to hold nElements without growing"
- 	^ self basicNew initialize: (self sizeFor: nElements)!

Item was removed:
- ----- Method: Set>>capacity (in category 'accessing') -----
- capacity
- 	"Answer the current capacity of the receiver."
- 
- 	^ array size!

Item was removed:
- ----- 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>>growTo: (in category 'private') -----
- growTo: anInteger
- 	"Grow the elements array and reinsert the old elements"
- 	
- 	| oldElements |
- 	oldElements := array.
- 	array := Array new: anInteger.
- 	self noCheckNoGrowFillFrom: oldElements!

Item was removed:
- ----- Method: Set>>rehash (in category 'private') -----
- rehash
- 	
- 	self growTo: array size!




More information about the Squeak-dev mailing list