Set.st
branchjv
changeset 17966 8b5df02e171f
parent 17928 8e8dad2e6269
child 18011 deb0c3355881
--- a/Set.st	Fri Sep 07 13:46:06 2012 +0100
+++ b/Set.st	Fri Sep 07 17:24:32 2012 +0100
@@ -25,6 +25,13 @@
 	privateIn:Set
 !
 
+Object subclass:#NilKey
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Set
+!
+
 !Set class methodsFor:'documentation'!
 
 copyright
@@ -44,11 +51,11 @@
 documentation
 "
     a Set is a collection where each element occurs at most once.
-    The inclusion test is done using = for comparison; 
+    The inclusion test is done using equality (=) for comparison; 
     see IdentitySet for sets using identity compare.
     Keep in mind, that a regular Set therefore treats 3.0 and 3 as equal
     and therefore:
-	(Set with:3.0) includes:3
+        (Set with:3.0) includes:3
     will return true (since 3.0 and 3 are equal).
     In contrast, an IdentitySet will return false, because 3.0 and 3 are not
     identical.
@@ -70,27 +77,28 @@
       If you have a rough idea how big the set is going to grow,
       create it using #new: instead of #new. Even if the size given is a
       poor guess (say half of the real size), there is some 20-30% performance
-      win to expect, since many resizing operations of the set are avoided.
+      win to expect, since many resizing operations of the set are avoided
+      (resizing is expensive, as the set does a rehash).
 
     Examples:
 
-	|s|
-	s := Set new.
-	s add:'hello'.
-	s add:'world'.
-	s add:#foo.
-	s add:1.2345678.
-	s add:'hello'.
+        |s|
+        s := Set new.
+        s add:'hello'.
+        s add:'world'.
+        s add:#foo.
+        s add:1.2345678.
+        s add:'hello'.
 
