class: OrderedDictionary
authorStefan Vogel <sv@exept.de>
Fri, 08 Nov 2013 16:12:05 +0100
changeset 15801 9a2b30dc6345
parent 15800 be0b36a7c1e2
child 15802 f2a9e65c3f8c
class: OrderedDictionary added: #removeIndex: #reversed comment/format in:6 methods changed:34 methods optimizations
OrderedDictionary.st
--- a/OrderedDictionary.st	Fri Nov 08 10:26:18 2013 +0100
+++ b/OrderedDictionary.st	Fri Nov 08 16:12:05 2013 +0100
@@ -73,6 +73,7 @@
 
     [author:]
         Ifor Wyn Williams <ifor@uk.ac.man.cs>
+        Changed by: exept
 
     [see also:]
         OrderedCollection Dictionary
@@ -144,17 +145,21 @@
 
 !OrderedDictionary methodsFor:'accessing'!
 
-after: anAssociation 
+after:anAssociation 
     "Return the association after anAssociation in the order. 
-     If anAssociation is the last association in the order, return nil. 
+     If anAssociation is the last association in the order, return nil.
      If anAssociation is not found, invoke an error notifier"
 
-    1 to: order size - 1 do: [:index | (self associationAt: (order at: index))
-                    = anAssociation ifTrue: [^self associationAt: (order at: index + 1)]].
-    (self associationAt: (order last))
-            = anAssociation
-            ifTrue: [^nil]
-            ifFalse: [^self error: 'not found']
+    |sz "{ Class:SmallInteger }"|
+
+    sz := order size.
+    1 to:sz do:[:index | 
+        (self associationAt:(order at:index)) = anAssociation ifTrue:[
+            index == sz ifTrue:[^ nil].
+            ^ self associationAt:(order at:index + 1)
+        ]
+    ].
+    ^ self errorNotFound:anAssociation.
 !
 
 associations
@@ -164,23 +169,17 @@
 !
 
 at:aKey ifAbsentPut:valueBlock
-    |val|
-
-    ^ self at:aKey ifAbsent:[ self at:aKey put:valueBlock value ]
+    ^ self at:aKey ifAbsent:[self at:aKey put:valueBlock value]
 !
 
-at: key put: anObject 
+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 its value to anObject. 
      If key is already present, the order remains unchanged.
      Return anObject."
 
-    "/ claus: super can check this much faster ...
-    "/ (super includesKey:key)
-    "/ ... but that leads to trouble in add:* methods. (sigh)
-
-    (order includes: key) ifFalse: [order add: key].
-    ^ super at: key put: anObject
+    (self includesKey: key) ifFalse:[order add: key].
+    ^ super at:key put:anObject
 !
 
 atAll:indexCollection put: anObject 
@@ -193,7 +192,7 @@
 atAllPut: anObject 
     "Put anObject into the value field of every association in the dictionary"
 
-    order do: [:key | self at: key put: anObject]
+    order do:[:key | super at: key put:anObject]
 !
 
 atIndex:index
@@ -211,7 +210,7 @@
 !
 
 atIndex:index put:anAssociation
-    "put an association to a given index. remove the old associatioan at this index"
+    "put an association to a given index. remove the old association at this index"
     |key|
 
     key := anAssociation key.
@@ -220,22 +219,27 @@
     ].
     super removeKey:(order at:index) ifAbsent:[].
     order at:index put:key.
-    ^ super add:anAssociation.
+    super at:key put:anAssociation value.
+    ^ anAssociation.
 
     "Created: 28.9.1995 / 16:30:15 / stefan"
 !
 
-before: anAssociation 
+before:anAssociation 
     "Return the association before anAssociation in the order. 
-     If anAssociation is the first association in the order, return nil. 
+     If anAssociation is the first association in the order, return nil.
      If anAssociation is not found, invoke an error notifier"
+    
+    |sz "{ Class:SmallInteger }"|
 
