Dict.st
author claus
Fri, 16 Jul 1993 11:39:45 +0200
changeset 1 a27a279701f8
child 2 6526dde5f3ac
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1991-93 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Collection subclass:#Dictionary
         instanceVariableNames:'valueArray keyArray tally'
         classVariableNames:''
         poolDictionaries:''
         category:'Collections-Unordered'
!

Dictionary comment:'

COPYRIGHT (c) 1991-93 by Claus Gittinger
              All Rights Reserved

a Dictionary is (conceptionally) a collection of Associations storing key-value pairs.
(The implementation uses two array to store the keys and values separately.)
Searching for an element is done using a hash into the key arrlay.

%W% %E%

written jun 91 by claus
rewritten 92 to use hash scheme
'!

!Dictionary class methodsFor:'instance creation'!

new
    "return a new empty Dictionary"

    ^ self new:5
!

new:anInteger
    "return a new empty Dictionary with space for anInteger elements"

    ^ self basicNew setTally:anInteger
! !

!Dictionary methodsFor:'testing'!

size
    "return the number of elements in the receiver"

    ^ tally
!

includesKey:aKey
    "return true, if the argument, aKey is a key in the receiver"

    ^ (self findKey:aKey ifAbsent:[0]) ~~ 0
!

isFixedSize
    "return true if the receiver cannot grow - this will vanish once
     Arrays and Strings learn how to grow ..."

    ^ false
! !

!Dictionary methodsFor:'accessing'!

at:aKey
    "return the element indexed by aKey - report an error if none found"

    |index|

    aKey isNil ifTrue:[
        self error:'nil is not allowed as key'
    ] ifFalse:[
        index := self findKey:aKey ifAbsent:[0].
        index == 0 ifTrue:[^ self errorKeyNotFound].
        ^ valueArray basicAt:index
    ]
!

at:aKey ifAbsent:exceptionBlock
    |index|

    aKey isNil ifTrue:[
        self error:'nil is not allowed as key'
    ] ifFalse:[
        index := self findKey:aKey ifAbsent:[0].
        index == 0 ifTrue:[^ exceptionBlock value].
        ^ valueArray basicAt:index
    ]
!

at:aKey put:anObject
    "add the argument anObject under key, aKey to the receiver"

    |index element|

    aKey isNil ifTrue:[
        self error:'nil is not allowed as key'
    ] ifFalse:[
        index := self findKeyOrNil:aKey.
        element := valueArray basicAt:index.
        element notNil ifTrue:[
            valueArray basicAt:index put:anObject.
            ^ anObject
        ].
        keyArray basicAt:index put:aKey.
        valueArray basicAt:index put:anObject.
        tally := tally + 1.

        "grow if filled more than 70% "
        tally > (keyArray basicSize * 7 // 10) ifTrue:[
            self grow
        ].

        ^ anObject
    ]
!

keys
    "return a collection containing all keys of the receiver"

    ^ keyArray select:[:key | key notNil]
! !

!Dictionary methodsFor:'adding & removing'!

add:anAssociation
    "add the argument, anAssociation to the receiver"

    self at:(anAssociation key) put:(anAssociation value).
    ^ anAssociation
!

remove:oldObject ifAbsent:aBlock
    "remove oldObject from the collection and return it.
     If it was not in the collection return the value of aBlock."

    self shouldNotImplement
!

removeAssociation:assoc
    "remove the association from the collection.
     If it was not in the collection report an error"

    self removeKey:assoc key
!

removeKey:aKey
    "remove the association under aKey from the collection.
     If it was not in the collection report an error"

    |index 
     next  "{ Class:SmallInteger }" |

    aKey isNil ifTrue:[
        self error:'nil is not allowed as key'
    ] ifFalse:[
        index := self findKey:aKey ifAbsent:[0].
        (index == 0) ifTrue:[^ self errorNotFound].
        valueArray basicAt:index put:nil.
        keyArray basicAt:index put:nil.
        tally := tally - 1.
        tally == 0 ifTrue:[
            self setTally:0
        ] ifFalse:[
            index == keyArray basicSize ifTrue:[
                next := 1
            ] ifFalse:[
                next := index + 1.
            ].
            "redundant check to save a send sometimes"
            (keyArray basicAt:next) notNil ifTrue:[
                self rehashFrom:next.
            ]
        ]
    ]