-	s printCR.
-	's size -> ' print. s size printCR.
-	'(s includes:''hello'') -> ' print. (s includes:'hello') printCR.
-	'(s includes:#foo)    -> ' print. (s includes:#foo) printCR.
-	'(s includes:''foo'')   -> ' print. (s includes:'foo') printCR.
-	'(s includes:#bar)    -> ' print. (s includes:#bar) printCR.
+        s printCR.
+        's size -> ' print. s size printCR.
+        '(s includes:''hello'') -> ' print. (s includes:'hello') printCR.
+        '(s includes:#foo)    -> ' print. (s includes:#foo) printCR.
+        '(s includes:''foo'')   -> ' print. (s includes:'foo') printCR.
+        '(s includes:#bar)    -> ' print. (s includes:#bar) printCR.
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 "
 ! !
 
@@ -100,10 +108,13 @@
     "initialize the Set class"
 
     DeletedEntry isNil ifTrue:[
-	DeletedEntry := EmptySlot new
+        DeletedEntry := EmptySlot new.
+        NilEntry := NilKey new.
     ].
 
-    "Set initialize"
+    "
+        Set initialize
+    "
 
     "Modified: 24.1.1997 / 21:09:00 / cg"
 ! !
@@ -187,7 +198,6 @@
     "Created: / 24.10.1997 / 23:13:44 / cg"
 ! !
 
-
 !Set methodsFor:'Compatibility-ST80'!
 
 initialIndexFor:hashKey boundedBy:length
@@ -298,13 +308,17 @@
      This is the same functionality as provided by the goodies/KeyedSet
      goody."
 
-    |index "{ Class: SmallInteger }" |
+    |index "{ Class: SmallInteger }"  ret|
 
-    index := self find:anObject ifAbsent:0.
+    index := self find:(anObject ? NilEntry)ifAbsent:0.
     index == 0 ifTrue:[
-	^ exceptionBlock value
+        ^ exceptionBlock value
     ].
-    ^ keyArray basicAt:index
+    ret := keyArray basicAt:index.
+    ret == NilEntry ifTrue:[
+        ret := nil.
+    ].
+    ^ ret.
 
     "Created: 20.3.1997 / 20:34:07 / cg"
     "Modified: 20.3.1997 / 20:35:49 / cg"
@@ -327,81 +341,73 @@
 
 !Set methodsFor:'adding & removing'!
 
-add:anObject
+add:keyArg
     "add the argument, anObject to the receiver.
 
      WARNING: do not add elements while iterating over the receiver.
               Iterate over a copy to do this."
 
-    |index "{ Class: SmallInteger }"|
+    |key index "{ Class: SmallInteger }"|
 
-    anObject isNil ifTrue:[  
-        ^ self invalidElementError.
+    keyArg isNil ifTrue:[
+        key := NilEntry.
+    ] ifFalse:[
+        key := keyArg.
     ].
 
-    index := self findKeyOrNil:anObject.
+    index := self findKeyOrNil:key.
     (keyArray basicAt:index) isNil ifTrue:[
         "/ not already there
-        keyArray basicAt:index put:anObject.
+        keyArray basicAt:index put:key.
         tally := tally + 1.
 
         self fullCheck.
     ].
-    ^ anObject
+    ^ keyArg
 
     "Modified: 30.1.1997 / 14:58:08 / cg"
 !
 
-addAllNonNilElements:aCollection
-    "add all non-nil elements of the argument, aCollection to the receiver.
-     Use this, when operating on a Set, that cannot hold nil.
-     Answer the argument, aCollection (sigh)."
-
-    aCollection do:[:eachElement |
-        eachElement notNil ifTrue:[
-            self add:eachElement
-        ].
-    ].
-    ^ aCollection
-
-    "
-     #(1 2 3 4) asSet addAllNonNilElements:#(5 nil 6 7 8)
-    "
-!
-
-remove:oldObject ifAbsent:exceptionBlock
+remove:oldObjectArg ifAbsent:exceptionBlock
     "remove oldObject from the collection and return it.
      If it was not in the collection return the value of exceptionBlock.
      Notice, that the returned object could be non-identical to the argument
      (although it will always be equal).
 
      WARNING: do not remove elements while iterating over the receiver.
-	      See #saveRemove: to do this."
+              See #saveRemove: to do this."
+
+    |oldObject index next removedObject|
 
-    |index next objectRemoved|
-
-    oldObject isNil ifTrue:[^ exceptionBlock value].
+    oldObjectArg isNil ifTrue:[
+        oldObject := NilEntry.
+    ] ifFalse:[
+        oldObject := oldObjectArg.
+    ].
 
     index := self find:oldObject ifAbsent:0.
     index == 0 ifTrue:[^ exceptionBlock value].
 
-    objectRemoved := keyArray basicAt:index.
+    removedObject := keyArray basicAt:index.
     keyArray basicAt:index put:nil.
     tally := tally - 1.
     tally == 0 ifTrue:[
-	keyArray := self keyContainerOfSize:(self class goodSizeFrom:0). 
+        keyArray := self keyContainerOfSize:(self class goodSizeFrom:0). 
     ] ifFalse:[
-	index == keyArray basicSize ifTrue:[
-	    next := 1
-	] ifFalse:[
-	    next := index + 1.
-	].
-	(keyArray basicAt:next) notNil ifTrue:[
-	    keyArray basicAt:index put:DeletedEntry.
-	].
-	self emptyCheck
+        index == keyArray basicSize ifTrue:[
+            next := 1
+        ] ifFalse:[
+            next := index + 1.
+        ].
+        (keyArray basicAt:next) notNil ifTrue:[
+            keyArray basicAt:index put:DeletedEntry.
+        ].
+        self emptyCheck
     ].
-    ^ objectRemoved
+    removedObject == NilEntry ifTrue:[
+        removedObject := nil.
+    ].
+    ^ removedObject
 
     "Modified: / 16.11.2001 / 10:14:24 / cg"
 !
@@ -422,6 +428,28 @@
 
      In contrast to #remove:, this does not resize the underlying collection
      and therefore does NOT rehash & change the elements order.
+     Therefor this can be used while enumerating the receiver,
+     which is not possible if #remove: is used.
+
+     WARNING: since no resizing is done, the physical amount of memory used
+              by the container remains the same, although the logical size shrinks.
+              You may want to manually resize the receiver using #emptyCheck.
+              (after the loop)"
+
+    ^ self saveRemove:oldObject ifAbsent:[].
+
+    "Created: / 16.11.2001 / 10:23:48 / cg"
+    "Modified: / 16.11.2001 / 10:24:03 / cg"
+!
+
+saveRemove:oldObjectArg ifAbsent:exceptionValueProvider
+    "remove the element, oldObject from the collection.
+     Return the element 
+     (could be non-identical to oldObject, since I hash on equality, not on identity).
+     If it was not in the collection return the value of exceptionValueProvider.
+
+     In contrast to #remove:, this does not resize the underlying collection
+     and therefore does NOT rehash & change the elements order.
      Therefore this can be used while enumerating the receiver,
      which is not possible if #remove: is used.
 
@@ -430,14 +458,19 @@
               You may want to manually resize the receiver using #emptyCheck.
               (after the loop)"
 
-    |index "{ Class:SmallInteger }"
+    |oldObject
+     index "{ Class:SmallInteger }"
      next  "{ Class:SmallInteger }"
      removedObject|
 
-    oldObject isNil ifTrue:[^ nil].
+    oldObjectArg isNil ifTrue:[
+        oldObject := NilEntry.
+    ] ifFalse:[
+        oldObject := oldObjectArg.
+    ].
 
     index := self find:oldObject ifAbsent:0.
-    index == 0 ifTrue:[^ nil].
+    index == 0 ifTrue:[^ exceptionValueProvider value].
 
     removedObject := keyArray basicAt:index.
     keyArray basicAt:index put:nil.
@@ -453,6 +486,9 @@
             keyArray basicAt:index put:DeletedEntry
         ].
     ].
+    removedObject == NilEntry ifTrue:[
+        removedObject := nil.
+    ].
     ^ removedObject
 
     "does NOT work:
@@ -503,7 +539,7 @@
     "Modified: / 16.11.2001 / 10:22:59 / cg"
 !
 
-testAndAdd:anObject
+testAndAdd:keyArg
     "add the argument, anObject to the receiver.
      Answer true, if the element did already exist in the collection,
      false otherwise.
@@ -511,16 +547,18 @@
      WARNING: do not add elements while iterating over the receiver.
               Iterate over a copy to do this."
 
-    |index "{ Class: SmallInteger }"|
+    |key index "{ Class: SmallInteger }"|
 
-    anObject isNil ifTrue:[
-        ^ self invalidElementError.
+    keyArg isNil ifTrue:[
+        key := NilEntry.
+    ] ifFalse:[
+        key := keyArg.
     ].
 
-    index := self findKeyOrNil:anObject.
+    index := self findKeyOrNil:key.
     (keyArray basicAt:index) isNil ifTrue:[
         "/ not already there
-        keyArray basicAt:index put:anObject.
+        keyArray basicAt:index put:key.
         tally := tally + 1.
 
         self fullCheck.
@@ -554,6 +592,7 @@
 
     "
      #(1 2 3 4 5) asSet = #(2 3 4 5 1) asSet
+     #(nil 1 2 3 4 5) asSet = #(2 3 4 5 1) asSet´
      #(1 2 3 4 5) asSet = #(2 3 4 5 1.0) asSet 
      #(1 2 3 4 5) asSet = #(2 3 4 5 'one') asSet 
     "
@@ -662,17 +701,20 @@
     "perform the block for all members in the collection.
 
      WARNING: do not add/remove elements while iterating over the receiver.
-	      Iterate over a copy to do this."
+              Iterate over a copy to do this."
 
     |sz "{ Class: SmallInteger }"
      element|
 
     sz := keyArray size.
     1 to:sz do:[:index |
-	element := keyArray at:index.
-	(element notNil and:[element ~~ DeletedEntry]) ifTrue:[
-	    aBlock value:element
-	]
+        element := keyArray at:index.
+        (element notNil and:[element ~~ DeletedEntry]) ifTrue:[
+            element == NilEntry ifTrue:[
+                element := nil.
+            ].
+            aBlock value:element
+        ]
     ]
 
     "Modified: 1.3.1996 / 21:41:13 / cg"
@@ -1115,12 +1157,7 @@
 includes:anObject
     "return true if the argument anObject is in the receiver"
 
-    anObject isNil ifTrue:[
-	"even if adding nil to a set is forbidden, asking for it should be ok!!"
-	"self invalidElementError."
-	^ false 
-    ].
-    ^ (self find:anObject ifAbsent:0) ~~ 0
+    ^ (self find:(anObject ? NilEntry) ifAbsent:0) ~~ 0
 !
 
 isEmpty
@@ -1148,13 +1185,7 @@
     "return the number of occurrences of anObject in the receiver.
      As I am a Set, this can only return 0 or 1."
 
-    anObject isNil ifTrue:[
-	"even if adding nil to a set is forbidden, asking for it should be ok!!"
-	"self invalidElementError."
-	^ 0.
-    ].
-
-    (self find:anObject ifAbsent:0) == 0 ifTrue:[^ 0].
+    (self find:(anObject ? NilEntry) ifAbsent:0) == 0 ifTrue:[^ 0].
     ^ 1
 
     "Modified: / 16.11.2001 / 10:30:14 / cg"
@@ -1200,21 +1231,29 @@
 
 ! !
 
+!Set::NilKey class methodsFor:'instance creation'!
+
+basicNew
+    TheOneAndOnlyInstance isNil ifTrue:[
+        TheOneAndOnlyInstance := super basicNew
+    ].
+    ^ TheOneAndOnlyInstance
+
+
+! !
+
 !Set class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Set.st,v 1.110 2012/02/22 12:55:54 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Set.st,v 1.115 2012/08/13 17:11:21 stefan Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Set.st,v 1.110 2012/02/22 12:55:54 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/Set.st,v 1.115 2012/08/13 17:11:21 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: Set.st 10792 2012-03-21 17:45:38Z vranyj1 $'
+    ^ '$Id: Set.st 10844 2012-09-07 16:24:32Z vranyj1 $'
 ! !
 
 Set initialize!
-
-
-