Dictionary.st
author claus
Fri, 11 Aug 1995 05:05:04 +0200
changeset 384 cc3d110ea879
parent 379 5b5a130ccd09
child 399 c15cfaf3ed4d
permissions -rw-r--r--
.

"
 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

$Header: /cvs/stx/stx/libbasic/Dictionary.st,v 1.26 1995-08-11 03:00:04 claus Exp $
'!

!Dictionary class methodsFor:'documentation'!

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

version
"
$Header: /cvs/stx/stx/libbasic/Dictionary.st,v 1.26 1995-08-11 03:00:04 claus Exp $
"
!

documentation
"
    a Dictionary is (conceptionally) a set of Associations storing key-value pairs.
    (The implementation uses two arrays to store the keys and values separately.)
    Searching for an element is done using a hash into the key array.
    Another way of looking at a dictionary is as a array which uses
    arbitrary access keys (i.e. not just integers as arrays do).

    Since the keys are unordered, no internal element order is defined
    (i.e. enumerating them may return elements in any order - even changing
     over time).

    Many methods for searching and hashing are inherited from Set.

    Instance variables:

	keyArray        <Array>         (from Set) the keys
	valueArray      <Array>         the values ('valueArray at:index' corresponds
					to the value stored under 'keyArray at:index')

    Performance hints: 
      since the dictionary does not really store associations internally,
      it is less efficient, to store/retrieve associations. The reason is
      that because these assocs are created temporarily in some extract methods. 
      I.e. 'at:key put:value' is faster than 'add:anAssoc' 
      and 'keysAndValuesDo:' is faster than 'associationsDo:' etc.

      If only symbols or smallIntegers are used as keys, use IdentityDictionaries
      for slightly better performance, since both hashing and comparison is faster.

      If you have a rough idea how big the dictionary 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 are avoided when associations
      are added.

    See also: Set, IdentityDictionary, IdentitySet, WeakIdentitySet and
	      WeakIdentityDictionary
"
! !

!Dictionary class methodsFor:'instance creation'!

