Explainer.st
author Claus Gittinger <cg@exept.de>
Wed, 29 Oct 2003 11:45:21 +0100
changeset 1472 d69fc5970cd7
parent 1438 d8553b015a28
child 1637 993d58b1789b
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 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:libcomp' }"

Parser subclass:#Explainer
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-Compiler'
!

!Explainer class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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 very simple explainer - much more should be added ...
    This one is involved, when the 'explain' function is used in a 
    codeView (popup or via CMD-E).

    [author:]
        Claus Gittinger
"
! !

!Explainer class methodsFor:'explaining'!

commonSuperClassOf:listOfClassesOrClassNames
    |common|

    listOfClassesOrClassNames do:[:classOrClassName |
        |class|

        class := classOrClassName isBehavior 
                        ifTrue:[classOrClassName]
                        ifFalse:[Smalltalk classNamed:classOrClassName].

        common isNil ifTrue:[
            common := class
        ] ifFalse:[
            (class isSubclassOf:common) ifTrue:[
                "keep common"
            ] ifFalse:[
                (common isSubclassOf:class) ifTrue:[
                    common := class
                ] ifFalse:[
                    common := common commonSuperclass:class.

"/                    "walk up, checking"
"/                    found := false.
"/
"/                    common allSuperclassesDo:[:sup |
"/                        (found not and:[class isSubclassOf:sup]) ifTrue:[
"/                            common := sup.
"/                            found := true.
"/                        ]
"/                    ].
"/                    found ifFalse:[
"/                        class allSuperclassesDo:[:sup |
"/                            (found not and:[common isSubclassOf:sup]) ifTrue:[
"/                                common := sup.
"/                                found := true.
"/                            ]
"/                        ].
"/                    ].
                ]
            ].
        ].
        (common isNil or:[common == Object]) ifTrue:[^ common].
    ].
    ^ common

    "Modified: 17.6.1996 / 17:09:21 / stefan"
    "Modified: 5.9.1996 / 19:34:41 / cg"
!

explain:someText in:source forClass:aClass
    "Given a source and a substring of it, return a string containing
     an explanation.
     This is just a q&d implementation - to be correct, it should use the parser,
     and explain from the parsetree (instead of doing string matches).
     This leads to some wrong explanations, for example if some string is
     used as selector within a string, or if a variable is named like a
     message selector. I.e. the explanation should be context sensitive.
     Also, there could be much more detailed explanations."

    ^ self
        explain:someText in:source forClass:aClass short:false
!

explain:someText in:source forClass:aClass short:shortText
    "Given a source and a substring of it, return a string containing
     an explanation.
     This is just a q&d implementation - to be correct, it should use the parser,
     and explain from the parsetree (instead of doing string matches).
     This leads to some wrong explanations, for example if some string is
     used as selector within a string, or if a variable is named like a
     message selector. I.e. the explanation should be context sensitive.
     Also, there could be much more detailed explanations."

    |parser variables c string tmp
     spc sym sel stringText clsName val valString|

    string := someText string withoutSeparators.
    stringText := string allBold.
    stringText := '''' , stringText , ''''.

    "
     ask parser for variable names
    "
    ParseErrorSignal catch:[
        parser := self parseMethod:source in:aClass ignoreErrors:true ignoreWarnings:true.
    ].
    parser notNil ifTrue:[
        "look for variables"

        variables := parser methodVars.
        (variables notNil and:[variables includes:string]) ifTrue:[
            ^ stringText , ' is a method variable.'
        ].
        variables := parser methodArgs.
        (variables notNil and:[variables includes:string]) ifTrue:[
            ^ stringText , ' is a method argument.'
        ]
    ].

    parser isNil ifTrue:[
        parser := self for:(ReadStream on:source) in:aClass
    ].

    "instvars"
    c := aClass whichClassDefinesInstVar:string.
    c notNil ifTrue:[
        c isMeta ifTrue:[
            clsName := c theNonMetaclass name.
            shortText ifTrue:[
                ^ stringText , ' is a class instVar in ' , clsName , '.'
            ].
            ^ stringText, ' is a class instance variable in ' , clsName , '.'
        ].

        clsName := c name.
        shortText ifTrue:[
            ^ stringText , ' is an instVar in ' , clsName , '.'
        ].
        ^ stringText , ' is an instance variable in ' , clsName , '.'
    ].

