KeyedCollection.st
author Claus Gittinger <cg@exept.de>
Tue, 09 Jul 2019 20:55:17 +0200
changeset 24417 03b083548da2
parent 23888 ecd7ab5136be
child 24612 1ac50ebe401a
permissions -rw-r--r--
#REFACTORING by exept class: Smalltalk class changed: #recursiveInstallAutoloadedClassesFrom:rememberIn:maxLevels:noAutoload:packageTop:showSplashInLevels: Transcript showCR:(... bindWith:...) -> Transcript showCR:... with:...

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1998 by eXept Software AG
              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.
"
"{ Package: 'stx:libbasic' }"

"{ NameSpace: Smalltalk }"

Collection subclass:#KeyedCollection
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Abstract'
!

!KeyedCollection class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1998 by eXept Software AG
              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.
"

!

documentation
"
    Abstract superclass for collections which have a key->value mapping.
    This abstract class provides functionality common to those collections,
    without knowing how the concrete class implements things. 
    Thus, all methods found here depend on some basic mechanisms 
    to be defined in the concrete class. 
    These basic methods are usually defined as #subclassResponsibility here.
    Some methods are also redefined for better performance.

    Subclasses should at least implement:
        at:ifAbsent:        - accessing elements
        removeKey:ifAbsent  - removing
        keysAndValuesDo:    - enumerating

    [author:]
        Claus Gittinger
"
! !

!KeyedCollection class methodsFor:'instance creation'!

decodeFromLiteralArray:anArray
    "create & return a new instance from information encoded in anArray."

    |dictionary
     sz "{ Class: SmallInteger }"|

    sz := anArray size.
    dictionary := self new:sz//2.
    2 to:sz by:2 do:[:idx | |key val|
        key := (anArray at:idx) decodeAsLiteralArray.
        val := (anArray at:idx+1) decodeAsLiteralArray.
        dictionary at:key put:val
    ].
    ^ dictionary

    "
     (SmallDictionary new
         at:1 put:'one';
         at:2 put:'two';
         yourself
     ) literalArrayEncoding decodeAsLiteralArray
    "

    "Created: / 17-09-2018 / 14:51:59 / Stefan Vogel"
!

withAll:aCollection
    "create a KeyedCollection from another Collection with keys"

    |newDict|

    newDict := self new:aCollection size.
    aCollection keysAndValuesDo:[:key :value |
        newDict at:key put:value.
    ].
    ^ newDict

    "
        |d|

        d := Dictionary withKeys:#(a b c d e) andValues:#(1 2 3 4 5).
        SmallDictionary withAll:d.

        SmallDictionary withAll:#('one' 'two' 'three' 'four').
    "

    "Created: / 17-03-2017 / 11:29:09 / stefan"
    "Modified (comment): / 14-09-2018 / 17:54:12 / Stefan Vogel"
!

