Dict.st
author claus
Sat, 11 Dec 1993 01:46:55 +0100
changeset 12 8e03bd717355
parent 10 4f1f9a91e406
child 38 454b1b94a48e
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1991 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.
"

Set subclass:#Dictionary
         instanceVariableNames:'valueArray'
         classVariableNames:''
         poolDictionaries:''
         category:'Collections-Unordered'
!

Dictionary comment:'

COPYRIGHT (c) 1991 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 array.

$Header: /cvs/stx/stx/libbasic/Attic/Dict.st,v 1.6 1993-12-11 00:45:55 claus Exp $

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

!Dictionary methodsFor:'testing'!

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

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

includes:aValue
    "return true, if the argument, aValue is stoerd in the dictionary,
     This is a slow search, since there is no fast reverse mapping"

    ^ valueArray includes:aValue
! !

!Dictionary methodsFor:'accessing'!

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

    |index|

    aKey isNil ifTrue:[
        self errorInvalidKey
    ] ifFalse:[
        index := self find:aKey ifAbsent:[0].
        index == 0 ifTrue:[^ self errorKeyNotFound].
        ^ valueArray basicAt:index
    ]
!

at:aKey ifAbsent:exceptionBlock
    "return the element indexed by aKey - 
     return result of exceptionBlock if no element is stured under aKey"

    |index|

    aKey isNil ifTrue:[
        self errorInvalidKey
    ] ifFalse:[
        index := self find:aKey ifAbsent:[0].
        index == 0 ifTrue:[^ exceptionBlock value].
        ^ valueArray basicAt:index
    ]
!

associationAt:aKey
    "return an association consisting of aKey and the element indexed 
     by aKey - 
     report an error, if no element is stored under aKey"

    ^ aKey -> (self at:aKey)
!

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

    |index element|

    aKey isNil ifTrue:[
        self errorInvalidKey
    ] 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.

        self fullCheck.

        ^ anObject
    ]
!

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

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

keyAtValue:aValue
    "return the key whose value equals the argument, nil if none found.
     This is a slow access, since there is no fast reverse mapping"

    ^ self keyAtValue:aValue ifAbsent:[nil]
!

keyAtValue:aValue ifAbsent:exceptionBlock
    "return the key whose value equals the argument, the value of the 
     exceptionBlock if none is found..
     This is a slow access, since there is no fast reverse mapping"

    keyArray keysAndValuesDo:[:index :aKey |
        aKey notNil ifTrue:[
            (valueArray at:index) = aValue ifTrue:[^ aKey].
        ].
    ].
    ^ exceptionBlock value
! !

!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"

    ^ self removeKey:aKey ifAbsent:[^ self errorNotFound]
!

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 "{ Class:SmallInteger }"
     next  "{ Class:SmallInteger }" |

    aKey isNil ifTrue:[
        self errorInvalidKey
    ] ifFalse:[
        index := self find: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
    ]
!

keysAndValuesDo:aTwoArgBlock
    "evaluate the argument, aBlock for every element in the collection,
     passing both key and element as arguments."

    |index "{ Class:SmallInteger }" |

    tally == 0 ifTrue:[^ self].
    index := 1.
    keyArray do:[:key |
        key notNil ifTrue:[
            aTwoArgBlock value:key 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:(aBlock value: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'!

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.
    keyArray := self keyContainerOfSize:n.
    valueArray := Array new:n.
    tally := 0
!

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)."

    |oldKeyArray oldValueArray key n
     oldSize "{ Class:SmallInteger }" 
     newIndex "{ Class:SmallInteger }" |

    oldKeyArray := keyArray.
    oldValueArray := valueArray.

    n := self goodSizeFor:newSize.
    keyArray := self keyContainerOfSize:n.
    valueArray := Array new:n.

    oldSize := oldKeyArray size.
    1 to:oldSize do:[:index |
        key := oldKeyArray basicAt:index.
        key notNil ifTrue:[
            newIndex := self findNil:key.
            keyArray basicAt:newIndex put:key.
            valueArray basicAt:newIndex put:(oldValueArray basicAt:index).
        ]
    ]
!

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

    | oldKeyArray oldValueArray key 
      n        "{ Class:SmallInteger }"
      newIndex "{ Class:SmallInteger }" |

    oldKeyArray := keyArray.
    oldValueArray := valueArray.

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

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

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 findNil: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
    ]
! !