SharedPool.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 13 Feb 2012 19:19:41 +0000
branchjv
changeset 17921 4069fe8e9039
parent 17911 a99f15c5efa5
child 17928 8e8dad2e6269
permissions -rw-r--r--
Merged with /trunk

"
 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-Squeak'!

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 notNil ifTrue:[^binding].

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

    "subclassing and environment are not preserved"
    ^nil

    "Modified: / 12-09-2011 / 09:40:36 / cg"
!

bindingsDo: aBlock
    self classVarNames do:[:eachKey |
        aBlock value:(eachKey -> (self classVarAt:eachKey))
    ].

    "Modified: / 12-09-2011 / 09:42:00 / cg"
! !

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

declareVariable:varName
    self == SharedPool ifTrue:[ self error ].

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

    "Created: / 07-02-2012 / 15:57:35 / cg"
! !

!SharedPool class methodsFor:'code generation'!

initializeFrom:aDictionary
    "given a dictionary, generate my classvars and the init code"

    |sortedNames code|

    sortedNames := aDictionary keys asSortedCollection.
    self addClassVarNames:sortedNames.

    code := String streamContents:[:s |
        s nextPutLine:'initialize'.
        sortedNames do:[:k |
            |v|

            v := aDictionary at:k.
            s nextPutLine:('    %1 := %2.' bindWith:k with:v storeString).
        ].
    ].
    self class compile:code classified:'initialization'

    "
     OLEStatusCodeConstants initializeFrom:aDictionary
    "

    "Created: / 21-12-2010 / 17:58:25 / cg"
    "Modified: / 15-01-2011 / 14:20:58 / cg"
! !

!SharedPool class methodsFor:'misc ui support'!

iconInBrowserSymbol
    <resource: #programImage>

    self == SharedPool ifTrue:[^ super iconInBrowserSymbol].
    ^ #sharedPoolBrowserIcon

    "Created: / 14-10-2010 / 12:04:32 / cg"
! !

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

at:name put:aValue
    "set a pool variable by name"

    ^ self classVarAt:name put:aValue

    "Created: / 08-09-2011 / 05:48:16 / cg"
!

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

keyAtValue:value ifAbsent:exceptionValue
    self keysDo:[:k |
        (self at:k) == value ifTrue:[ ^ k ].
    ].
    ^ exceptionValue value

    "Created: / 08-09-2011 / 05:51:10 / cg"
!

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
    ^ '$Header: /cvs/stx/stx/libbasic/SharedPool.st,v 1.19 2012/02/07 14:58:03 cg Exp $'
!

version_CVS
    ^ 'Header: /cvs/stx/stx/libbasic/SharedPool.st,v 1.19 2012/02/07 14:58:03 cg Exp '
!

version_SVN
    ^ '$Id: SharedPool.st 10777 2012-02-13 19:19:41Z vranyj1 $'
! !