SharedPool.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 05 Nov 2009 14:41:30 +0000
branchjv
changeset 17734 406b1590afe8
parent 17732 a1892eeca6c0
child 17735 6a5bc05f696a
permissions -rw-r--r--
Merged with trunk r10476

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

Object subclass:#SharedPool
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Classes'
!

!SharedPool class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2004 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 shared pool represents a set of bindings which are accessible to all classes
    which import the pool in its 'pool dictionaries'.
    SharedPool is NOT a dictionary but rather a name space.
    Bindings are represented by 'class variables' - as long as we have no better way to represent
    them at least. This is done to make stc happy (or at least, to not be forced to adapt it
    to any new semantics).
"
! !

!SharedPool class methodsFor:'Compatibility-V''Age'!

declareConstant:constantName value:value
    self == SharedPool ifTrue:[ self error ].

    (self classVarNames includes:constantName) ifFalse:[
        self addClassVarName:constantName
    ].

    self classVarAt:constantName put:value.
! !

!SharedPool class methodsFor:'name lookup'!

at:name
    "retrieve a pool variable by name"

    ^ self at:name ifAbsent:[self errorKeyNotFound:name]
!

at:name ifAbsent:aBlock
    "retrieve a pool variable by name"

    (self includesKey:name) ifFalse:[^ aBlock value].
    ^ self classVarAt:name
!

bindingOf: varName
    "Answer the binding of some variable resolved in the scope of the receiver"

    | aSymbol binding |

    self shouldImplement.       "not yet finished"
    aSymbol := varName asSymbol.

    "First look in classVar dictionary."
    binding := self classPool bindingOf: aSymbol.
    binding ifNotNil:[^binding].

    "Next look in shared pools."
    self sharedPools do:[:pool |
            binding := pool bindingOf: aSymbol.
            binding ifNotNil:[^binding].
    ].

    "subclassing and environment are not preserved"
    ^nil
!

bindingsDo: aBlock
self halt:'unfinished implementation'.
    ^ self classPool bindingsDo: aBlock
!

classBindingOf: varName
    "For initialization messages grant the regular scope"

    self shouldImplement.       "not yet finished"
    ^ super bindingOf: varName
!

includesKey:aSymbol
    ^ self keys includes:aSymbol

    "
     OpenGLConstants includesKey:#GL3Bytes
    "
!

keys
    ^ self classVarNames

    "
     OpenGLConstants keys
    "
!

keysDo:aBlock
    ^ self keys do:aBlock
! !

!SharedPool class methodsFor:'printing & storing'!

displayString
    "return a printed represenation - here, a reminder is appended,
     that this is not a regular class"

    self == SharedPool ifTrue:[
        ^ super displayString
    ].
    ^ self name , ' (* SharedPool *)'
! !

!SharedPool class methodsFor:'queries'!

isSharedPool
    ^ self ~~ SharedPool
! !

!SharedPool class methodsFor:'documentation'!

version
    ^ '$Id: SharedPool.st 10477 2009-11-05 14:41:30Z vranyj1 $'
!

version_CVS
    ^ '$Id: SharedPool.st 10477 2009-11-05 14:41:30Z vranyj1 $'
! !