!

removeKey:aKey ifAbsent:aBlock
    "remove the association under aKey from the collection.
     If it was not in the collection return result from evaluating aBlock"

    |index 
     next  "{ Class:SmallInteger }" |

    aKey isNil ifTrue:[
        self error:'nil is not allowed as key'
    ] ifFalse:[
        index := self findKey:aKey ifAbsent:[0].
        index == 0 ifTrue:[^ aBlock value].
        valueArray basicAt:index put:nil.
        keyArray basicAt:index put:nil.
        tally := tally - 1.
        tally == 0 ifTrue:[
            self setTally:0
        ] ifFalse:[
            index == keyArray basicSize ifTrue:[
                next := 1
            ] ifFalse:[
                next := index + 1.
            ].
            "redundant check to save a send sometimes"
            (keyArray basicAt:next) notNil ifTrue:[
                self rehashFrom:next.
            ]
        ]
    ]
! !

!Dictionary methodsFor:'enumeration'!

allKeysDo:aBlock
    "perform the block for all keys in the collection."

    keyArray nonNilElementsDo:aBlock
!

associationsDo:aBlock
    "perform the block for all associations in the collection."

    |key|

    tally == 0 ifTrue:[^ self].
    1 to:(keyArray basicSize) do:[:index |
        key := keyArray basicAt:index.
        key notNil ifTrue:[
            aBlock value:(Association key:key value:(valueArray basicAt:index))
        ]
    ]
!

do:aBlock
    "perform the block for all values in the collection."

    |index "{ Class:SmallInteger }" |

    tally == 0 ifTrue:[^ self].
    index := 1.
    keyArray do:[:key |
        key notNil ifTrue:[
            aBlock value:(valueArray basicAt:index)
        ].
        index := index + 1
    ]
!

collect:aBlock
    "for each element in the receiver, evaluate the argument, aBlock
     and return a Bag with the results"

    |newCollection|

    newCollection := Bag new.
    self do:[:each |
        newCollection add:each
    ].
    ^ newCollection
!

select:aBlock
    "return a new collection with all elements from the receiver, for which
     the argument aBlock evaluates to true"

    |newCollection|

    newCollection := self species new.
    self associationsDo:[:assoc |
        (aBlock value:(assoc value)) ifTrue:[
            newCollection add:assoc
        ]
    ].
    ^ newCollection
! !

!Dictionary methodsFor:'private'!

goodSizeFor:arg
    "return a good array size for the given argument.
     Returns the next prime after arg"

    arg <= 7 ifTrue:[^ 7].
    arg <= 16384 ifTrue:[
           "2 4 8  16 32 64 128 256 512 1024 2048 4096 8192 16384"
        ^ #(7 7 11 17 37 67 131 257 521 1031 2053 4099 8209 16411) at:(arg highBit)
    ].
    ^ arg bitOr:1
!

setTally:count
    "initialize the contents array (for at least count slots)
     and set tally to zero.
     The size is increased to the next prime for better hashing behavior."

    |n|

    n := self goodSizeFor:count.
    valueArray := Array new:n.
    keyArray := Array new:n.
    tally := 0
!

findKeyOrNil:key  
    "Look for the key in the receiver.  If it is found, return
     the index of the association containing the key, otherwise
     return the index of the first unused slot. Grow the receiver,
     if key was not found, and no unused slots where present"

    |index  "{ Class:SmallInteger }"
     length "{ Class:SmallInteger }"
     startIndex
     probe|

    length := keyArray basicSize.
    startIndex := key hash \\ length + 1.

    index := startIndex.
    [true] whileTrue:[
        probe := keyArray basicAt:index.
        (probe isNil or: [key = probe]) ifTrue:[^ index].

        index == length ifTrue:[
            index := 1
        ] ifFalse:[
            index := index + 1
        ].
        index == startIndex ifTrue:[^ self grow findKeyOrNil:key]
    ]