withKeysAndValues:anArray
    "return a new instance where keys and values are taken from alternating
     elements of anArray"

    |newDict sz "{ Class: SmallInteger }"|

    sz := anArray size.
    newDict := self new:(sz // 2).
    1 to:sz by:2 do:[:i |
	newDict at:(anArray at:i) put:(anArray at:i+1)
    ].
    ^ newDict

    "
     Dictionary withKeysAndValues:#('one' 1 'two' 2 'three' 3 'four' 4)
    "
!

withKeys:keyArray andValues:valueArray
    "return a new instance where keys and values are taken from
     the argumentArrays."

    |newDict sz "{ Class: SmallInteger }"|

    sz := keyArray size.
    newDict := self new:sz.
    keyArray with:valueArray do:[:key :value |
	newDict at:key put:value
    ].
    ^ newDict

    "
     Dictionary withKeys:#('one' 'two' 'three' 'four')
	       andValues:#(1 2 3 4)
    "
! !

!Dictionary methodsFor:'inspecting'!

inspectorClass
    "redefined to use DictionaryInspector
     (instead of the default Inspector)."

    ^ DictionaryInspectorView
! !

!Dictionary methodsFor:'testing'!

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

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

includesValue:aValue
    "return true, if the argument, aValue is stored in the dictionary,
     i.e. if there is an associaten, with aValue as value.
     This is a slow search, since there is no fast reverse mapping;
     the values have to be all scanned without any hashing.
     You need a special collection (or two Dictionaries) to get this
     reverse mapping fast."

    ^ valueArray includes:aValue
!

includes:anObject
"/ OLD:
"/    "return true, if there is an association in the receiver with the
"/     same key as the argument, anObject.
"/     NOTICE: in contrast to #includesAssociation:, this compares only the key."
"/
"/    ^ self includesKey:(anObject key)

"/ NEW:
    "return true, if the argument, aValue is stored in the dictionary,
     i.e. if there is an associaten, with aValue as value.
     This is a slow search, since there is no fast reverse mapping;
     the values have to be all scanned without any hashing.
     You need a special collection (or two Dictionaries) to get this
     reverse mapping fast."

    ^ self includesValue:anObject
!

includesAssociation:anAssociation
    "return true, if there is an association in the receiver with the
     same key and value as the argument, anAssociation.
     NOTICE: in contrast to #includes:, this compares both key and value."

    |val|

    val := self at:(anAssociation key) ifAbsent:[^ false].
    ^ (self compareSame:val with:anAssociation) value
!

occurrencesOf:anObject
    "count & return how often anObject is stored in the dictionary.
     This counts values - not keys."

    ^ valueArray occurrencesOf:anObject
! !

!Dictionary methodsFor:'accessing'!

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

    |index|

    aKey isNil ifTrue:[
	"/ nil is not allowed as key
	^ self errorInvalidKey:aKey
    ].

    "/
    "/ I could have written:
    "/ index := self find:aKey ifAbsent:[^ self errorKeyNotFound:aKey]
    "/ but the code below is slighlty more efficient, since it avoids
    "/ a block creation ([0] is very cheap) - thus speeding up the good case.
 
    index := self find:aKey ifAbsent:0.
    index == 0 ifTrue:[
	"no such key"
	^ self errorKeyNotFound:aKey
    ].
    ^ valueArray basicAt:index
!

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

    |index|

    aKey isNil ifTrue:[
	"/ nil is not allowed as key
	"/
	"/ previous versions of ST/X raised an error
	"/ here. However, there seem to exist applications
	"/ which depend on getting the exceptionBlocks value
	"/ in this case ... well ...
	"/ ^ self errorInvalidKey:aKey
	^ exceptionBlock value
    ].

    "/ I could have written:
    "/ index := self find:aKey ifAbsent:[^ exceptionBlock value]
    "/ but the code below is slighlty more efficient, since it avoids
    "/ a block creation ([0] is very cheap) - thus speeding up the good case.

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

associationAt:aKey ifAbsent:exceptionBlock
    "return an association consisting of aKey and the element indexed by aKey - 
     return result of exceptionBlock if no element is stored under aKey"

    ^ aKey -> (self at:aKey ifAbsent:[^ exceptionBlock value])
!

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

    |index|

    aKey isNil ifTrue:[
	"nil is not allowed as key"
	self errorInvalidKey:aKey
    ] ifFalse:[
	index := self findKeyOrNil:aKey.
	(valueArray basicAt:index) 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"

    |keySet|

    keySet := self emptyCollectionForKeys.
    keyArray do:[:key | 
	(key notNil and:[key ~~ DeletedEntry]) ifTrue:[
	    keySet add:key
	]
    ].
    ^ keySet
!

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

"old:
kk: this fails if the receiver contains nils
    ^ valueArray asBag
new:
"
    |aCollection|

    aCollection := OrderedCollection new:valueArray size.
    self do:[:value| aCollection add:value].
    ^ aCollection
!

associations
    "return an ordered collection containing the receivers associations."

    |coll|

    coll := OrderedCollection new:(keyArray size).
    self associationsDo:[:assoc | coll add:assoc].
    ^ coll
!

keyAtValue:aValue
    "return the key whose value is identical (i.e. using #== for compare)
     to the argument, nil if none found.
     This is a slow access, since there is no fast reverse mapping.
     NOTICE:
	The value is searched using identity compare; 
	use #keyAtEqualValue: to compare for equality."

    ^ self keyAtValue:aValue ifAbsent:[nil]
!

keyAtValue:aValue ifAbsent:exceptionBlock
    "return the key whose value is identical (i.e. using #== for compare) 
     to the argument, if not found, return the value of exceptionBlock.
     This is a slow access, since there is no fast reverse mapping.
     NOTICE:
	The value is searched using identity compare; 
	use #keyAtEqualValue:ifAbsent: to compare for equality."

    |idx|

    idx := valueArray identityIndexOf:aValue.
    idx ~~ 0 ifTrue:[
	^ keyArray at:idx
    ].

"/  keyArray keysAndValuesDo:[:index :aKey |
"/      (aKey notNil and:[aKey ~~ DeletedEntry]) ifTrue:[
"/          (valueArray at:index) == aValue ifTrue:[^ aKey].  
"/      ].
"/  ].

    ^ exceptionBlock value
!

keyAtEqualValue:aValue
    "return the key whose value is equal (i.e. using #= for compare)
     to the argument, nil if none found.
     This is a slow access, since there is no fast reverse mapping.
     NOTICE:
	The value is searched using equality compare; 
	use #keyAtValue: to compare for identity."

    ^ self keyAtEqualValue:aValue ifAbsent:[nil]
!

keyAtEqualValue:aValue ifAbsent:exceptionBlock
    "return the key whose value is equal (i.e. using #= for compare) 
     to the argument, if not found, return the value of exceptionBlock.
     This is a slow access, since there is no fast reverse mapping.
     NOTICE:
	The value is searched using equality compare; 
	use #keyAtValue:ifAbsent: to compare for identity."

    |idx|

    idx := valueArray indexOf:aValue.
    idx ~~ 0 ifTrue:[
	^ keyArray at:idx
    ].

"/  keyArray keysAndValuesDo:[:index :aKey |
"/      (aKey notNil and:[aKey ~~ DeletedEntry]) 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
!

declare:key from:aDictionary
    "if the receiver does not include an association for key,
     take the association from aDictionary and add it to the receiver.
     If aDictionary does not contain such an association, use nil
     as the value of the new dictionary."

    |value|

    (self includesKey:key) ifFalse:[
	value := aDictionary at:key ifAbsent:nil.
	self at:key put:value.
    ]
!

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 errorKeyNotFound:aKey]
!

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:aKey
    ] ifFalse:[
"/      
"/       I could have written:
"/          index := self find:aKey ifAbsent:[^ aBlock value]
"/       but the code below is slighlty more efficient, since it avoids
"/       a block creation ([0] is very cheap) - thus speeding up the good case.
"/      
	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.
	    ].
	    (keyArray basicAt:next) notNil ifTrue:[
		keyArray basicAt:index put:DeletedEntry
	    ].
	    self emptyCheck
	]
    ]