withAssociations:aCollectionOfAssociations
    "return a new instance where associations are taken from the argument"

    |newDict|

    newDict := self new:aCollectionOfAssociations size.
    aCollectionOfAssociations do:[:assoc |
        newDict at:assoc key put:assoc value
    ].
    ^ newDict

    "
     SmallDictionary withAssociations:{ #'one'->1 .
                                   #'two'->2 .
                                   #'three'->3 .
                                   #'four'->4 }
    "

    "Created: / 16-03-2017 / 12:15:38 / stefan"
    "Modified: / 17-03-2017 / 11:30:55 / stefan"
    "Modified (comment): / 14-09-2018 / 17:45:56 / Stefan Vogel"
!

withKeyValuePairs:aCollection
    "return a new instance where keys and values are taken from 
     elements of aCollection, which are pairs (2-element SeuqenceableCollection) of key and value"

    |newDict|

    newDict := self new:(aCollection size).
    aCollection do:[:pair |
        newDict at:(pair first) put:(pair second)
    ].
    ^ newDict

    "
     SmallDictionary withKeyValuePairs:#( ('one' 1) ('two' 2) ('three' 3) ('four' 4))
    "

    "Created: / 14-09-2018 / 17:44:35 / Stefan Vogel"
!

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

    |newColl sz "{ Class: SmallInteger }"|

    sz := keyCollection size.
    newColl := self new:sz.
    1 to:sz do:[:index |
        newColl at:(keyCollection at:index) put:(valueCollection at:index).
    ].
    ^ newColl

    "Created: / 16-03-2017 / 11:06:51 / stefan"
    "Modified (format): / 16-03-2017 / 12:12:09 / stefan"
    "Modified (format): / 14-09-2018 / 17:50:05 / Stefan Vogel"
!

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

    |newDict sz "{ Class: SmallInteger }"|

    sz := aSequenceableCollection size.
    sz odd ifTrue:[
        SubscriptOutOfBoundsError
            raiseRequestWith:sz+1
            errorString:('odd number of elements - subscript (' , (sz+1) printString , ') would be out of bounds')
    ].
    newDict := self new:sz.
    1 to:sz by:2 do:[:i |
        newDict at:(aSequenceableCollection at:i) put:(aSequenceableCollection at:i+1)
    ].
    ^ newDict

    "
     SmallDictionary withKeysAndValues:#('one' 1 'two' 2 'three' 3 'four' 4)
     SmallDictionary withKeysAndValues:#('one' 1 'two' 2 'three' 3 'incomplete')
    "

    "Created: / 16-03-2017 / 12:13:27 / stefan"
    "Modified: / 17-03-2017 / 11:32:42 / stefan"
    "Modified (comment): / 04-10-2018 / 10:09:46 / Stefan Vogel"
! !

!KeyedCollection class methodsFor:'queries'!

isAbstract
    "Return if this class is an abstract class.
     True is returned for KeyedCollection here; false for subclasses.
     Abstract subclasses must redefine this again."

    ^ self == KeyedCollection
! !

!KeyedCollection methodsFor:'accessing'!

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

    ^ self associationAt:aKey ifAbsent:[self errorKeyNotFound:aKey]

    "Modified: / 16-03-2017 / 17:19:52 / stefan"
!

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.
     Warning: this is a comatibility interface only, with a different semantic as
              the original ST80 implementation. The returned assoc is created on the fly,
              and not the one stored in the receiver (there are not assocs there)"

    |value|

    value := self at:aKey ifAbsent:[^ exceptionBlock value].
    ^ Association key:aKey value:value.

    "Created: / 16-03-2017 / 17:17:05 / stefan"
!

associations
    "return an ordered collection containing the receiver's associations."

    |coll|

    coll := OrderedCollection new.
    self associationsDo:[:assoc | coll add:assoc].
    ^ coll

    "Created: / 16-03-2017 / 17:30:47 / stefan"
!

at:key
    "return the value stored under akey.
     Raise an error if not found"

    ^ self at:key ifAbsent:[self errorKeyNotFound:key].

    "Modified: / 19.6.1998 / 00:48:27 / cg"
!

at:key ifAbsent:exceptionBlock
    "return the value stored under akey.
     Return the value from evaluating exceptionBlock if not found"

    ^ self subclassResponsibility

    "Created: / 19.6.1998 / 00:48:23 / cg"
!

at:aKey ifAbsent:default update:aBlock
    "update the element stored under aKey with the result from
     evaluating aBlock with the previous stored value as argument, or with default,
     if there was no such key initially.
     Return the new value stored."

    ^ self at:aKey put:(aBlock value:(self at:aKey ifAbsent:default))

    "Created: / 16-03-2017 / 17:28:15 / stefan"
!

at:aKey ifAbsentPut:valueBlock
    "return the element indexed by aKey if present,
     if not present, store the result of evaluating valueBlock
     under aKey and return it.
     WARNING: do not add elements while iterating over the receiver.
              Iterate over a copy to do this."

    ^ self at:aKey ifAbsent:[self at:aKey put:valueBlock value].

    "Created: / 16-03-2017 / 17:23:07 / stefan"
!

at:aKey ifPresent:aBlock
    "try to retrieve the value stored at aKey.
     If there is nothing stored under this key, do nothing.
     Otherwise, evaluate aBlock, passing the retrieved value as argument."

    |v|

    v := self at:aKey ifAbsent:[^ nil].
    ^ aBlock value:v.

    "Created: / 16-03-2017 / 17:11:27 / stefan"
!

at:aKey put:anObject
    "add the argument anObject under key, aKey to the receiver.
     Return anObject (sigh).
     WARNING: do not add elements while iterating over the receiver.
              Iterate over a copy to do this."

    ^ self subclassResponsibility

    "Created: / 16-03-2017 / 17:33:12 / stefan"
!

at:aKey put:anObject ifPresent:aBlock
    "if the receiver contains an element stored under aKey,
     retrieve it and evaluate aBlock passing the element as argument,
     return the block's value.
     If not, store aValue under the key.
     Use this with an error-reporting block, to ensure that no keys are reused"

    |value isAbsent|

    value := self at:aKey ifAbsentPut:[isAbsent := true. anObject].
    isAbsent notNil ifTrue:[
        ^ value.
    ].

    ^ aBlock value:value.

    "Created: / 16-03-2017 / 17:38:00 / stefan"
    "Modified: / 17-03-2017 / 11:37:26 / stefan"
    "Modified (comment): / 13-03-2019 / 10:26:05 / Claus Gittinger"
!

at:aKey update:aBlock
    "update the element stored under aKey with the result from
     evaluating aBlock with the previous stored value as argument.
     Report an error if there was no such key initially.
     Return the new value stored."

    ^ self at:aKey put:(aBlock value:(self at:aKey))

    "Created: / 16-03-2017 / 17:29:22 / stefan"
!

keyAtEqualValue:value
    "return the key under which value is stored.
     Raise an error if not found.
     This is a slow access, since the receiver is searched sequentially.
     NOTICE:
        The value is searched using equality compare"

    ^ self keyAtEqualValue:value ifAbsent:[self errorValueNotFound:value].

    "Created: / 07-02-2017 / 11:11:41 / cg"
!

keyAtEqualValue:value ifAbsent:exceptionBlock
    "return the key under which value is stored.
     If not found, return the value from evaluating exceptionBlock.
     This is a slow access, since the receiver is searched sequentially.
     NOTICE:
        The value is searched using equality compare"

    self keysAndValuesDo:[:elKey :elValue |
        value = elValue ifTrue:[^ elKey]
    ].
    ^ exceptionBlock value

    "Created: / 07-02-2017 / 11:12:03 / cg"
!

keyAtIdenticalValue:value
    "return the key under which value is stored.
     Raise an error if not found.
     This is a slow access, since the receiver is searched sequentially.
     NOTICE:
        The value is searched using identity compare"

    ^ self keyAtIdenticalValue:value ifAbsent:[self errorValueNotFound:value].

    "Created: / 07-02-2017 / 11:12:23 / cg"
!

keyAtIdenticalValue:value ifAbsent:exceptionBlock
    "return the key under which value is stored.
     If not found, return the value from evaluating exceptionBlock.
     This is a slow access, since the receiver is searched sequentially.
     NOTICE:
        The value is searched using identity compare"

    self keysAndValuesDo:[:elKey :elValue |
        value == elValue ifTrue:[^ elKey]
    ].
    ^ exceptionBlock value

    "Created: / 07-02-2017 / 11:12:46 / cg"
!

keyAtValue:value
    "return the key under which value is stored.
     Raise an error if not found.
     This is a slow access, since the receiver is searched sequentially.
     NOTICE:
        The value is searched using equality compare"


    ^ self keyAtEqualValue:value.

    "Created: / 19-06-1998 / 00:49:16 / cg"
    "Modified (comment): / 07-02-2017 / 11:13:29 / cg"
    "Modified (comment): / 16-03-2017 / 18:00:28 / stefan"
!

keyAtValue:value ifAbsent:exceptionBlock
    "return the key under which value is stored.
     If not found, return the value from evaluating exceptionBlock.
     This is a slow access, since the receiver is searched sequentially.
     NOTICE:
        The value is searched using equality compare"


    ^ self keyAtEqualValue:value ifAbsent:exceptionBlock.

    "Created: / 19-06-1998 / 00:50:34 / cg"
    "Modified: / 07-02-2017 / 11:13:20 / cg"
    "Modified (comment): / 16-03-2017 / 18:00:37 / stefan"
!

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

    |keyCollection|

    keyCollection := OrderedCollection new.
    self keysDo:[:aKey |
        keyCollection add:aKey
    ].
    ^ keyCollection

    "Modified: / 19.6.1998 / 00:48:27 / cg"
    "Created: / 19.6.1998 / 00:51:49 / cg"
! !

!KeyedCollection methodsFor:'adding'!

addAll:aCollection
    "ANSI 5.7.2.1:
     Message:  addAll: dictionary
      Synopsis
        Store the elements of dictionary in the receiver at the
        corresponding keys from dictionary.
      Definition: <abstractDictionary>
        This message is equivalent to repeatedly sending the #at:put:
        message to the receiver with each of the keys and elements in
        dictionary in turn.  If a key in dictionary is key equivalent
        to a key in the receiver, the associated element in dictionary
        replaces the element in the receiver.

     Returns the argument, aCollection (sigh).

     WARNING: do not add elements while iterating over the receiver.
              Iterate over a copy to do this."


    self ~~ aCollection ifTrue:[
        aCollection isSequenceable ifTrue:[
            aCollection do:[:eachPair |
                self at:eachPair key put:eachPair value.
            ].
        ] ifFalse:[
            aCollection keysAndValuesDo:[:eachKey :eachValue |
                self at:eachKey put:eachValue.
            ]
        ].
    ].
    ^ aCollection

    "
     |d1 d2|

     d1 := Dictionary new.
     d1 at:1 put:'one'.
     d1 at:2 put:'two'.
     d2 := Dictionary new.
     d2 at:3 put:'three'.
     d2 at:4 put:'four'.
     d1 addAll:d2.
     d1.
    "

    "Created: / 14-09-2018 / 16:41:49 / Stefan Vogel"
!

declareAllFrom:aDictionaryOrNil
    "merge all key-value pairs from aDictionary into the receiver.
     Values present in the arg will always end up in the receiver;
     i.e. a value coming from the argument is already in the receiver,
     the value from aDictionaryOrNil is stored into the receiver.

     sigh:
        For compatibility with #declare:from: the behavior should be changed as following:
        If the receiver already contains a key, the existing value is retained.
        To keep the compatibility with other smalltalks, the semantics of this remains
        as is, and #declareAllNewFrom: was added for convenience.
        See #declareAllNewFrom: which does exactly what this name implies."

    (aDictionaryOrNil notNil and:[self ~~ aDictionaryOrNil]) ifTrue:[
        aDictionaryOrNil keysAndValuesDo:[:key :value |
            self at:key put:value.
        ].
    ]

    "Created: / 14-09-2018 / 16:46:38 / Stefan Vogel"
!

declareAllNewFrom:aDictionaryOrNil
    "merge all new key-value pairs from aDictionary into the receiver
     i.e. If the receiver already contains a key, the existing value is retained.
     See also #declareAllFrom:"

    (aDictionaryOrNil notNil and:[self ~~ aDictionaryOrNil]) ifTrue:[
        aDictionaryOrNil keysAndValuesDo:[:key :value |
            (self includesKey:key) ifFalse:[
                self at:key put:value.
            ].
        ]
    ]

    "Created: / 14-09-2018 / 16:56:36 / Stefan Vogel"
! !

!KeyedCollection methodsFor:'converting'!

literalArrayEncoding
    |literalArray idx|

    literalArray := Array new:(self size * 2)+1.
    literalArray at:1 put:self class name.
    idx := 2.
    self keysAndValuesDo:[:eachKey :eachValue |
        literalArray
            at:idx   put:eachKey literalArrayEncoding;
            at:idx+1 put:eachValue literalArrayEncoding.
        idx := idx + 2.
    ].
    ^ literalArray

    "
      |dict|

      dict := SmallDictionary new.
      dict at:1 put:'bla'.
      dict at:'fasel' put:#[1 2 3 4].
      dict literalArrayEncoding
    "

    "Created: / 17-09-2018 / 14:49:52 / Stefan Vogel"
! !

!KeyedCollection methodsFor:'enumerating'!

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

     See also:
        #do:              (which passes values to its block)
        #keysDo:          (which passes only keys to its block)
        #keysAndValuesDo: (which passes keys&values)

     This is much like #keysAndValuesDo:, but aBlock gets the
     key and value as a single association argument.
     #keysAndValuesDo: and is a bit faster therefore (no intermediate objects).

     WARNING: do not add/remove elements while iterating over the receiver.
              Iterate over a copy to do this."

    self keysAndValuesDo:[:eachKey :eachValue|
        aBlock value:(Association key:eachKey value:eachValue).
    ].

    "Created: / 17-03-2017 / 11:05:29 / stefan"
!

associationsSelect:aBlock
    "return a new collection with all elements from the receiver, for which
     the argument aBlock evaluates to true.
     The block gets keys and values as an association argument.

     See also: #keysAndValuesSelect: (which is slightly faster),
               #select: (which only passes the value)

     This is much like #keysAndValuesSelect:, but aBlock gets the
     key and value as a single association argument.
     #keysAndValuesSelect: and is a bit faster therefore (no intermediate objects).

     WARNING: do not add/remove elements while iterating over the receiver.
              Iterate over a copy to do this."

    |newCollection|

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

    "
     |ages|

     ages := Dictionary new.
     ages at:'cg' put:37.
     ages at:'ca' put:33.
     ages at:'sv' put:36.
     ages at:'tk' put:28.

     ages associationsSelect:[:assoc |
                (assoc key startsWith:'c') or:[assoc value < 30]].
    "

    "Created: / 14-09-2018 / 16:44:11 / Stefan Vogel"
!

do:aBlock
    "evaluate aBlock for each value"

    self keysAndValuesDo:[:elKey :elValue | aBlock value:elValue]

    "Created: / 19.6.1998 / 00:56:24 / cg"
!

keysAndValuesDo:aBlock
    "evaluate aBlock for each key and value"

    ^ self subclassResponsibility

    "Created: / 19.6.1998 / 00:56:52 / cg"
!

keysAndValuesSelect:aBlock
    "return a new collection with all elements from the receiver, for which
     the argument aBlock evaluates to true.
     The block gets keys and values as separate arguments.

     See also:
        #associationsSelect:    (which passes key-value pairs),
        #keysSelect:            (which passes key values),
        #select:                (which only passes the value)

     This is much like #associationsSelect:, but aBlock gets the
     key and value as two separate arguments.
     #associationsSelect: is a bit slower.

     WARNING: do not add/remove elements while iterating over the receiver.
              Iterate over a copy to do this."

    |newCollection|

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

    "
     |ages|

     ages := SmallDictionary new.
     ages at:'cg' put:37.
     ages at:'ca' put:33.
     ages at:'sv' put:36.
     ages at:'tk' put:28.

     ages keysAndValuesSelect:[:name :age |
                (name startsWith:'c') or:[age < 30]].
    "

    "Created: / 18-09-2018 / 15:22:05 / Stefan Vogel"
!

keysSelect:aBlock
    "return a new collection with all elements from the receiver, for which
     the argument aBlock evaluates to true.
     The block gets the individual keys as its single argument.

     See also:
        #associationsSelect:            (which passes key->value associations),
        #keysAndValuesSelect:           (which passes key & value args)
        #select:                        (which passes values as arg),

     WARNING: do not add/remove elements while iterating over the receiver.
              Iterate over a copy to do this."

    |newCollection|

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

    "
     |d|

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

     d keysSelect:[:el | el startsWith:'b'].
    "

    "Created: / 18-09-2018 / 15:23:26 / Stefan Vogel"
!

printElementsDo:aBlock
    "redefined, so #printOn: prints associations"

    ^ self associationsDo:aBlock

    "Created: / 14-09-2018 / 17:47:48 / Stefan Vogel"
!

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.

     See also:
        #associationsSelect:            (which passes key->value associations),
        #keysAndValuesSelect:           (which passes key & value args)
        #keysSelect:                    (which passes key values),

     WARNING: do not add/remove elements while iterating over the receiver.
              Iterate over a copy to do this."

    |newCollection|

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

    "
     |d|

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

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

    "Created: / 18-09-2018 / 15:25:15 / Stefan Vogel"
! !


!KeyedCollection methodsFor:'queries'!

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].
    ^ val = anAssociation value

    "Created: / 14-09-2018 / 16:48:10 / Stefan Vogel"
