MthdDict.st
author Claus Gittinger <cg@exept.de>
Thu, 23 Nov 1995 02:21:27 +0100
changeset 607 a9a526c51233
parent 530 07d0bce293c9
child 1461 dd25bb1e9973
permissions -rw-r--r--
checkin from browser

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

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

version
    ^ '$Header: /cvs/stx/stx/libbasic/Attic/MthdDict.st,v 1.4 1995-11-11 15:24:32 cg Exp $'
!

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:'queries'!

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

    ^ self == MethodDictionary
! !

!MethodDictionary class methodsFor:'instance creation'!

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

!MethodDictionary methodsFor:'accessing'!

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

    ^ self basicSize // 2
!

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
!

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
!

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 put:value 
    "set the value for a given key, which is supposed to be a symbol.
     In contrast to dictionaries, we do not allow adding elements here."

    |sz "{ Class: SmallInteger }"|

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

!MethodDictionary methodsFor:'queries'!

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

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


!MethodDictionary methodsFor:'enumeration'!

do:aBlock
    "evaluate the argument, aBlock for each element in the collection."

    |sz "{ Class: SmallInteger }"|

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

keysAndValuesDo:aBlock
    "evaluate the argument, aBlock for each element in the collection.
     Pass both index and element to the block."

    |sz "{ Class: SmallInteger }"|

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