"/    variables := aClass allInstVarNames.
"/    (variables notNil and:[variables includes:string]) ifTrue:[
"/        "where is it"
"/        c := aClass.
"/        [c notNil] whileTrue:[ |v|
"/            v := c instVarNames.
"/            (v notNil and:[v includes:string]) ifTrue:[
"/                ^ string , ' is an instance variable in ' , c name
"/            ].
"/            c := c superclass
"/        ].
"/        self error:'oops'
"/    ].

"/    "class instvars"
"/    variables := aClass class allInstVarNames.
"/    (variables notNil and:[variables includes:string]) ifTrue:[
"/        "where is it"
"/        c := aClass.
"/        [c notNil] whileTrue:[ |v|
"/            v := c class instVarNames.
"/            (v notNil and:[v includes:string]) ifTrue:[
"/                ^ string , ' is a class instance variable in ' , c name
"/            ].
"/            c := c superclass
"/        ].
"/        self error:'oops'
"/    ].

    "classvars"
    c := parser inWhichClassIsClassVar:string.
    c notNil ifTrue:[
        clsName := c name.
        shortText ifTrue:[
            stringText := stringText , ' is a classVar in ' , clsName 
        ] ifFalse:[
            stringText := stringText , ' is a class variable in ' , clsName
        ].
        val := Smalltalk at:(clsName , ':' , string) asSymbol.
        (val isBoolean or:[val isNil or:[val isSymbol]]) ifTrue:[
            valString := val storeString.
        ] ifFalse:[
            valString := val classNameWithArticle.
        ].
        ^ stringText , ' (' , valString , ').'
    ].

    c := aClass theNonMetaclass.
    c privateClasses do:[:pClass |
        (pClass name = string 
         or:[pClass nameWithoutPrefix = string]) ifTrue:[
            string := stringText , ' is a private class in ''' , c name , '''.'.
            shortText ifFalse:[
                string := (string , '\\It is only visible locally.') withCRs
            ].
            ^ string withCRs
        ].
    ].

    (spc := aClass nameSpace) notNil ifTrue:[
        sym := (spc name , '::' , string) asSymbolIfInterned.
        sym notNil ifTrue:[
            (Smalltalk at:sym) isBehavior ifTrue:[
                string :=  stringText , ' is a class in the ''' , spc name , ''' nameSpace.'.
                shortText ifFalse:[
                    string := (string 
                         , '\\It is only visible within this nameSpace.'
                         , '\Access from the outside is possible'
                         , '\by the special name ''' , spc name , '::' , string , '''.') withCRs
                ].
                ^ string withCRs
            ].
        ].
    ].

"/    string knownAsSymbol ifTrue:[
        "globals & symbols"

        tmp := self explainKnownSymbol:string inClass:aClass short:shortText.
        tmp notNil ifTrue:[ ^ tmp].

        "/ try with added colon ...
        sel := string , ':'.
        Symbol allInstancesDo:[:sym |
            (sym startsWith:sel) ifTrue:[
                tmp := self explainKnownSymbol:sym inClass:aClass short:shortText.
                tmp notNil ifTrue:[ ^ tmp].
            ]
        ].
"/    ].

    "try for some obvious things"
    tmp := self explainPseudoVariable:string in:aClass short:true.
    tmp notNil ifTrue:[ ^ tmp].

    "try syntax ..."

    tmp := self explainSyntax:string short:shortText.
    tmp notNil ifTrue:[ ^ tmp].

    shortText ifTrue:[
        ^ 'no explanation'
    ].

    parser isNil ifTrue:[
        ^ 'parse error - no explanation'
    ].
    ^ 'cannot explain this (could not figure out what this is).'

    "Created: / 3.12.1995 / 12:47:37 / cg"
    "Modified: / 16.4.1997 / 12:46:11 / stefan"
    "Modified: / 5.11.2001 / 16:54:23 / cg"
!

explainGlobal:string inClass:aClass short:shortText
    "return explanation or nil"

    |sym stringText tmp val classCategory|

    "if not even known as key, its definitely not a global"
    sym := string asSymbolIfInterned. 
    sym isNil ifTrue:[^ nil].

    "try globals"
    (Smalltalk includesKey:sym) ifFalse:[ ^ nil].

    stringText := string allBold.

    "/ stringText := '''' , stringText , ''''.
    tmp := stringText , ' is a global variable.'.

    val := Smalltalk at:sym.
    val isBehavior ifTrue:[
        "/ a class
        val isNameSpace ifTrue:[
            ^ stringText , ' is a namespace.'
        ].

        classCategory := val category ? 'uncategorized'.
        shortText ifTrue:[
            ^ stringText , ' is ' , (val isLoaded ifTrue:['a'] ifFalse:['an autoloaded'])
, ' class in the ''' , classCategory , ''' category.'.
        ].

        val name = string ifTrue:[
            tmp := tmp , '
' , string , ' is ' , (val isLoaded ifTrue:['a'] ifFalse:['an autoloaded'])
, ' class categorized as ' , classCategory , '
in the ''' , val package , ''' package.'.
            ^ tmp.
        ].

        tmp := tmp , '

' , string , ' is bound to the class ' , val name ,
' in the ''' , classCategory , ''' category.'.
        ^ tmp.
    ].

    shortText ifTrue:[
        ^ stringText , ' is a global, currently bound to ''' , val classNameWithArticle , '''.'.
    ].
    tmp := tmp , '

Its current value is ''' , val classNameWithArticle , '''.'.
    ^ tmp.
!

explainHereIn:aClass
    ^ 'like self, here refers to the object which received the message.

However, when sending a message to here the search for methods
implementing this message will start in the defining class (' , aClass name , ')
instead of the receivers class (' , aClass name , ' or subclass).
Thus, using here, redefined methods will NOT be reached with a here-send.'
!

explainKnownSymbol:string inClass:aClass
    "return explanation or nil"

    ^ self explainKnownSymbol:string inClass:aClass short:false
!

explainKnownSymbol:string inClass:aClass short:shortText
    "return explanation or nil"

    |sym|

    sym := string asSymbolIfInterned.
    sym isNil ifTrue:[^ nil].

    "try globals"

    (Smalltalk includesKey:sym) ifTrue:[
        ^ self explainGlobal:string inClass:aClass short:shortText
    ].

    ^ self explainSelector:string inClass:aClass short:shortText
!

explainPseudoVariable:string in:aClass
    "return explanation for the pseudoVariables self, super etc."

    ^ self explainPseudoVariable:string in:aClass short:false
!

explainPseudoVariable:string in:aClass short:shortText
    "return explanation for the pseudoVariables self, super etc."

    (string = 'self') ifTrue:[
        ^ self explainSelfIn:aClass short:shortText
    ].

    (string = 'super') ifTrue:[
        shortText ifTrue:[
            ^ '''super'' - message lookup starts in superclass ''' , aClass superclass name , '''.'
        ].
        ^ self explainSuperIn:aClass short:shortText
    ].

    (string = 'here') ifTrue:[
        shortText ifTrue:[
            ^ '''here'' - message lookup always starts in ''' , aClass name , '''.'
        ].
        ^ self explainHereIn:aClass
    ].

    (string = 'thisContext') ifTrue:[
        shortText ifTrue:[
            ^ '''thisContext'' - the current stack frame as an object.'
        ].
        ^ 'thisContext is a pseudo variable (i.e. it is built in).

ThisContext always refers to the context object for the currently executed method or
block (an instance of Context or BlockContext respectively). The calling chain and calling
receivers/selectors can be accessed via thisContext.'
    ].

    (string = 'true') ifTrue:[
        shortText ifTrue:[
            ^ '''true'' - the truth and nothing but the truth.'
        ].
        ^ 'true is a pseudo variable (i.e. it is built in).

True represents logical truth. It is the one and only instance of class True.'
    ].

    (string = 'false') ifTrue:[
        shortText ifTrue:[
            ^ '''false'' - obvisously not true.'
        ].
        ^ 'false is a pseudo variable (i.e. it is built in).

False represents logical falseness. It is the one and only instance of class False.'
    ].

    (string = 'nil') ifTrue:[
        shortText ifTrue:[
            ^ '''nil'' - undefined, unknown, void or dont care.'
        ].
        ^ 'nil is a pseudo variable (i.e. it is built in).

Nil is used for unitialized variables (among other uses).
Nil is the one and only instance of class UndefinedObject.'
    ].
    ^ nil
!

explainSelector:string inClass:aClass short:shortText
    "return explanation or nil"

    |sym list count tmp commonSuperClass s s2 
     firstImplementingClass cm msg t|

    sym := string asSymbolIfInterned.
    sym isNil ifTrue:[^ nil].

    "
     try selectors
     look who implements it
    "
    list := Set new.
    Smalltalk allClassesDo:[:c|
        (c includesSelector:sym) ifTrue:[
            list add:(c name).
            firstImplementingClass isNil ifTrue:[
                firstImplementingClass := c
            ]
        ].
        (c class includesSelector:sym) ifTrue:[
            list add:(c name , ' class').
            firstImplementingClass isNil ifTrue:[
                firstImplementingClass := c class
            ]
        ]
    ].

    (aClass canUnderstand:sym) ifTrue:[
        s2 := ('Instances of ''' , aClass name , ''' respond to #') , sym allBold , '.'.
        shortText ifFalse:[
            s2 := '\\' , s2 
                  , '\- inherited from ' withCRs
                  , (aClass whichClassImplements:sym) name allBold.
        ].
        firstImplementingClass := (aClass whichClassImplements:sym)
    ] ifFalse:[
        s2 := ''.
    ].

    count := list size.
    (count ~~ 0) ifTrue:[
        "
         for up-to 4 implementing classes,
         list them
        "
        list := list asOrderedCollection sort.
        shortText ifTrue:[
            tmp := ' is implemented in '.
        ] ifFalse:[
            tmp := ' is a selector implemented in '.
        ].
        s := '#' , string allBold.

        (count == 1) ifTrue:[
            (t := list first) isMeta ifTrue:[
                t := 'the ' , t
            ].
            msg := s , tmp , t , '.'.
            shortText ifFalse:[
                msg := msg , s2.
            ]
        ] ifFalse:[
            (count == 2) ifTrue:[
                msg := s , tmp , (list at:1) , ' and ' , (list at:2) , '.'.
                shortText ifFalse:[
                    msg := msg , s2.
                ].
            ] ifFalse:[
                shortText ifTrue:[
                    msg := s , tmp , count printString , ' classes'.
                    commonSuperClass := self commonSuperClassOf:list.
                    (commonSuperClass == Object
                    and:[commonSuperClass includesSelector:sym]) ifTrue:[
                        msg := msg , ' (including ' , 'Object' allBold, ')'
                    ].
                    msg := msg , '.'.
                    ^ msg
                ].

                (count == 3) ifTrue:[
                    msg := s , tmp , '
' , (list at:1) , ', ' , (list at:2) , ' and ' , (list at:3) , '.' , s2
                ] ifFalse:[
                    (count == 4) ifTrue:[
                        msg := s , tmp , '
' , (list at:1) , ', ' , (list at:2) , ', ' , (list at:3), ' and ' , (list at:4) , '.' , s2
                    ] ifFalse:[
                        "
                         if there are more, look for a common
                         superclass and show it ...
                        "
                        commonSuperClass := self commonSuperClassOf:list.
                        (commonSuperClass ~~ Object 
                        and:[commonSuperClass ~~ Behavior
                        and:[commonSuperClass ~~ Class
                        and:[commonSuperClass ~~ ClassDescription]]]) ifTrue:[
                            (list includes:commonSuperClass) ifTrue:[
                                msg := s . tmp , count printString , commonSuperClass name 
                                         , ' and redefined in ' , (count - 1) printString  
                                         , ' subclasses'
                                         , s2.
                                firstImplementingClass := commonSuperClass
                            ] ifFalse:[
                                msg := s , tmp, count printString , ' subclasses of ' , commonSuperClass name , s2
                            ]
                        ] ifFalse:[
                            (commonSuperClass == Object
                            and:[commonSuperClass includesSelector:sym]) ifTrue:[
                                msg := s , tmp , count printString , ' classes.

All objects seem to respond to that message, 
since there is an implementation in Object.' , s2.

                                firstImplementingClass := Object
                            ] ifFalse:[
                                ((commonSuperClass == Behavior
                                 or:[commonSuperClass == Class
                                 or:[commonSuperClass == ClassDescription]])
                                and:[commonSuperClass includesSelector:sym]) ifTrue:[
                                    msg := s , tmp , count printString , ' classes.

All classes seem to respond to that message, 
since there is an implementation in ' , commonSuperClass name , '.' , s2.

                                    firstImplementingClass := commonSuperClass
                                ] ifFalse:[
                                    "
                                     otherwise just give the number.
                                    "
                                    msg := s , tmp , count printString , ' classes.' , s2
                                ]
                            ]
                        ]
                    ]
                ]
            ].
        ].
        shortText ifFalse:[
            firstImplementingClass notNil ifTrue:[
                WindowGroup activeGroup withWaitCursorDo:[
                    cm := firstImplementingClass compiledMethodAt:sym.
                    cm notNil ifTrue:[
                        cm := cm methodComment.
                    ]
                ].
                cm notNil ifTrue:[
                    msg := msg , '\\The comment in ' withCRs , firstImplementingClass name allBold , ' is:\' withCRs , cm allItalic.
                ]
            ].
        ].
        ^ msg
    ].

    ^ nil

    "Modified: / 17.6.1996 / 17:09:30 / stefan"
    "Created: / 23.3.1999 / 13:29:33 / cg"
    "Modified: / 23.3.1999 / 13:40:40 / cg"
!

explainSelfIn:aClass short:shortText
    |sub subNames selfString className nSubClasses|

    selfString := '''' , 'self' allBold , ''''.

    sub := aClass allSubclasses.
    nSubClasses := sub size.

    aClass isMeta ifTrue:[
        className := aClass theNonMetaclass name.
        subNames := sub collect:[:c | c theNonMetaclass name].
        nSubClasses == 0 ifTrue:[
            shortText ifTrue:[
                ^ selfString , ' - the ''' , className , '''-class.'
            ].
            ^ selfString , 'refers to the object which received the message.

In this case, it will be the ' , className , '-class itself.'
        ].

        shortText ifTrue:[
            nSubClasses == 1 ifTrue:[
                ^ selfString , ' - the ''' , className , '''- or ''' , subNames first , '''-class.'
            ].
            ^ selfString , ' - the ''' , className , '''-class or one of its subclasses.'
        ].
        nSubClasses <= 5 ifTrue:[
            ^ selfString , ' refers to the object which received the message.

In this case, it will be the ' , className , '-class
or one of its subclasses:

' , subNames asStringCollection asString
        ].

        ^ selfString , ' refers to the object which received the message.

In this case, it will be the ' , className , '-class
or one of its ' , nSubClasses printString , ' subclasses.'
    ].

    subNames := aClass allSubclasses collect:[:c | c theNonMetaclass name].
    className := aClass name.
    nSubClasses == 0 ifTrue:[
        shortText ifTrue:[
            ^ selfString , ' - an instance of ''' , className , '''.'
        ].
        ^ selfString , 'refers to the object which received the message.

In this case, it will be an instance of ' , className , '.'
    ].

    shortText ifTrue:[
        nSubClasses == 1 ifTrue:[
            ^ selfString , ' - an instance of ''' , className , ''' or ''' , subNames first , '''.'
        ].
        ^ selfString , ' - an instance of ''' , className , ''' or one of its subclasses.'
    ].
    nSubClasses <= 5 ifTrue:[
        ^ selfString , ' refers to the object which received the message.

In this case, it will be an instance of ' , className , '
or one of its subclasses:

' , subNames asStringCollection asString
    ].

    ^ selfString , ' refers to the object which received the message.

In this case, it will be an instance of ' , className , '
or one of its ' , nSubClasses printString , ' subclasses.'
!

explainSuperIn:aClass short:shortText
    |superName|

    superName := aClass superclass name.

    shortText ifTrue:[
        ^ '''super'' - message lookup starts in ' , superName , '.'
    ].

    ^ 'like self, super refers to the object which received the message.

However, when sending a message to super the search for methods
implementing this message will start in the superclass (' , superName , ')
instead of the receivers class (' , aClass name , ' or subclass).
Thus, using super, a redefined method can call the original method in its superclass.'
!

explainSyntax:string
    "try syntax ...; return explanation or nil"

    ^ self explainSyntax:string short:false
!

explainSyntax:string short:shortText
    "try syntax ...; return explanation or nil"

    ((string = ':=') or:[string = '_']) ifTrue:[
        shortText ifTrue:[
            ^ 'Assign to variable on the left side.'.
        ].

        ^ '<variable> := <expression>

'':='' and ''_'' (which is left-arrow in some fonts) mean assignment.
The variable is bound to (i.e. points to) the value of <expression>.'
    ].

    (string = '^') ifTrue:[
        shortText ifTrue:[
            ^ 'Return value from method.'.
        ].
        ^ '^ <expression>

returns the value of <expression> as value from the method.
A return from within a block exits the method where the block is defined.'
    ].

    (string = ';') ifTrue:[
        shortText ifTrue:[
            ^ 'Cascade expression.'.
        ].
        ^ '<expression> ; selector1 ; .... ; selectorN

a cascade expression; evaluate expression, and send messages 
<selector1> ... <selectorN> to the first expressions receiver. 
Returns the value of the last send. The cascade sends may also have arguments.'
    ].

    (string = '|') ifTrue:[
        shortText ifTrue:[
            ^ ''.
        ].
        ^ '| locals |  or: [:arg | statements]

''|'' is used to mark a local variable declaration or separates arguments
from the statements in a block. Notice, that in a block-argument declaration
these must be prefixed by a colon character.
''|'' is also a selector understood by Booleans.'
    ].

    ((string startsWith:'(') or:[string endsWith:')']) ifTrue:[
        shortText ifTrue:[
            ^ ''.
        ].
        ^ '(<expression>)

expression grouping.'
    ].

    ((string startsWith:'[') or:[string endsWith:']']) ifTrue:[
        shortText ifTrue:[
            ^ ''.
        ].
        ^ '[:arg1 .. :argN | statements]

defines a block. 
Blocks represent pieces of executable code. Definition of a block does
not evaluate it. The block is evaluated by sending it a value/value:
message.
Blocks are often passed as arguments to Booleans (i.e. ifTrue:[...]) or
collections (i.e. do:[...]).'
    ].

    (string = ':') ifTrue:[
        shortText ifTrue:[
            ^ ''.
        ].
        ^ 'colons have different meaning depending on context:

1) they separate keyword-parts in symbols and keyword-messages as in:

    #at:put:                     a constant keyword symbol

    rec at:index put:value       sends the #at:put: message to rec,
                                 passing index and value as arguments.

2) within block-argument declarations as in:

    [:arg1 :arg2 | statements]