!

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

    self keysDo:[:elKey | aKey == elKey ifTrue:[^ true]].
    ^ false

    "Created: / 19.6.1998 / 00:55:05 / cg"
!

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

    self keysDo:[:elKey | aKey = elKey ifTrue:[^ true]].
    ^ false

    "Created: / 19.6.1998 / 00:55:05 / cg"
! !

!KeyedCollection methodsFor:'removing'!

removeAllKeys:aCollection
    "remove all keys of the argument, aCollection from the receiver.
     Raises an error, if some element-to-remove is not in the receiver."

    aCollection do:[:element | self removeKey:element].

    "Modified (comment): / 28-04-2017 / 13:36:15 / stefan"
!

removeAssociation:assoc
    "remove the association from the collection.
     If it was not in the collection report an error.
     Only the key is used in the passed argument, and a new
     association, for the key and the previously stored value is returned.

     WARNING: do not remove elements while iterating over the receiver.
              See #saveRemoveKey: to do this."

    |key|

    key := assoc key.
    ^ Association key:key value:(self removeKey:key)

    "Created: / 14-09-2018 / 16:20:47 / Stefan Vogel"
!

removeKey:aKey
    "remove key (and the value stored under that key) from the
     receiver; raise an error if no such element is contained"

    ^ self removeKey:aKey ifAbsent:[self errorKeyNotFound:aKey]

    "Created: / 19.6.1998 / 00:53:25 / cg"
    "Modified: / 19.6.1998 / 00:54:02 / cg"
