NameSpace.st
author Claus Gittinger <cg@exept.de>
Mon, 19 May 2003 12:13:53 +0200
changeset 7298 9b3c69eb2c5d
parent 6824 6fbe85d05646
child 7317 461d6124fd63
permissions -rw-r--r--
category

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


"{ Package: 'stx:libbasic' }"

Object subclass:#NameSpace
	instanceVariableNames:'category'
	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. 
    Thus, internally, the same mechanism is used for classes in
    a NameSpace and 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 possibly 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.

                "/ nameSpaces are not in any package
                thisNamespace setPackage:nil.
            ]    
        ]
    ].

    ^ thisNamespace

    "Created: 8.11.1996 / 13:41:59 / cg"
    "Modified: 4.1.1997 / 16:50:59 / cg"
!

name:aStringOrSymbol
    "create a new nameSpace, named aStringOrSymbol.
     Notice, that the nameSpace is created in the current one -
     dont get confused; we recommend, not to nest them too much."

    |currentNameSpace newNamespace existing ok nameSym fullName|

    ok := aStringOrSymbol first isLetter.
    ok ifTrue:[
        (aStringOrSymbol 
            findFirst:[:ch | (ch isLetterOrDigit or:[ch == $_]) not]
            startingAt:2) ~~ 0
        ifTrue:[
            ok := false.
        ]

"/        2 to:aStringOrSymbol size do:[:idx | |ch|
"/            ch := aStringOrSymbol at:idx.
"/            ok ifTrue:[
"/                ok := ch isLetterOrDigit or:[ch == $_].
"/            ]
"/        ]
    ].
    ok ifFalse:[
        self error:'invalid namespace name:''' , aStringOrSymbol printString , ''' (must be a valid identifier)'.
    ].

    nameSym := aStringOrSymbol asSymbol.

    self == NameSpace ifTrue:[
        currentNameSpace := Class nameSpaceQuerySignal query.
        currentNameSpace isNil ifTrue:[currentNameSpace := Smalltalk].
        fullName := nameSym
    ] ifFalse:[
        currentNameSpace := self.
        fullName := (self name , '::' , nameSym) asSymbol
    ].

    (existing := currentNameSpace at:nameSym) notNil ifTrue:[
        ^ existing
    ].

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

    "/ nameSpaces are not in any package
    newNamespace notNil ifTrue:[newNamespace setPackage:nil].
    ^ newNamespace

    "
     NameSpace name:'foo'
     (NameSpace name:'foo') category:'my name space'
     foo at:#bar put:(Metaclass new new)
     (NameSpace name:'foo') name:'bar'
    "
    "
     NameSpace name:'an-invalid++name'
     NameSpace name:'another:invalidName'
     NameSpace name:'another::invalidName'
    "

    "Modified: / 14.9.1997 / 09:46:59 / cg"
    "Modified: / 18.3.1999 / 18:24:13 / stefan"
!

new
    "catch new - namespaces are not to be created by the user"

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

    "Modified: 8.11.1996 / 21:38:00 / cg"
! !

!NameSpace class methodsFor:'Compatibility-VW5.4'!

defineClass: name
                superclass: superclass
                indexedType: indexed
                private: private
                instanceVariableNames: instVars
                classInstanceVariableNames: classInstVars
                imports: imports
                category: category

    ^ self
        defineClass: name
        superclass: superclass
        indexedType: indexed
        private: private
        instanceVariableNames: instVars
        classInstanceVariableNames: classInstVars
        imports: imports
        category: category
        attributes: nil
!

defineClass: name
                superclass: superclass
                indexedType: indexed
                private: private
                instanceVariableNames: instVars
                classInstanceVariableNames: classInstVars
                imports: imports
                category: category
                attributes: annotations

    "VW5i compatibility class/namespace creation"

    |variable words pointers|

    variable := words := pointers := false.
    indexed ~~ #none ifTrue:[
        self halt:'not yet implemented'.
    ].
    ^ superclass value class
        name:name 
        inEnvironment:self
        subclassOf:superclass value
        instanceVariableNames:instVars
        variable:variable
        words:words
        pointers:pointers
        classVariableNames:''
        poolDictionaries:''
        category:category
        comment:nil
        changed:true
        classInstanceVariableNames:classInstVars
! !

!NameSpace class methodsFor:'accessing'!

allClasses
    |classes|

    classes := IdentitySet new.
    self allClassesDo:[:aClass | classes add:aClass].
    ^ classes

    "Modified: 20.12.1996 / 15:34:50 / cg"
!

allClassesWithAllPrivateClasses
    |classes|

    classes := IdentitySet new.
    self allClassesDo:[:aClass | 
        classes add:aClass.
        aClass addAllPrivateClassesTo:classes.
    ].
    ^ classes

    "Modified: 20.12.1996 / 15:34:50 / cg"
!

at:classNameSymbol
    "return a class from the namespace defined by the receiver"

    ^ self privateClassesAt:classNameSymbol

    "Modified: 8.11.1996 / 21:39:41 / cg"
!

at:classNameSymbol ifAbsent:exceptionBlock
    "return a class or an alternative
     from the namespace defined by the receiver"

    |cls|

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

    "Modified: 8.11.1996 / 21:40:01 / cg"
!

at:classNameSymbol put:aClass
    "add a class to the namespace defined by the receiver"

    ^ self privateClassesAt:classNameSymbol put:aClass

    "Modified: 8.11.1996 / 21:40:12 / cg"
!

classNamed:aString
    "return the class with name aString, or nil if absent.
     To get to the metaClass, append ' class' to the string."

    ^ Smalltalk classNamed:(self name , '::' , aString)

    "Created: 9.9.1997 / 03:33:56 / cg"
!

includesKey:aClassNameStringOrSymbol
    "{ Pragma: +optSpace }"

    "return true if such a key is present"

    |nmSym|

    nmSym := (self name , '::' , aClassNameStringOrSymbol) asSymbolIfInterned.
    nmSym isNil ifTrue:[^ false].
    ^ Smalltalk includesKey:nmSym.


! !

!NameSpace class methodsFor:'enumerating'!

allBehaviorsDo:aBlock
    "enumerate all classes in this namespace"

    Smalltalk allBehaviorsDo:[:aClass |
        (aClass isBehavior and:[aClass isMeta not]) ifTrue:[
            aClass nameSpace == self ifTrue:[
                aBlock value:aClass
            ].
        ]
    ].

    "Modified: / 18.3.1999 / 17:21:06 / cg"
!

allClassesDo:aBlock
    "enumerate all classes in this namespace"

    Smalltalk allClassesDo:[:aClass |
        (aClass isBehavior and:[aClass isMeta not]) ifTrue:[
            aClass nameSpace == self ifTrue:[
                aBlock value:aClass
            ].
        ]
    ].

    "Modified: / 18.3.1999 / 17:21:06 / cg"
!

keysDo:aBlock
    "enumerate all class names in this namespace"

    |prefix prefixLen|

    prefix := self name , '::'.
    prefixLen := prefix size.

    Smalltalk keysAndValuesDo:[:aName :aClass |
        |key|

        (aName startsWith:prefix) ifTrue:[
            key := (aName copyFrom:prefixLen+1) asSymbol.
            aBlock value:key
        ]
    ].

    "
     Benchmarks keysDo:[:k | Transcript showCR:k]
    "
! !

!NameSpace class methodsFor:'fileOut'!

fileOutDefinitionOn:aStream
    "redefined to generate another definition message"

    self == NameSpace ifTrue:[
        super fileOutDefinitionOn:aStream
    ] ifFalse:[
        aStream nextPutAll:('NameSpace name:' , self name storeString)
    ]

    "Modified: 8.11.1996 / 21:39:03 / cg"
    "Created: 4.1.1997 / 20:36:32 / cg"
! !

!NameSpace class methodsFor:'fileOut-xml'!

fileOutXMLDefinitionOn:aStream
    "redefined to generate another definition message"

    self == NameSpace ifTrue:[
        super fileOutXMLDefinitionOn:aStream
    ] ifFalse:[
        aStream nextPutLine:'<name-space>'.
        aStream nextPutLine:'  <name>' , self name , '</name>'.
        aStream nextPutLine:'  <environment>Smalltalk</environment>'.
        aStream nextPutLine:'  <private>false</private>'.
        aStream nextPutLine:'  <imports>Smalltalk.*</imports>'.
        aStream nextPutLine:'  <category>none</category>'.
        aStream nextPutLine:'</name-space>'.
    ]
! !

!NameSpace class methodsFor:'inspecting'!

inspectorClass
    "{ Pragma: +optSpace }"

    "redefined to launch a DictionaryInspector
     (instead of the default Inspector)."

    ^ DictionaryInspectorView


! !

!NameSpace class methodsFor:'printing & storing'!

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

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

    "Created: 8.11.1996 / 21:37:24 / cg"
    "Modified: 20.12.1996 / 15:11:31 / cg"
! !

!NameSpace class methodsFor:'queries'!

allNamespaces
    "return a list of all namespaces"

    ^ self allNamespacesIn:Smalltalk
!

allNamespacesIn:anEnvironment
    "return a list of all namespaces"

    |set|

    set := IdentitySet with:anEnvironment.
    anEnvironment allClassesDo:[:aClass |
        (aClass isNameSpace 
        and:[aClass ~~ NameSpace
        and:[aClass ~~ anEnvironment
        and:[aClass ~~ Smalltalk]]]) ifTrue:[
            set add:aClass
        ]
    ].
    ^ set
!

isNameSpace
    "return true - I am a namespace"

    self == NameSpace ifTrue:[^ false].
    ^ true

!

isTopLevelNameSpace
    ^ (self name includes:$:) not
!

isTopLevelNamespace
    "obsolete - use isTopLevelNameSpace"

    ^ (self name includes:$:) not
! !

!NameSpace class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/NameSpace.st,v 1.46 2003-05-19 10:13:53 cg Exp $'
! !