3) within an identifier, they separate the nameSpace part from
   the name part; as in:

    Smalltalk::Array    - the Array class in the Smalltalk nameSpace.
    Foo::Array          - the Array class in the Foo nameSpace.
'
    ].

    (string = '.') ifTrue:[
        ^ 'statement. "<- period here"
statement

within a method or block, individual statements are separated by periods.
'
    ].

    (string startsWith:'#' ) ifTrue:[
        (string startsWith:'#(' ) ifTrue:[
            shortText ifTrue:[
                ^ 'Array Literal.'.
            ].
            ^ 'is a constant Array.

The elements of a constant Array must be Number-constants, nil, true or false.
(notice, that not all Smalltalk implementations allow true, false and nil as
 constant-Array elements).'
        ].

        (string startsWith:'#[') ifTrue:[
            shortText ifTrue:[
                ^ 'ByteArray Literal.'.
            ].
            ^ 'is a constant ByteArray.

The elements of a constant ByteArray must be Integer constants in the range
0 .. 255.
(notice, that not all Smalltalk implementations support constant ByteArrays).'
        ].

        (string startsWith:'#''') ifTrue:[
            shortText ifTrue:[
                ^ 'Symbol Literal.'.
            ].
            ^ 'is a constant symbol containing non-alphanumeric characters.

Symbols are unique strings, meaning that there exists
exactly one instance of a given symbol. Therefore symbols can
be compared using == (identity compare) in addition to = (contents compare).
Beside this, Symbols behave mostly like Strings.

Notice, that not all Smalltalk implementations support this kind of symbols.'
        ].

        shortText ifTrue:[
            ^ 'Symbol Literal.'.
        ].
        ^ 'is a symbol.

Symbols are unique strings, meaning that there exists
exactly one instance of a given symbol. Therefore symbols can
be compared using == (identity compare) in addition to = (contents compare).
Beside this, Symbols behave mostly like Strings.'
    ].

    "/ is it a symbol without hash-character ?
    "/
"/    string knownAsSymbol ifTrue:[
"/        ^ 'is nothing, but #' , string , ' is known as a symbol.
"/
"/Symbols are unique strings, meaning that there exists
"/exactly one instance of a given symbol. Therefore symbols can
"/be compared using == (identity compare) in addition to = (contents compare).
"/Beside this, Symbols behave mostly like Strings.'
"/    ].

    ^ nil

    "Modified: / 31.10.1998 / 14:28:58 / cg"
! !

!Explainer class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/Explainer.st,v 1.61 2003-07-01 13:22:17 cg Exp $'
! !