!

removeKey:aKey ifAbsent:exceptionBlock
    "remove key (and the value stored under that key) from the
     receiver; return the value which was stored previously there.
     If no such element is contained, return the value
     from evaluating exceptionBlock"

    ^ self subclassResponsibility

    "Created: / 19.6.1998 / 00:53:58 / cg"
! !

!KeyedCollection methodsFor:'searching'!

findFirst:aBlock ifNone:exceptionValue
    "find the index of the first element, for which evaluation of the argument, aBlock returns true;
     return its index or the value from exceptionValue if none detected.
     This is much like #detect:ifNone:, however, here an INDEX is returned,
     while #detect:ifNone: returns the element.

     Here we return the first key for which aBlock matches the value.
     Note that there is no order in a Dictionary, so any element is first."

    self keysAndValuesDo:[:eachKey :eachValue| (aBlock value:eachValue) ifTrue:[^ eachKey]].
    ^ exceptionValue value.

    "
        (KeyValueList withKeys:#('a' 'b' 'c') andValues:#('bla' 'hello' 'hallo'))
            findFirst:[:v| v first = $h].
    "

    "Created: / 16-03-2017 / 17:46:02 / stefan"
!

findFirstKey:aBlock
    "find and return the first key, for which evaluation of the argument, aBlock
     returns true; return nil if none is detected."

    self keysDo:[:key |
        (aBlock value:key) ifTrue:[^ key].
    ].
    ^ nil

    "Created: 8.10.1996 / 22:01:31 / cg"
    "Modified: 8.10.1996 / 22:02:03 / cg"
! !

!KeyedCollection class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !