NameSpace.st
author Claus Gittinger <cg@exept.de>
Fri, 08 Nov 1996 14:44:16 +0100
changeset 1933 74a0bff1ad19
parent 1931 5f60d3e5ba6e
child 1934 f21f70387dc4
permissions -rw-r--r--
*** empty log message ***

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

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

!Namespace class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996 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
"
    A Namespace is actually a dummy class, providing a home
    for its private classes. This has two advantages:
        - we only need one mechanism for both namespaces
          and private classes

        - there are no possible conflicts between a class
          and a namespace named alike.


    [author:]
        Claus Gittinger

    [see also:]
        Behavior ClassDescription Class Metaclass
        PrivateMetaclass
"

! !

!Namespace class methodsFor:'instance creation'!

fullName:aFullNameSpacePathName
    "given a pissibly nested name of a namespace, create all required
     intermediate spaces (if not already existing) and return the
     bottom-level space."

    "/ break it up, check for all intermediate spaces to exist
    "/ create them as required.

    |list idx0 idx superSpace done thisNamespace|

    list := OrderedCollection new.
    idx0 := 1.
    done := false.
    [done] whileFalse:[
        idx := aFullNameSpacePathName indexOf:$: startingAt:idx0.
        (idx ~~ 0) ifTrue:[
            (idx < aFullNameSpacePathName size and:[(aFullNameSpacePathName at:(idx+1)) == $:]) ifTrue:[
                superSpace := aFullNameSpacePathName copyFrom:idx0 to:(idx-1).
                list add:superSpace.
                idx0 := idx +2.
            ] ifFalse:[
                done := true
            ]
        ] ifFalse:[
            done := true.
        ]
    ].
    list add:(aFullNameSpacePathName copyFrom:idx0).

    "/ now, look and create 'em

    thisNamespace := nil.
    list do:[:aName |
        |key x|

        key := aName asSymbol.

        thisNamespace isNil ifTrue:[
            (Smalltalk includesKey:key) ifTrue:[
                thisNamespace := Smalltalk at:key.
                (thisNamespace notNil
                and:[thisNamespace isBehavior not]) ifTrue:[
                    ^ self error:'name conflict: namespace ' , aName , ' vs. global'.
                ]
            ].
            thisNamespace isNil ifTrue:[
                thisNamespace := self name:key
            ]
        ] ifFalse:[
            x := thisNamespace privateClassesAt:key.
            x notNil ifTrue:[
                thisNamespace := x
            ] ifFalse:[
                thisNamespace :=
                    self subclass:key
                       instanceVariableNames:''
                       classVariableNames:''
                       poolDictionaries:''
                       privateIn:thisNamespace
            ]    
        ]
    ].

    ^ thisNamespace

    "Created: 8.11.1996 / 13:41:59 / cg"
!

name:aSymbol
    "create a new nameSpace, named aSymbol"

    |newNamespace|

    (aSymbol includes:$:) ifTrue:[
        self error:'invalid namespace name'.
        ^ nil.
    ].

    newNamespace := self subclass:aSymbol
                         instanceVariableNames:''
                         classVariableNames:''
                         poolDictionaries:''
                         category:'uncategorized namespace'.

    ^ newNamespace

    "
     Namespace name:'foo'
     (Namespace name:'foo') category:'my name space'
    "

    "Modified: 8.11.1996 / 13:40:03 / cg"
!

new
    self error:'namespaces are not to be created with new'
! !

!Namespace class methodsFor:'accessing'!

at:classNameSymbol
    ^ self privateClassesAt:classNameSymbol
!

at:classNameSymbol ifAbsent:exceptionBlock
    |cls|

    cls := self privateClassesAt:classNameSymbol.
    cls isNil ifTrue:[
        ^ exceptionBlock value
    ].
    ^ cls
!

at:classNameSymbol put:aClass
    ^ self privateClassesAt:classNameSymbol put:aClass
! !

!Namespace class methodsFor:'enumerating'!

allBehaviorsDo:aBlock
    self privateClassesDo:aBlock

    "Created: 26.10.1996 / 12:29:01 / cg"
! !

!Namespace class methodsFor:'fileOut'!

basicFileOutDefinitionOn:aStream
    aStream nextPutAll:('Namespace name:' , self name storeString)
! !

!Namespace class methodsFor:'queries'!

isNamespace
    ^ true

    "Created: 26.10.1996 / 11:13:36 / cg"
! !

!Namespace class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/NameSpace.st,v 1.7 1996-11-08 13:44:16 cg Exp $'
! !