Levente Uzonyi uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ul.282.mcz ==================== Summary ==================== Name: Collections-ul.282 Author: ul Time: 25 January 2010, 10:56:13.924 pm UUID: 44962376-0c2e-ea4c-9fce-9fb056cd768b Ancestors: Collections-nice.281 In the HashedCollection hierarchy: - cosmetic changes: use #ifNotNil: if possible - use unary symbols instead of blocks with a single unary send - removed unnecessary line from #atRandom - restored correct compatibility method for #fullCheck In Dictionary: - make sure that #associationsSelect: works with PluggableDictionary by using #copyEmpty instead of #species + #new - deprecated #keyForIdentity:, because it's similar to #keyAtIdentityValue:ifAbsent: In WeakKeyDictionary: - #rehash throws away nil keys, so we don't have to iterate twice over array - don't let the key go away in #noCheckNoGrowFillFrom: In WeakKeyToCollectionDictionary: - don't let the key go away in #noCheckNoGrowFillFrom: - removed #finalizeValues because it became same as super In WeakSet: - #do:after: doesn't skip the first element if anElement is nil - speed up #slowSize - don't rehash twice in #grow, just count the occupied slots first with #slowSize Other: - simplified a few KeyedSet's methods - added #collect: to PluggableDictionary (super doesn't copy the blocks) =============== Diff against Collections-nice.281 =============== Item was changed: + ----- Method: IdentityDictionary>>keyAtValue:ifAbsent: (in category 'accessing') ----- - ----- Method: IdentityDictionary>>keyAtValue:ifAbsent: (in category 'private') ----- keyAtValue: value ifAbsent: exceptionBlock "Answer the key that is the external name for the argument, value. If there is none, answer the result of evaluating exceptionBlock." + ^super keyAtIdentityValue: value ifAbsent: exceptionBlock! - self associationsDo: - [:association | value == association value ifTrue: [^ association key]]. - ^ exceptionBlock value! Item was changed: ----- Method: Set>>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." 1 to: anArray size do: [ :index | + (anArray at: index) ifNotNil: [ :object | - | object | - (object := anArray at: index) ifNotNil: [ array at: (self scanForEmptySlotFor: object) put: object ] ]! Item was changed: ----- Method: WeakSet>>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 | + (anArray at: index) ifNotNil: [ :object | + object == flag ifFalse: [ - | object | - ((object := anArray at: index) == flag or: [ - object == nil ]) ifFalse: [ array at: (self scanForEmptySlotFor: object) put: object. + tally := tally + 1 ] ] ]! - tally := tally + 1 ] ]! Item was changed: ----- Method: WeakKeyDictionary>>finalizeValues: (in category 'finalization') ----- finalizeValues: finiObjects "Remove all associations with key == nil and value is in finiObjects. This method is folded with #rehash for efficiency." | oldArray | oldArray := array. array := Array new: oldArray size. tally := 0. + 1 to: array size do: [ :index | + (oldArray at: index) ifNotNil: [ :association | + association key ifNotNil: [ :key | "Don't let the key go away" + (finiObjects includes: association value) ifFalse: [ + array + at: (self scanForEmptySlotFor: key) + put: association. + tally := tally + 1 ] ] ] ]! - 1 to: array size do:[ :i | - | association | - (association := oldArray at: i) ifNotNil: [ - | key | - ((key := association key) == nil and: [ "Don't let the key go away" - finiObjects includes: association value ]) - ifFalse: [ - array - at: (self scanForEmptySlotFor: key) - put: association. - tally := tally + 1 ] ] ]! Item was changed: ----- 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 ] + ! - | oldTally | - oldTally := tally. - self rehash. - oldTally // 2 < tally ifTrue: [ super grow ]! Item was changed: ----- Method: WeakSet>>growTo: (in category 'private') ----- growTo: anInteger "Grow the elements array and reinsert the old elements" | oldElements | oldElements := array. + array := WeakArray new: anInteger withAll: flag. - array := WeakArray new: anInteger. - array atAllPut: flag. self noCheckNoGrowFillFrom: oldElements! Item was changed: ----- 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 - 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 :index | + index = rand ifTrue: [ ^each ] ]! - self doWithIndex:[:each :ind | - ind = rand ifTrue:[^each]]. - ^ self errorEmptyCollection - ! Item was changed: ----- Method: KeyedSet>>member: (in category 'adding') ----- member: newObject "Include newObject as one of the receiver's elements, if already exists just return it" | index | newObject ifNil: [self error: 'Sets cannot meaningfully contain nil as an element']. index := self scanFor: (keyBlock value: newObject). + (array at: index) ifNotNil: [ :element | ^element ]. - (array at: index) ifNotNil: [^ array at: index]. self atNewIndex: index put: newObject. ^ newObject! Item was changed: + ----- Method: WeakSet>>add: (in category 'adding') ----- - ----- 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 | newObject ifNil: [self error: 'Sets cannot meaningfully contain nil as an element']. index := self scanFor: newObject. ((element := array at: index) == flag or: [ element == nil ]) ifTrue: [self atNewIndex: index put: newObject]. ^newObject! Item was changed: ----- Method: KeyedSet>>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 ]! - | obj | - obj := array at: (self scanFor: key). - obj ifNil: [^ aBlock value]. - ^ obj! Item was changed: + ----- Method: WeakSet>>includes: (in category 'testing') ----- - ----- Method: WeakSet>>includes: (in category 'public') ----- includes: anObject + ^(array at: (self scanFor: anObject)) + ifNil: [ false ] + ifNotNil: [ :object | object ~~ flag ]! - | element | - ^((element := array at: (self scanFor: anObject)) == flag or: [ element == nil ]) not! Item was changed: ----- Method: Dictionary>>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." 1 to: anArray size do: [ :index | + (anArray at: index) ifNotNil: [ :association | - | object | - (object := anArray at: index) ifNotNil: [ array + at: (self scanForEmptySlotFor: association key) + put: association ] ]! - at: (self scanForEmptySlotFor: object key) - put: object ] ]! Item was changed: ----- Method: KeyedSet>>initialize: (in category 'private') ----- initialize: n + super initialize: n. + keyBlock := #key - keyBlock := [:element | element key]. ! 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" - | key | - (key := association key) ifNotNil: [ "Don't let the key go away" aBlock value: key ] ].! Item was changed: ----- Method: Dictionary>>add: (in category 'adding') ----- add: anAssociation + | index | - | index element | index := self scanFor: anAssociation key. + (array at: index) - (element := array at: index) ifNil: [ self atNewIndex: index put: anAssociation ] + ifNotNil: [ :element | element value: anAssociation value ]. - ifNotNil: [ element value: anAssociation value ]. ^anAssociation! Item was changed: ----- Method: WeakSet>>do:after: (in category 'public') ----- do: aBlock after: anElement - | each startIndex | + | startIndex | + tally = 0 ifTrue: [ ^self ]. + startIndex := anElement + ifNil: [ 0 ] + ifNotNil: [ self scanFor: anElement ]. + startIndex + 1 to: array size do: [ :index | + (array at: index) ifNotNil: [ :object | + object == flag ifFalse: [ + aBlock value: object ] ] ]! - tally = 0 ifTrue: [^self]. - startIndex := anElement ifNil: [1] ifNotNil: - [self scanFor: anElement]. - startIndex + 1 to: array size do: - [:index | - ((each := array at: index) == nil or: [each == flag]) - ifFalse: [aBlock value: each] - ]! Item was changed: + ----- Method: WeakSet>>remove:ifAbsent: (in category 'removing') ----- - ----- Method: WeakSet>>remove:ifAbsent: (in category 'public') ----- remove: oldObject ifAbsent: aBlock | index | index := self scanFor: oldObject. (array at: index) == flag ifTrue: [ ^ aBlock value ]. array at: index put: flag. tally := tally - 1. self fixCollisionsFrom: index. ^oldObject! 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! Item was changed: ----- Method: HashedCollection class>>goodPrimeAtLeast: (in category 'sizing') ----- goodPrimeAtLeast: lowerLimit "Answer the next good prime >= lowerlimit. If lowerLimit is larger than the largest known good prime, just make it odd." | primes low mid high prime | primes := self goodPrimes. low := 1. high := primes size. lowerLimit > (primes at: high) ifTrue: [ + ^lowerLimit bitOr: 1 ]. - ^lowerLimit even - ifTrue: [ lowerLimit + 1 ] - ifFalse: [ lowerLimit ] ]. [ high - low <= 1 ] whileFalse: [ mid := high + low // 2. prime := primes at: mid. prime = lowerLimit ifTrue: [ ^prime ]. prime < lowerLimit ifTrue: [ low := mid ] ifFalse: [ high := mid ] ]. (primes at: low) >= lowerLimit ifTrue: [ ^primes at: low ]. ^primes at: high! Item was changed: ----- Method: Dictionary>>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 | - | index assoc | index := self scanFor: key. + (array at: index) + ifNil: [ self atNewIndex: index put: (Association key: key value: anObject) ] + ifNotNil: [ :association | association value: anObject ]. + ^anObject! - assoc := array at: index. - assoc - ifNil: [self atNewIndex: index put: (Association key: key value: anObject)] - ifNotNil: [assoc value: anObject]. - ^ anObject! Item was changed: ----- Method: KeyedSet>>keysSorted (in category 'accessing') ----- keysSorted + ^self keys sort! - | keys | - keys := SortedCollection new. - self do: [:item | keys add: (keyBlock value: item)]. - ^ keys! 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 ] ] ]. + ^tally := count! - tally := array inject: 0 into: - [:total :each | (each == nil or: [each == flag]) - ifTrue: [total] ifFalse: [total + 1]]. - ^tally! 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 | + (anArray at: index) ifNotNil: [ :association | + association key ifNotNil: [ :key | "Don't let the key go away" + array + at: (self scanForEmptySlotFor: key) + put: association. + tally := tally + 1 ] ] ]! - 1 to: anArray size do:[ :i | - | association | - (association := anArray at: i) ifNotNil: [ - array - at: (self scanForEmptySlotFor: association key) - put: association. - tally := tally + 1 ] ]! Item was changed: ----- Method: WeakKeyToCollectionDictionary>>noCheckNoGrowFillFrom: (in category 'as yet unclassified') ----- noCheckNoGrowFillFrom: anArray "Add the elements of anArray except nils and associations with empty collections (or with only nils) 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 | + (anArray at: index) ifNotNil: [ :association | + association key ifNotNil: [ :key | "Don't let the key go away" + | cleanedValue | + (cleanedValue := association value copyWithout: nil) isEmpty + ifFalse: [ + association value: cleanedValue. + array + at: (self scanForEmptySlotFor: key) + put: association. + tally := tally + 1 ] ] ] ]! - 1 to: anArray size do:[ :i | - | association cleanedValue | - ((association := anArray at: i) == nil or: [ - (cleanedValue := association value copyWithout: nil) isEmpty ]) - ifFalse: [ - association value: cleanedValue. - array - at: (self scanForEmptySlotFor: association key) - put: association. - tally := tally + 1 ] ]! Item was changed: ----- Method: HashedCollection class>>rehashAll (in category 'initialization') ----- rehashAll "HashedCollection rehashAll" + self allSubclassesDo: #rehashAllInstances! - self allSubclassesDo: [ :each | each rehashAllInstances ]! Item was changed: ----- Method: HashedCollection>>fullCheck (in category 'compatibility') ----- fullCheck "This is a private method, formerly implemented in Set, that is no longer required. It is here for compatibility with external packages only." + "Keep array at least 1/4 free for decent hash behavior" + + array size * 3 < (tally * 4) ifTrue: [ self grow ]! - ^ self - ! Item was changed: ----- Method: KeyedSet>>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." 1 to: anArray size do: [ :index | + (anArray at: index) ifNotNil: [ :object | - | object | - (object := anArray at: index) ifNotNil: [ array at: (self scanForEmptySlotFor: (keyBlock value: object)) put: object ] ]! Item was changed: ----- Method: Dictionary>>associationsSelect: (in category 'enumerating') ----- associationsSelect: aBlock "Evaluate aBlock with each of my associations as the argument. Collect into a new dictionary, only those associations for which aBlock evaluates to true." | newCollection | + newCollection := self copyEmpty. + self associationsDo: [ :each | + (aBlock value: each) ifTrue: [ newCollection add: each ] ]. - newCollection := self species new. - self associationsDo: - [:each | - (aBlock value: each) ifTrue: [newCollection add: each]]. ^newCollection! 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 | + (array at: index) ifNotNil: [ :element | + aBlock value: element ] ]! - | each | - (each := array at: index) - ifNotNil: [ aBlock value: each ] ]! Item was changed: ----- Method: Set>>do: (in category 'enumerating') ----- do: aBlock tally = 0 ifTrue: [ ^self ]. 1 to: array size do: [ :index | + (array at: index) ifNotNil: [ :element | + aBlock value: element ] ]! - | each | - (each := array at: index) - ifNotNil: [ aBlock value: each ] ]! Item was changed: + ----- Method: Dictionary>>keyForIdentity: (in category 'accessing') ----- - ----- Method: Dictionary>>keyForIdentity: (in category 'testing') ----- keyForIdentity: anObject "If anObject is one of the values of the receive, return its key, else return nil. Contrast #keyAtValue: in which there is only an equality check, here there is an identity check" + self deprecated: 'Use #keyAtIdentityValue:ifAbsent:'. + ^self keyAtIdentityValue: anObject ifAbsent: nil! - self associationsDo: [:assoc | assoc value == anObject ifTrue: [^ assoc key]]. - ^ nil! Item was changed: + ----- Method: WeakSet>>do: (in category 'enumerating') ----- - ----- Method: WeakSet>>do: (in category 'public') ----- do: aBlock tally = 0 ifTrue: [ ^self ]. 1 to: array size do: [ :index | + (array at: index) ifNotNil: [ :object | + object == flag ifFalse: [ + aBlock value: object ] ] ]! - | each | - ((each := array at: index) == nil or: [ each == flag ]) - ifFalse: [ aBlock value: each ] ]! Item was changed: + ----- Method: WeakSet>>like: (in category 'accessing') ----- - ----- Method: WeakSet>>like: (in category 'public') ----- 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" | element | ^(element := array at: (self scanFor: anObject)) == flag ifFalse: [ element ]! 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 | - | index element | key ifNil: [ ^anObject ]. index := self scanFor: key. + (array at: index) - (element := array at: index) ifNil: [ self atNewIndex: index put: (WeakKeyAssociation key: key value: anObject) ] + ifNotNil: [ :association | association value: anObject ]. - ifNotNil: [ element value: anObject ]. ^anObject! Item was changed: + ----- Method: WeakSet>>collect: (in category 'enumerating') ----- - ----- Method: WeakSet>>collect: (in category 'public') ----- collect: aBlock + + | newSet | - | each newSet | newSet := self species new: self size. + tally = 0 ifTrue: [ ^newSet ]. + 1 to: array size do: [ :index | + (array at: index) ifNotNil: [ :object | + object == flag ifFalse: [ + newSet add: (aBlock value: object) ] ] ]. - tally = 0 ifTrue: [^newSet ]. - 1 to: array size do: - [:index | - ((each := array at: index) == nil or: [each == flag]) - ifFalse: [newSet add: (aBlock value: each)] - ]. ^newSet! Item was changed: ----- Method: HashedCollection class>>rehashAllInstances (in category 'initialization') ----- rehashAllInstances "Do not use #allInstancesDo: because rehash may create new instances." + self allInstances do: #rehash! - self allInstances do: [ :each | each rehash ] ! Item was changed: + ----- Method: WeakSet>>size (in category 'accessing') ----- - ----- Method: WeakSet>>size (in category 'public') ----- size "Careful!! Answer the maximum amount of elements in the receiver, not the exact amount" ^tally! Item was added: + ----- Method: PluggableDictionary>>collect: (in category 'enumerating') ----- + collect: aBlock + "Evaluate aBlock with each of my values as the argument. Collect the resulting values into a collection that is like me. Answer with the new collection." + + | newCollection | + newCollection := (self species new: self size) + hashBlock: hashBlock; + equalBlock: equalBlock; + yourself. + self associationsDo: [ :each | + newCollection at: each key put: (aBlock value: each value) ]. + ^newCollection + + ! Item was removed: - ----- Method: WeakKeyToCollectionDictionary>>finalizeValues (in category 'as yet unclassified') ----- - finalizeValues - self rehash! |
Free forum by Nabble | Edit this page |