SmallDictionary.st
author Stefan Vogel <sv@exept.de>
Tue, 22 Oct 2019 20:26:06 +0200
changeset 24856 b622eeb3467d
parent 24503 7251ff5af5cd
child 24860 47e5de23dbf9
permissions -rw-r--r--
#REFACTORING by stefan class: SmallDictionary changed: #speciesForCollecting

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 2018 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 }"

KeyedCollection subclass:#SmallDictionary
	instanceVariableNames:'keysAndValues tally'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Unordered'
!

!SmallDictionary class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2018 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
"
    A lightweight Dictionary implementation (without hashing)
    for small dictionaries.

    Use this, when you have to store a small number (e.g. < 20) key/value pairs.
    As a side effect of the implementation, the dictionary is also ordered.

    Inspired by and compatible with RBSmallDictionary from RefactoryBrowser
    (although the implementaion is different).

    [instance variables:]
        keysAndValues       Array           keys are stored at odd indices, values at even indices
        tally               SmallInterger   the number of valid key/value pairs

    [class variables:]

    [see also:]
        Dictionary
        MethodDictionary

    [author:]
        Stefan Vogel
"
! !

!SmallDictionary class methodsFor:'instance creation'!

new
    ^ self basicNew initialize:2

    "Modified: / 14-09-2018 / 15:58:29 / Stefan Vogel"
!

new:capacity 
    ^ self basicNew initialize:capacity

    "Modified: / 14-09-2018 / 15:58:49 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'accessing'!

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

    |keyIndex "{Class: SmallInteger}"|

    keyIndex := keysAndValues indexOf:key startingAt:1 step:2.
    ^ keyIndex == 0 ifTrue:[aBlock value] ifFalse:[keysAndValues basicAt:keyIndex+1]

    "Modified: / 18-09-2018 / 14:08:21 / Stefan Vogel"
!

at:key ifAbsentPut:aBlock 
    "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."

    |keyIndex|

    keyIndex := keysAndValues indexOf:key startingAt:1 step:2.
    keyIndex == 0 ifTrue:[
        ^ self privateAt:key put:aBlock value
    ] ifFalse:[
        ^ keysAndValues basicAt:keyIndex+1.
    ]

    "Modified: / 18-09-2018 / 14:08:26 / Stefan Vogel"
!

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

    |keys sz "{Class: SmallInteger}"|

    keys := Array new:tally.
    sz := tally.
    1 to:sz do:[:i | keys at:i put:(keysAndValues at:i*2-1)].
    ^ keys

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

order
    "returns the keys in the order of their appearance"

    ^ self keys

    "
     |s|

     s := SmallDictionary new.
     s at:#a put:'aaa'; at:#b put:'bbb'; at:#c put:'ccc'; at:#d put:'ddd'; at:#a put:'aaaa'.
     s order    
    "

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

size
    "return the number of elements in the receiver."

    ^ tally

    "Modified (format): / 14-09-2018 / 15:44:11 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'adding'!

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

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

    self at:anAssociation key put:anAssociation value.
    ^ anAssociation

    "Modified (format): / 14-09-2018 / 15:25:38 / Stefan Vogel"
!

at:key put:value 
    "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."

    |keyIndex|

    "/ specially tuned for single-element small dicts (most are)
    tally == 0 ifTrue:[
        keysAndValues size >= 2 ifTrue:[
            keysAndValues basicAt:1 put:key.
            keysAndValues basicAt:2 put:value.
            tally := 1.
            ^ self.
        ].
    ].

    keyIndex := keysAndValues indexOf:key startingAt:1 step:2.
    keyIndex == 0 ifTrue:[
        self privateAt:key put:value
    ] ifFalse:[
        keysAndValues basicAt:keyIndex+1 put:value.
    ].
    ^ value

    "Modified: / 18-09-2018 / 14:12:13 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'copying-private'!

postCopy
    keysAndValues := keysAndValues copy.

    "Modified: / 14-09-2018 / 15:38:50 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'enumerating'!

do:aBlock
    "enumerate the values"

    |sz "{Class: SmallInteger}"|

    sz := tally * 2.
    2 to:sz by:2 do:[:i | aBlock value:(keysAndValues at:i)]

    "Modified: / 14-09-2018 / 16:30:18 / Stefan Vogel"
!