!

findKey:key ifAbsent:aBlock 
    "Look for the key in the receiver.  If it is found, return
     the index of the association containing the key, otherwise
     return the value of evaluating aBlock."

    |index  "{ Class:SmallInteger }"
     length "{ Class:SmallInteger }"
     startIndex
     probe|

    length := keyArray basicSize.
    length < 10 ifTrue:[
        "assuming, that for small dictionaries the overhead of hashing
         is large ... maybe that proves wrong (if overhead of comparing
         is high)"
        index := keyArray indexOf:key.
        index == 0 ifTrue:[
            ^ aBlock value
        ].
        ^ index
    ].

    startIndex := key hash \\ length + 1.

    index := startIndex.
    [true] whileTrue:[
        probe := (keyArray basicAt:index).
        key = probe ifTrue:[^ index].

        index == length ifTrue:[
            index := 1
        ] ifFalse:[
            index := index + 1
        ].
        ((probe isNil) or:[index == startIndex]) ifTrue:[
            ^ aBlock value
        ]
    ]
!

grow
    "change the number of element slots of the collection to a useful
     new size"

    self grow:(keyArray basicSize * 2)
!

grow:newSize
    "grow the receiver to make space for at least newSize elements.
     To do this, we have to rehash into the new arrays.
     (which is done by re-adding all elements to a new, empty key/value array pair)."

    |oldKeys oldValues
     index "{ Class:SmallInteger }" |

    oldKeys := keyArray.
    oldValues := valueArray.

    self setTally:newSize.

    index := 1.
    oldKeys do:[:aKey |
        aKey notNil ifTrue:[
            self at:aKey put:(oldValues basicAt:index)
        ].
        index := index + 1
    ]
!

rehash
    "rehash contents - is done by re-adding all elements to a new, empty key/value array pair)."

    | oldKeyArray oldValueArray n key 
      newIndex index |

    oldKeyArray := keyArray.
    oldValueArray := valueArray.

    n := keyArray size.
    valueArray := Array new:n.
    keyArray := Array new:n.

    index := 1.
    oldKeyArray do:[:key |
        key notNil ifTrue:[
            newIndex := self findKeyOrNil:key.
            keyArray basicAt:newIndex put:key.
            valueArray basicAt:newIndex put:(oldValueArray basicAt:index).
        ].
	index := index + 1
    ]
!

rehashFrom:startIndex
    "rehash elements starting at index - after a remove"

    |key i length
     index "{ Class:SmallInteger }" |

    length := keyArray basicSize.
    index := startIndex.
    key := keyArray basicAt:index.
    [key notNil] whileTrue:[
        i := self findKeyOrNil:key.
        i == index ifTrue:[
            ^ self
        ].
        keyArray basicAt:i put:key.
        valueArray basicAt:i put:(valueArray basicAt:index).
        keyArray basicAt:index put:nil.
        valueArray basicAt:index put:nil.

        index == length ifTrue:[
            index := 1
        ] ifFalse:[
            index := index + 1.
        ].
        key := keyArray basicAt:index.
    ]
! !

!Dictionary methodsFor:'printing & storing'!

stringWith:aSelector
    "common code for printString & displayString"

    |thisString string noneYet|

    string := (self class name) , '('.
    noneYet := true.
    self associationsDo:[:element |
        thisString := element perform:aSelector.
        noneYet ifTrue:[noneYet := false]
               ifFalse:[thisString := ' ' , thisString].
        string := string , thisString
    ].
    string := string , ')'.
    ^string
!

printString
    ^ self stringWith:#printString
!

displayString
    ^ self stringWith:#displayString
! !

!Dictionary methodsFor:'inspecting'!

inspect
    "redefined to launch a DictionaryInspector on the receiver
     (instead of the default InspectorView)."

    DictionaryInspectorView isNil ifTrue:[
        super inspect
    ] ifFalse:[
        DictionaryInspectorView openOn:self
    ]
! !

!Dictionary methodsFor:'error handling'!

errorKeyNotFound
    "report an error that an element was not found in the collection"

    self error:'the key is not in the collection'
! !