-    2 to:order size do:[:index | 
-        (self associationAt:(order at:index)) = anAssociation 
-            ifTrue:[ ^ self associationAt:(order at:index - 1)] 
+    sz := order size.
+    1 to:sz do:[:index | 
+        (self associationAt:(order at:index)) = anAssociation ifTrue:[
+            index == 1 ifTrue:[^ nil].
+            ^ self associationAt:(order at:index - 1)
+        ]
     ].
-    (self associationAt:order first) = anAssociation ifTrue: [^ nil].
-    ^ self error: 'not found'
+    ^ self errorNotFound:anAssociation.
 !
 
 first
@@ -307,7 +311,7 @@
 valueAt:index
     "get the value at the given index"
 
-    ^ super at:(order at:index).
+    ^ self at:(order at:index).
 
     "
      |s|
@@ -321,58 +325,52 @@
 values
     "Return a OrderedCollection containing the receiver's values."
 
-    ^ order collect: [:key | (self at: key) ].
+    ^ order collect:[:key | self at:key].
 ! !
 
 !OrderedDictionary methodsFor:'adding'!
 
-add: anAssociation 
-    "add anAssociation to the dictionary. 
-     If anAssociation is already present in the dictionary,
-     the order will not be changed. (See also: #addLast:)"
-
-    | key |
-
-    key := anAssociation key.
-    (super includesKey: key) ifFalse: [order add: key].
-    ^ super add: anAssociation
-!
-
 add: anAssociation after: oldAssociation 
     "Add the argument, anAssociation, as an element of the dictionary. Put it 
     in the position just succeeding oldAssociation. Return anAssociation."
 
-    | index |
+    | index key |
 
     index := self indexOfAssociation: oldAssociation 
-                            ifAbsent: [self error: 'association not found'].
-    self removeFromOrder: anAssociation key.
-    order add: anAssociation key after: (order at: index).
-    super add: anAssociation.
+                            ifAbsent: [^ self errorNotFound:anAssociation].
+    key := anAssociation key.
+    order remove:key ifAbsent:[].
+    order add:key after:(order at: index).
+    super at:key put:anAssociation value.
     ^ anAssociation
 !
 
-add: anAssociation before: oldAssociation 
+add:anAssociation before:oldAssociation 
     "Add the argument, anAssociation, as an element of the dictionary. Put it 
     in the position just preceding oldAssociation. Return anAssociation."
 
-    | index |
+    | index key |
 
     index := self indexOfAssociation: oldAssociation 
-                            ifAbsent: [self error: 'association not found'].
-    self removeFromOrder: anAssociation key.
-    order add: anAssociation key before: (order at: index).
-    super add: anAssociation.
+                            ifAbsent: [^ self errorNotFound:anAssociation].
+    key := anAssociation key.
+    order remove:key ifAbsent:[].
+    order add:key before:(order at: index).
+    super at:key put:anAssociation value.
     ^ anAssociation
 !
 
-add: anAssociation beforeIndex: spot 
+add:anAssociation beforeIndex:spot 
     "Add the argument, anAssociation, as an element of the receiver.  Put it
     in the position just preceding the indexed position spot.  Return newObject."
 
-    self removeFromOrder: anAssociation key.
-    order add: anAssociation key beforeIndex: spot.
-    ^ super add: anAssociation
+    |key|
+
+    key := anAssociation key.
+    order remove:key ifAbsent:[].
+    order add:key beforeIndex:spot.
+    super at:key put:anAssociation value.
+    ^ anAssociation
 
     "Modified: 28.9.1995 / 14:06:53 / stefan"
 !
@@ -383,8 +381,7 @@
      if it does not (i.e. it is another OD or a dictionary), use #addAllAssociationsFirst:.
      Returns the argument, aCollectionOfAssociations (sigh)."
 
-    self addAllLast:aCollectionOfAssociations.
-    ^ aCollectionOfAssociations
+    ^ self addAllLast:aCollectionOfAssociations.
 
     "Modified: 28.2.1997 / 15:51:23 / cg"
 !
@@ -393,8 +390,7 @@
     "Add each association of aDictionaryOrOrderedDictionary to my end.
      We expect the argument to respond to #associationsDo:."
 
-    self addAllAssociationsLast:aDictionaryOrOrderedDictionary.
-    ^ aDictionaryOrOrderedDictionary
+    ^ self addAllAssociationsLast:aDictionaryOrOrderedDictionary.
 
     "Created: 28.2.1997 / 15:52:02 / cg"
 !
@@ -419,22 +415,30 @@
     "Created: 28.2.1997 / 15:48:37 / cg"
 !
 
-addFirst: anAssociation 
+addFirst:anAssociation 
     "Add anAssociation to the beginning of the receiver."
 
-    self removeFromOrder: anAssociation key.
-    order addFirst: anAssociation key.
-    ^ super add: anAssociation.
+    |key|
+
+    key := anAssociation key.
+    order remove:key ifAbsent:[].
+    order addFirst:key.
+    super at:key put:anAssociation value.
+    ^ anAssociation
 !
 
-addLast: anAssociation 
+addLast:anAssociation 
     "Add anAssociation to the end of the receiver.
      If anAssociation is already present in the dictionary,
      it will be moved to the end. (See also: #add:)"
 
-    self removeFromOrder: anAssociation key.
-    order add: anAssociation key.
-    ^ super add: anAssociation.
+    |key|
+
+    key := anAssociation key.
+    order remove:key ifAbsent:[].
+    order add:key.
+    super at:key put:anAssociation value.
+    ^ anAssociation
 ! !
 
 !OrderedDictionary methodsFor:'copying'!
@@ -442,29 +446,25 @@
 copyEmpty
     "Return a copy of the receiver that contains no elements."
 
-    ^ (self class) new: 10
+    ^ self species new: 10
 !
 
-copyFrom: startIndex to: endIndex 
+copyFrom:startIndex to:endIndex 
     "Return a copy of the receiver that contains elements from 
      position startIndex to endIndex."
+    
+    |newDict|
 
-    | newDict |
-    endIndex < startIndex ifTrue: [^self copyEmpty].
-    (startIndex < 1 or: [endIndex > order size])
-            ifTrue: [^ self errorNotFound].
-    newDict := self copyEmpty: endIndex - startIndex + 1.
-    startIndex to: endIndex do: [:index | newDict add: (self associationAt: (order at: index))].
-    ^ newDict
-!
-
-copyWith: anAssociation 
-    "Return a copy of the dictionary that is 1 bigger than the receiver and 
-     includes the argument, anAssociation, at the end."
-
-    | newDict |
-    newDict := self copy.
-    newDict add: anAssociation.
+    endIndex < startIndex ifTrue:[
+        ^ self copyEmpty
+    ].
+    (startIndex < 1 or:[ endIndex > order size ]) ifTrue:[
+        ^ self errorNotFound
+    ].
+    newDict := self copyEmpty:endIndex - startIndex + 1.
+    startIndex to:endIndex do:[:index | 
+        newDict add:(self associationAt:(order at:index))
+    ].
     ^ newDict
 !
 
@@ -474,8 +474,8 @@
      No error is reported, if elementToSkip is not in the collection."
 
     | newDict |
-    newDict := self class new:order size - 1.
-    self associationsDo: [:assoc | anAssociation = assoc ifFalse: [newDict add: assoc]]
+    newDict := self species new:order size - 1.
+    self associationsDo:[:assoc | anAssociation = assoc ifFalse:[newDict add:assoc]]
 !
 
 postCopy
@@ -524,13 +524,13 @@
 
     |newDict|
 
-    newDict := self class new.
+    newDict := self species new.
     order do:[:key | 
         |assoc|
 
         assoc := self associationAt:key.
         (aBlock value:assoc) ifTrue: [
-            newDict add:assoc
+            newDict at:key put:assoc value.
         ]
     ].
     ^ newDict
@@ -552,8 +552,8 @@
 
     order do:[:key | 
         |el|
-
-        (aBlock value: (el := self at:key)) ifTrue:[^ el]
+        el := self at:key.
+        (aBlock value:el) ifTrue:[^ el]
     ].
     ^ exceptionBlock value
 !
@@ -564,9 +564,10 @@
     order do: [:key | aBlock value: (self at: key)]
 !
 
-do: aBlock from: firstIndex to: lastIndex 
-    "Evaluate aBlock with each of the dictionary's associations from index 
-    firstIndex to index secondIndex as the argument."
+do: aBlock from: firstIndex to: lastIndex
+    <resource: #obsolete>
+
+    self obsoleteMethodWarning:'use #from:to:do:'.
 
     self from:firstIndex to:lastIndex do:aBlock.
 !
@@ -575,7 +576,10 @@
     "Return the index of the first association in the dictionary for which aBlock
     evaluates as true. If the block does not evaluate to true, return exceptionalValue"
 
-    1 to:order size do:[:index | 
+    |stop  "{ Class: SmallInteger }" |
+
+    stop := order size.
+    1 to:stop do:[:index | 
         (aBlock value:(self associationAt:(order at:index))) ifTrue: [^ index]
     ].
     ^ exceptionalValue value
@@ -585,7 +589,10 @@
     "Return the index of the last association in the dictionary for which aBlock
      evaluates as true. If the block does not evaluate to true, return 0"
 
-    order size to:1 by:-1 do: [:index | 
+    |start "{ Class: SmallInteger }"|
+
+    start := order size.
+    start to:1 by:-1 do: [:index | 
         (aBlock value:(self associationAt:(order at:index))) ifTrue: [^ index]
     ].
     ^ 0
@@ -596,7 +603,10 @@
      evaluates as true. Start the backward search at startIndex.
      If the block does not evaluate to true, return 0"
 
-    startIndex to:1 by:-1 do: [:index | 
+    |start "{ Class: SmallInteger }"|
+
+    start := startIndex.
+    start to:1 by:-1 do: [:index | 
         (aBlock value:(self associationAt:(order at:index))) ifTrue: [^ index]
     ].
     ^ 0
@@ -608,7 +618,12 @@
      End the search at endIndex or when an element is found.
      If the block does not evaluate to true, return 0"
 
-    startIndex to:endIndex by:-1 do: [:index | 
+    |start "{ Class: SmallInteger }" 
+     end "{ Class: SmallInteger }"|
+
+    start := startIndex.
+    end := endIndex.
+    start to:end by:-1 do: [:index | 
         (aBlock value:(self associationAt:(order at:index))) ifTrue: [^ index]
     ].
     ^ 0
@@ -618,7 +633,12 @@
     "Evaluate aBlock with each of the dictionary's associations from index 
     firstIndex to index secondIndex as the argument."
 
-    order from:firstIndex to:lastIndex do:[:key |
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }" |
+
+    start := firstIndex. "/ these assignments force type checking...
+    stop := lastIndex.  "/ and guarantee inline loop code below.
+    order from:start to:stop do:[:key |
         aBlock value: (self at:key)
     ].
 !
@@ -632,8 +652,8 @@
 
     order do:[:key | 
         |el|
-
-        (aBlock value:key value: (el := self at:key)) ifTrue:[^ el]
+        el := self at:key.
+        (aBlock value:key value:el) ifTrue:[^ el]
     ].
     ^ exceptionBlock value
 !
@@ -650,7 +670,7 @@
      WARNING: do not add/remove elements while iterating over the receiver.
               Iterate over a copy to do this."
 
-    order do: [:key | aBlock value:key value:(self at: key)].
+    order do:[:key | aBlock value:key value:(self at: key)].
 
     "Modified: / 26.6.1999 / 10:55:30 / ps"
     "Created: / 15.10.1999 / 16:49:31 / cg"
@@ -697,7 +717,10 @@
     "Evaluate aBlock with each of the dictionary's associations as the argument,
     starting with the last element and taking each in sequence up to the first."
 
-    order size to:1 by:-1 do: [:index | 
+    |sz  "{ Class:SmallInteger }"|
+
+    sz := order size.
+    sz to:1 by:-1 do: [:index | 
         aBlock value:(self associationAt:(order at:index))
     ]
 !
@@ -705,16 +728,7 @@
 reversed
     "Return with a new OrderedDictionary with its associations in reverse order."
 
-    | newDict|
-
-    newDict := self class new.
-    order size to:1 by:-1 do:[:index | 
-        |key|
-
-        key := order at:index.
-        newDict at:key put:(self at:key)
-    ].
-    ^ newDict
+    ^ self copy reverse.
 !
 
 select:aBlock 
@@ -726,11 +740,11 @@
 
     newColl := self species new.
     order do:[:key | 
-        |assoc|
+        |val|
 
-        assoc := self associationAt:key.
-        (aBlock value:(assoc value)) ifTrue: [
-            newColl add:assoc
+        val := self at:key.
+        (aBlock value:val) ifTrue:[
+            newColl at:key put:val.
         ]
     ].
     ^ newColl
@@ -744,8 +758,10 @@
 
 !OrderedDictionary methodsFor:'private'!
 
-removeFromOrder: aKey 
-	order remove: aKey ifAbsent: []
+removeFromOrder: aKey
+    <resource: #obsolete>
+ 
+    order remove: aKey ifAbsent: []
 ! !
 
 !OrderedDictionary methodsFor:'queries'!
@@ -785,9 +801,8 @@
     |key|
 
     order size == 0 ifTrue:[
-	"error if collection is empty"
-
-	^ self emptyCollectionError.
+        "error if collection is empty"
+        ^ self emptyCollectionError.
     ].
     key := order removeFirst.
     ^ super removeKey:key.
@@ -796,25 +811,35 @@
 removeFromIndex:fromIndex toIndex:toIndex
     "Returns the receiver."
 
-    | keys |
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }" |
 
-    keys := order copyFrom:fromIndex to:toIndex.
-    order removeFromIndex:fromIndex toIndex:toIndex.
-    keys do:[ :key |
+    start := fromIndex. 
+    stop := toIndex. 
+
+    order from:start to:stop do:[:key |
         super removeKey:key.
     ].
+    order removeFromIndex:fromIndex toIndex:toIndex.
 
     "Created: 28.9.1995 / 12:04:33 / stefan"
 !
 
+removeIndex:anInteger
+    self removeFromIndex:anInteger toIndex:anInteger.
+!
+
 removeKey:aKey
     order remove:aKey.
     ^ super removeKey:aKey.
 !
 
 removeKey:aKey ifAbsent:aBlock
+    |oldValue|
+
+    oldValue := super removeKey:aKey ifAbsent:aBlock.
     order remove:aKey ifAbsent:[].
-    ^ super removeKey:aKey ifAbsent:aBlock.
+    ^ oldValue.
 
     "Created: / 31-01-2011 / 22:04:01 / cg"
 !
@@ -935,7 +960,12 @@
     "Return the next index of aAssociation within the receiver between startIndex
      and stopIndex. If the receiver does not contain aAssociation, return nil"
 
-    startIndex to: stopIndex do: [:i | 
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"|
+
+    start := startIndex.
+    stop := stopIndex.
+    start to: stop do: [:i | 
         (self associationAt: (order at: i)) = aAssociation ifTrue: [^i]].
     ^nil
 !
@@ -944,7 +974,12 @@
     "Return the next index of aKey within the receiver between startIndex and 
      stopIndex.  If the receiver does not contain aKey, return nil"
 
-    startIndex to: stopIndex do: [:i | 
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"|
+
+    start := startIndex.
+    stop := stopIndex.
+    start to: stop do: [:i | 
         (order at: i) = aKey ifTrue: [^i]].
     ^nil
 !
@@ -953,7 +988,12 @@
     "Return the next index of aValue within the receiver between startIndex and
      stopIndex. If the receiver does not contain aValue, return nil"
 
-    startIndex to: stopIndex do: [:i | 
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }" |
+
+    start := startIndex. 
+    stop := stopIndex.  
+    start to: stop do: [:i | 
         (self at: (order at: i)) = aValue ifTrue: [^i]].
     ^nil
 !
@@ -963,7 +1003,12 @@
      startIndex  and stopIndex working backwards through the receiver. 
      If the receiver does not contain aAssociation, return nil"
 
-    startIndex to: stopIndex by: -1
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"|
+
+    start := startIndex.
+    stop := stopIndex.
+    start to: stop by: -1
             do: [:i | (self associationAt: (order at: i)) = aAssociation ifTrue: [^i]].
     ^nil
 !
@@ -973,20 +1018,32 @@
      stopIndex working backwards through the receiver. 
      If the receiver does not contain aKey, return nil"
 
-    startIndex to: stopIndex by: -1
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"|
+
+    start := startIndex.
+    stop := stopIndex.
+    start to: stop by: -1
             do: [:i | (order at: i) = aKey ifTrue: [^i]].
     ^nil
 !
 
-prevIndexOfValue: aValue from: startIndex to: stopIndex 
+prevIndexOfValue:aValue from:startIndex to:stopIndex 
     "Return the previous index of aValue within the receiver between startIndex
-     and stopIndex working backwards through the receiver. 
+     and stopIndex working backwards through the receiver.
      If the receiver does not contain aValue, return nil"
+    
+    |start "{ Class:SmallInteger }"
+     stop  "{ Class:SmallInteger }"|
 
-    startIndex to: stopIndex by: -1
-            do: [:i | 
-                (self at: (order at: i)) = aValue ifTrue: [^i]].
-    ^nil
+    start := startIndex.
+    stop := stopIndex.
+    start to:stop by:-1 do:[:i | 
+        (self at:(order at:i)) = aValue ifTrue:[
+            ^ i
+        ]
+    ].
+    ^ nil
 ! !
 
 !OrderedDictionary methodsFor:'sorting & reordering'!
@@ -1016,10 +1073,10 @@
 !OrderedDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.44 2013-09-15 10:43:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.45 2013-11-08 15:12:05 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.44 2013-09-15 10:43:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.45 2013-11-08 15:12:05 stefan Exp $'
 ! !