!

removeValue:aValue ifAbsent:aBlock
    "remove (first) the association to aValue from the collection.
     If it was not in the collection return result from evaluating aBlock.
     The value is searched using identity compare."

    |next  "{ Class:SmallInteger }" |

    aValue notNil ifTrue:[
	keyArray keysAndValuesDo:[:index :aKey |
	    (aKey notNil and:[aKey ~~ DeletedEntry]) ifTrue:[
		(self compareSame:(valueArray at:index) with:aValue) ifTrue:[  
		    "found it"
		    valueArray basicAt:index put:nil.
		    keyArray basicAt:index put:nil.
		    tally := tally - 1.
		    tally == 0 ifTrue:[
			self setTally:0.
			^ self
		    ].
		    index == keyArray basicSize ifTrue:[
			next := 1
		    ] ifFalse:[
			next := index + 1.
		    ].
		    (keyArray basicAt:next) notNil ifTrue:[
			keyArray basicAt:index put:DeletedEntry
		    ].
		    self emptyCheck.
		    ^ self
		]
	    ]
	]
    ].
    ^ aBlock value
! !

!Dictionary methodsFor:'copying'!

postCopy
    "have to copy the valueArray too"

    super postCopy.
    valueArray := valueArray shallowCopy
! !

!Dictionary methodsFor:'enumerating'!

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

    ^ super do:aBlock
!

allKeysDo:aBlock
    "perform the block for all keys in the collection.
     Obsolete: use keysDo: for ST-80 compatibility."

    ^ super do:aBlock