keysAndValuesDo:aBlock 
    |sz "{Class: SmallInteger}"|

    sz := tally * 2.
    1 to:sz-1 by:2 do:[:i | 
        aBlock 
            value:(keysAndValues at:i) 
            value:(keysAndValues at:i+1)]

    "Modified: / 14-09-2018 / 16:31:18 / Stefan Vogel"
!

keysDo:aBlock 
    |sz "{Class: SmallInteger}"|

    sz := tally * 2.
    1 to:sz-1 by:2 do:[:i | aBlock value:(keysAndValues at:i)]

    "Modified: / 14-09-2018 / 16:30:51 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'initialize-release'!

initialize:capacity
    keysAndValues := Array new:capacity*2.
    tally := 0

    "Created: / 14-09-2018 / 15:57:42 / Stefan Vogel"
! !


!SmallDictionary methodsFor:'private'!

grow:capacity 
    |newKeysAndValues|

    newKeysAndValues := Array new:capacity*2.
    newKeysAndValues replaceFrom:1 to:tally * 2 with:keysAndValues.
    keysAndValues := newKeysAndValues.

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

growKeysAndValues
    "duplicate the capacity"

    self grow:tally * 2

    "Modified: / 18-09-2018 / 15:37:34 / Stefan Vogel"
!

privateAt:key put:value
    |sz "{Class: SmallInteger}"|

    sz := tally * 2.
    sz == keysAndValues size ifTrue: [self growKeysAndValues].
    keysAndValues 
        basicAt:sz+1 put:key;
        basicAt:sz+2 put:value.
    tally := tally + 1.
    ^ value.

    "Modified: / 18-09-2018 / 13:33:30 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'queries'!

includesKey:aKey 
    ^ (keysAndValues indexOf:aKey startingAt:1 step:2) ~~ 0

    "Modified: / 18-09-2018 / 14:09:03 / Stefan Vogel"
!

isEmpty
    ^ tally == 0

    "Created: / 14-09-2018 / 15:44:49 / Stefan Vogel"
!

speciesForCollecting
    ^ SmallBag

    "
        (SmallDictionary 
            withKeys:#( 1 2 3 4 5 6 7 )
            andValues:#(10 20 30 10 20 30 10)
        ) collect:[:each| each < 25] 
    "

    "Created: / 18-09-2018 / 15:34:27 / Stefan Vogel"
    "Modified (comment): / 22-10-2019 / 20:15:32 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'removing'!

empty
    "RefactoryBrowser compatibility"

    self removeAll

    "Modified: / 14-09-2018 / 15:59:57 / Stefan Vogel"
!

remove:anAssociation ifAbsent:anExceptionBlock 
    self removeKey:(anAssociation key) ifAbsent:anExceptionBlock.
    ^ anAssociation

    "Modified (format): / 14-09-2018 / 15:40:44 / Stefan Vogel"
!

removeAll
    tally := 0.
    keysAndValues atAllPut:nil.

    "Modified: / 14-09-2018 / 16:02:28 / Stefan Vogel"
!

removeKey:key ifAbsent:aBlock 
    |keyIndex "{Class:SmallInteger}"
     sz "{Class:SmallInteger}"
     value|

    keyIndex := keysAndValues indexOf:key startingAt:1 step:2.
    keyIndex == 0 ifTrue:[
        ^ aBlock value
    ].
    value := keysAndValues at:keyIndex+1.
    sz := tally*2.
    keyIndex to:sz-2 do:[:i | 
        keysAndValues at:i put:(keysAndValues at:i + 2).
    ].
    keysAndValues at:sz-1 put:nil.
    keysAndValues at:sz put:nil.
    tally := tally - 1.
    ^ value

    "Modified: / 18-09-2018 / 14:09:15 / Stefan Vogel"
! !

!SmallDictionary methodsFor:'testing'!

isDictionary
    "return true, if the receiver is some kind of dictionary;
     true returned here - the method is redefined from Object."

    ^ true

    "Created: / 14-09-2018 / 18:31:24 / Stefan Vogel"
!

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

    ^ false

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

!SmallDictionary methodsFor:'visiting'!

acceptVisitor:aVisitor with:aParameter
    "dispatch for visitor pattern; send #visitDictionary:with: to aVisitor"

    ^ aVisitor visitDictionary:self with:aParameter
! !

!SmallDictionary class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !