MethodDictionary.st
author Stefan Vogel <sv@exept.de>
Thu, 13 Jun 1996 00:11:10 +0200
changeset 1461 dd25bb1e9973
parent 530 07d0bce293c9
child 1465 cfeb5a29bf0c
permissions -rw-r--r--
Use methodDictionary instead of selector/method arrays. Still backward compatible if UseMethodDictionary in Behavior is set to false.

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

'From Smalltalk/X, Version:2.10.9 on 12-jun-1996 at 16:15:19'                   !

Array subclass:#MethodDictionary
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Methods'
!

!MethodDictionary class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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.
"
!

documentation
"
    Instances of MethodDictionary store selector/method associations
    in classes. Conceptionally, they behave like Dictionaries, but are
    implemented using a single array (instead of dictionary, which uses
    two arrays to store keys and values separately).
    Also, they do not use hashing, since due to caching in the VM, hashing
    does not make too much of a difference in speed, but complicates the 
    VM implementations.
"
! !

!MethodDictionary class methodsFor:'instance creation'!

new:sz 
    ^ self basicNew:(sz * 2)
!

withAll:aDictionary
    "create a MethodDictionary from another Dictionary"

    |newDict i|

    newDict := self new:aDictionary size.
    i := 1.
    aDictionary keysAndValuesDo:[ :key :value |
        newDict basicAt:i   put:key.
        newDict basicAt:i+1 put:value.
        i := i+2.
    ].
    ^ newDict

    "
        |d|

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

    "Created: 12.6.1996 / 13:46:43 / stefan"
    "Modified: 12.6.1996 / 13:56:36 / stefan"
!

withKeys:keys andValues:values
    "create a MethodDictionary from a key (selector) array and value (method) array"

    |inst sz|

    sz := keys size.
    inst := self new:sz.
    1 to:sz do:[:i|
        inst basicAt:(i*2)-1  put:(keys   at:i).
        inst basicAt:(i*2)    put:(values at:i).
    ].
    ^ inst

    "Created: 12.6.1996 / 13:46:43 / stefan"
! !

!MethodDictionary class methodsFor:'binary storage'!

binaryFullDefinitionFrom:stream manager:manager
   |size inst|

   size := manager nextObject.
   inst := self new:size.
   1 to:size*2 by:2 do:[:i|
        inst basicAt:i put:manager nextObject.          "/ get selector
        inst basicAt:(i + 1) put:(Method binaryFullDefinitionFrom:stream manager:manager).
   ].
   ^ inst

    "Created: 7.6.1996 / 13:37:22 / stefan"
    "Modified: 7.6.1996 / 13:52:08 / stefan"
! !

!MethodDictionary class methodsFor:'queries'!

isBuiltInClass
    "this class is known by the run-time-system"

    ^ self == MethodDictionary
! !

!MethodDictionary methodsFor:'accessing'!

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

    |sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
	(self basicAt:i) == key ifTrue:[
	    ^ key -> (self basicAt:(i + 1))
	]
    ].
    ^ self errorKeyNotFound
!

at:key 
    "return the value for a given key, which is supposed to be a symbol"

    |sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        (self basicAt:i) == key ifTrue:[
            ^ self basicAt:(i + 1)
        ]
    ].
    ^ self errorKeyNotFound:key

    "Modified: 7.6.1996 / 15:53:28 / stefan"
!

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

    |sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
	(self basicAt:i) == key ifTrue:[
	    ^ self basicAt:(i + 1)
	]
    ].
    ^ exceptionBlock value
!

at:key put:value 
    "set the value for a given key, which is supposed to be a symbol.
     In contrast to dictionaries, we allow adding elements only, if there is a
     empty slot (nil key) present."

    |slot sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        slot := self basicAt:i.
        (slot == key) ifTrue:[
            ^ self basicAt:(i + 1) put:value
        ].
        slot isNil ifTrue:[
            self basicAt:i put:key.
            ^ self basicAt:(i + 1) put:value
        ].
    ].
    ^ self errorKeyNotFound:key

    "Modified: 7.6.1996 / 09:39:04 / stefan"
!

at:key putOrAppend:value 
    "set the value for a given key, which is supposed to be a symbol.
     In contrast to dictionaries, we allow adding elements only, if there is a
     empty slot (nil key) present.
     Otherwise we create a return a new MethodDictionary"

    |slot emptySlot newDict sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        slot := self basicAt:i.
        (slot == key) ifTrue:[
            self basicAt:(i + 1) put:value .
            ^ self.
        ].
        slot isNil ifTrue:[
            emptySlot := i.
        ]
    ].

    emptySlot notNil ifTrue:[
        self basicAt:emptySlot       put:key.
        self basicAt:(emptySlot + 1) put:value.
        ^ self.
    ].

    "/ not enough room for new entry, copy to new dictionary
    newDict := self copyEmpty:sz/2+1.
    newDict replaceFrom:1 to:sz with:self startingAt:1.
    newDict basicAt:(sz+1) put:key.
    newDict basicAt:(sz+2) put:value.
    ^ newDict.

    "Created: 7.6.1996 / 15:01:54 / stefan"
    "Modified: 7.6.1996 / 17:32:40 / stefan"