!

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

    |key n "{ Class: SmallInteger }"|

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

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

    |key n "{ Class: SmallInteger }"|

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

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

    |key n "{ Class: SmallInteger }"|

    tally == 0 ifTrue:[^ self].
    n := keyArray basicSize.
    1 to:n do:[:index |
	key := keyArray basicAt:index.
	(key notNil and:[key ~~ DeletedEntry]) ifTrue:[
	    aTwoArgBlock value:key value:(valueArray basicAt:index)
	].
    ]
!

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. The block gets the individual values
     as its single argument."

    |newCollection|

    newCollection := self species new.
    self keysAndValuesDo:[:key :value |
	(aBlock value:value) ifTrue:[
	    newCollection at:key put:value
	]
    ].
    ^ newCollection

    "
     |d|

     d := Dictionary new.
     d at:#foo put:#bar.
     d at:#bar put:#baz.
     d at:#baz put:#foo.

     d select:[:el | el startsWith:'b'].
    "
! !

!Dictionary methodsFor:'private'!

compareSame:element1 with:element2
    ^ element1 = element2
!

valueContainerOfSize:n
    "return a container for values of size n.
     Extracted to make life of weak subclasses easier ..."

    ^ Array basicNew:n
!

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 class goodSizeFrom:count.
    keyArray := self keyContainerOfSize:n.
    valueArray := self valueContainerOfSize: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)."

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

    oldKeyArray := keyArray.
    oldValueArray := valueArray.

    n := self class goodSizeFrom:newSize.
    oldSize := oldKeyArray size.
    n == oldSize ifTrue:[^ self].

    keyArray := self keyContainerOfSize:n.
    valueArray := self valueContainerOfSize:n.


    deletedEntry := DeletedEntry.
    1 to:oldSize do:[:index |
	key := oldKeyArray basicAt:index.
	(key notNil and:[key ~~ deletedEntry]) 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 := self valueContainerOfSize:n.

    1 to:n do:[:index |
	key := oldKeyArray basicAt:index.
	(key notNil and:[key ~~ DeletedEntry]) 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.
     NOTE: this method is no longer needed; 
	   the trick using DeletedEntry avoids the need to do this time 
	   consuming operation, making remove pretty fast :-)
    "

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

    length := keyArray basicSize.
    index := startIndex.
    key := keyArray basicAt:index.
    [key notNil] whileTrue:[
	key ~~ DeletedEntry ifTrue:[
	    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.
    ]
!

emptyCollectionForKeys
    ^ Set new:(self size)
! !

!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
    "return a string for printing"

    ^ self stringWith:#printString
!

displayString
    "return a string for displaying"

    ^ self stringWith:#displayString
!

storeOn:aStream
    "output a printed representation (which can be re-read)
     onto the argument aStream"

    |isEmpty|

    thisContext isRecursive ifTrue:[
	Transcript showCr:'Error: storeOn: of self referencing collection.'.
	aStream nextPutAll:'#recursive'.
	^ self
    ].

    aStream nextPutAll:'('.
    aStream nextPutAll:(self class name).
    aStream nextPutAll:' new'.
    isEmpty := true.
    self keysAndValuesDo:[:key :value |
	aStream nextPutAll:' at:'.
	key storeOn:aStream.
	aStream nextPutAll:' put:'.
	value storeOn:aStream.
	aStream nextPutAll:'; '.
	isEmpty := false
    ].
    isEmpty ifFalse:[aStream nextPutAll:' yourself'].
    aStream nextPut:$)

    "
     Dictionary new storeOn:Transcript

     (Dictionary new at:1 put:'hello'; yourself) storeOn:Transcript
    "

    "
     |d|
     d := Dictionary new.
     d at:1 put:'hello'.
     d at:'hello' put:#world.
     d storeOn:Transcript
    "

    "
     |d|
     d := Dictionary new.
     d at:1 put:'hello'.
     d at:'hello' put:#world.
     d at:2 put:d.
     d storeOn:Transcript
    "
! !