IdDict.st
author claus
Tue, 08 Aug 1995 02:49:43 +0200
changeset 375 e5019c22f40e
parent 362 4131e87e79ec
child 379 5b5a130ccd09
permissions -rw-r--r--
.

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

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

IdentityDictionary comment:'
COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libbasic/Attic/IdDict.st,v 1.13 1995-08-08 00:47:13 claus Exp $
'!

!IdentityDictionary class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 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/Attic/IdDict.st,v 1.13 1995-08-08 00:47:13 claus Exp $
"
!

documentation
"
    same as a Dictionary but key must be identical - not just equal.
    Since compare is on identical keys (using ==), hashing is also done via
    #identityHash instead of #hash.
    IdentityDictionaries are especially useful, when symbols are used as keys.
"
! !

!IdentityDictionary methodsFor:'testing'!

includesValue:aValue
    "return true, if the argument, aValue is stored in the dictionary,
     Redefined to use identity compare, NOT equality compare"

    ^ (valueArray identityIndexOf:aValue) ~~ 0
!

occurrencesOf:anObject
    "count & return how often anObject is stored in the dictionary.
     This counts values - not keys.
     Redefined to use identity compare, NOT equality compare."

    |cnt|

    cnt := 0.
    valueArray do:[:element |
       element == anObject ifTrue:[cnt := cnt + 1]
    ].
    ^ cnt
! !

!IdentityDictionary methodsFor:'private'!

compareSame:element1 with:element2
    ^ element1 == element2
!

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.
    index := key identityHash.
    index := index \\ length + 1.
    startIndex := index.

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

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

findNil:key
    "Look for the next slot usable for key.  This method assumes that
     key is not already in the receiver - used only while growing/rehashing"

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

    length := keyArray basicSize.
    index := key identityHash.
    index := index \\ length + 1.

    [(keyArray basicAt:index) notNil] whileTrue:[
	index == length ifTrue:[
	    index := 1
	] ifFalse:[
	    index := index + 1
	].
	"notice: no check for no nil found - we must find one since
	 this is only called after growing"
    ].
    ^ index
! 

find: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)"
	^ keyArray identityIndexOf:key ifAbsent:aBlock.
    ].

    index := key identityHash.
    index := index \\ length + 1.
    startIndex := index.

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

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

emptyCollectionForKeys
    "return an empty collection used for keys.
     Made a separate method to allow redefinition for different kind of
     containers in subclasses"

    ^ IdentitySet new:(self size)
! !