!

keyAtValue:value ifAbsent:exceptionBlock
    "return the first key with value - 
     return result of exceptionBlock if no key can be found"

    |sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    2 to:sz by:2 do:[:i |
        (self basicAt:i) == value ifTrue:[
            ^ self basicAt:(i - 1)
        ]
    ].
    ^ exceptionBlock value

    "Created: 7.6.1996 / 14:53:57 / stefan"
!

removeKey:key 
    "remove key from dictionary. 
     We actually do not remove it, but set it to nil."

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

    "Created: 7.6.1996 / 15:58:50 / stefan"
!

removeKey:key ifAbsent:failBlock
    "remove key from dictionary. 
     We actually do not remove it, but set it to nil."

    |value sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        (self basicAt:i) == key ifTrue:[
           self basicAt:i        put:nil.
           value := self basicAt:(i + 1).
           self basicAt:(i + 1)  put:nil.
           ^ value
        ]
    ].

    ^ failBlock.

    "Created: 7.6.1996 / 15:57:56 / stefan"
!

removeKeyAndCompress:key
    "remove key from dictionary. 
     A new, compressed MethodDictionary will be returned,
     or nil, if key is not present."

    |newDict dstIndex sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    newDict := self copyEmptyAndGrow:(sz/2-1).
    dstIndex := 1.
    1 to:sz by:2 do:[:i |
        (self basicAt:i) ~~ key ifTrue:[
           newDict basicAt:dstIndex   put:(self basicAt:i).
           newDict basicAt:dstIndex+1 put:(self basicAt:i+1).
           dstIndex := dstIndex + 2.
        ]
    ].
    dstIndex > sz ifTrue:[
        ^ nil
    ].
    ^ newDict

    "Created: 7.6.1996 / 15:57:56 / stefan"
    "Modified: 7.6.1996 / 16:47:02 / stefan"
!

size
    "return the number of elements (associations) in the receiver"

    ^ self basicSize // 2
! !

!MethodDictionary methodsFor:'binary storage'!

storeFullBinaryDefinitionOn:stream manager:manager
    "store the complete description (i.e. including methods)"

    self size storeBinaryOn:stream manager:manager.
    self keysAndValuesDo:[:sel :mthd|
        sel storeBinaryOn:stream manager:manager.
        mthd makeRealMethod storeFullBinaryDefinitionOn:stream manager:manager.
    ].

    "Created: 7.6.1996 / 12:53:00 / stefan"
! !

!MethodDictionary methodsFor:'enumerating'!

do:aBlock
    "evaluate the 1 arg block aBlock for each value (i.e. each Method)"

    |sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        (self basicAt:i) notNil ifTrue:[
            aBlock value:(self basicAt:(i + 1)).
        ]
    ].

    "Created: 7.6.1996 / 09:25:23 / stefan"
    "Modified: 7.6.1996 / 13:47:37 / stefan"
!

keysAndValuesDo:aBlock
    "evaluate the 2 arg block aBlock for each key (i.e. each selector)
     and each value (i.e. each method)"

    |key sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        key := self basicAt:i.
        (key notNil) ifTrue:[
            aBlock value:key value:(self basicAt:(i+1)).
        ]
    ].

    "Created: 7.6.1996 / 09:27:42 / stefan"
!

keysDo:aBlock
    "evaluate the 1 arg block aBlock for each key (i.e. each selector)"

    |key sz "{ Class: SmallInteger }"|

    sz := self basicSize.
    1 to:sz by:2 do:[:i |
        key := self basicAt:i.
        (key notNil) ifTrue:[
            aBlock value:key.
        ]
    ].

    "Created: 7.6.1996 / 09:26:34 / stefan"
! !

!MethodDictionary methodsFor:'inspecting'!

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

    ^ DictionaryInspectorView

    "Created: 12.6.1996 / 12:29:13 / stefan"
! !

!MethodDictionary methodsFor:'queries'!

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

    ^ (1 to:self basicSize by:2) collect:[:index | self basicAt:index].
!

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

    ^ (2 to:self basicSize by:2) collect:[:index | self basicAt:index].

    "Created: 7.6.1996 / 09:40:32 / stefan"
! !

!MethodDictionary class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/MethodDictionary.st,v 1.5 1996-06-12 22:11:09 stefan Exp $'
! !