Parser.st
author Claus Gittinger <cg@exept.de>
Wed, 28 May 2008 11:42:30 +0200
changeset 2098 a03891b6fc30
parent 2093 b6b27c9c4d26
child 2100 fae3bbf851e0
permissions -rw-r--r--
more intelligent genertion of missing method

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

Scanner subclass:#Parser
	instanceVariableNames:'classToCompileFor selfValue contextToEvaluateIn selector
		methodArgs methodArgNames methodVars methodVarNames tree
		currentBlock parseForCode readInstVars readClassVars readGlobals
		usedInstVars usedClassVars usedVars modifiedInstVars
		modifiedClassVars modifiedGlobals usesSuper usedGlobals
		usedSymbols messagesSent messagesSentToSelf messagesSentToSuper
		localVarDefPosition evalExitBlock selfNode superNode nilNode
		hasPrimitiveCode hasNonOptionalPrimitiveCode primitiveNr
		primitiveResource logged warnedUndefVars warnedUnknownNamespaces
		correctedSource foldConstants lineNumberInfo currentNamespace
		currentUsedNamespaces methodNode alreadyWarnedClassInstVarRefs
		localBlockVarDefPosition endOfSelectorPosition
		beginOfBodyPosition startOfBlockPosition primitiveContextInfo
		usedLocalVars modifiedLocalVars alreadyWarnedUninitializedVars
		alreadyWarnedUnimplementedSelectors returnedValues currentPackage
		doItTemporaries moreSharedPools inFunctionCallArgument
		didWarnAboutSTXNameSpaceUse didWarnAboutSTXHereExtensionUsed
		parenthesisLevel didWarnAboutBadSupersend
		didWarnAboutSqueakExtensions'
	classVariableNames:'PrevClass PrevInstVarNames PrevClassVarNames
		PrevClassInstVarNames LazyCompilation FoldConstants
		LineNumberInfo SuppressDoItCompilation ParseErrorSignal
		RestartCompilationSignal'
	poolDictionaries:''
	category:'System-Compiler'
!

ProceedableError subclass:#ParseError
	instanceVariableNames:'errorMessage startPosition endPosition lineNumber'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Parser
!

Notification subclass:#ParseWarning
	instanceVariableNames:'errorMessage startPosition endPosition lineNumber'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Parser
!

Parser subclass:#PrimitiveSpecParser
	instanceVariableNames:'masterParser'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Parser
!

Parser::ParseError subclass:#UndefinedSuperclassError
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Parser
!

Notification subclass:#UndefinedVariableNotification
	instanceVariableNames:'parser'
	classVariableNames:''
	poolDictionaries:''
	privateIn:Parser
!

!Parser class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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
"
    Parser is used for both parsing and evaluating smalltalk expressions;
    it first builds a parseTree which is then interpreted (evaluate) or
    compiled. Compilation is done in the subclass ByteCodeCompiler and/or
    the (planned) MachineCodeCompiler.

    methods of main interest are:
        Parser evaluateExpression:...

    and:
        Parser parseExpression:...
        Parser parseMethod:...

    there is protocol to parse complete methods, selector specs, body only etc.

    Parser is also used to find the referenced/modified inst/classvars of
    a method - this is done by sending parseXXX message to a parser and asking
    the parser for referencedXVars or modifiedXVars (see SystemBrowser).

    You can also use parsers for all kinds of other things (ChangesBrowser for
    example analyzes the expressions in the changelist ...) by looking at the
    parsers tree. (Although this is somewhat dangerous, since it exports the
    compilers internals ... better style is to add specialized query methods here)

    One instance of Parser is created to parse one method or expression - i.e.
    its not suggested to reuse parsers.


  Constant folding:

    The parser has various modes for constant folding; by default, only numeric
    expressions involving integers and floats are constant folded
    (i.e. something like 'Float pi sin' or '1.5 + 0.3' will be reduced to a constant).

    Constant folding can be turned off completely (setting FoldConstants to nil)
    to ``secure folding'', which only folds constant numbers (#level1) or to #full. 
    In full mode, more constant expressions are folded (for example: '1.0 @ 1.0' is 
    reduced to a constant point), but the resulting code may not be compatible with other 
    smalltalk systems (consider the case, where the point is modified using #x: or #y: messages). 
    Therefore, this mode is a bit dangerous and disabled by default.
    The current implementation, base upon a global constant-folding setting is somewhat stupid
    and intermediate - a better solution would be to allow the optimization to be controlled
    by a method-pragma, since it may make sense to disable optimization on a method level,
    if its known that the used constant objects are subject of modifications as described above.
    

  Immutable arrays:

    Immutable arrays are experimental and being evaluated.
    Consider the case of a method returning '#(1 2 3 4)', and that array being modified
    by some other method (using #at:put:). Since the array-return is actually a return of
    a reference to the compiler created array, the next invokation of the method will
    return the modified array. These are hard to find bugs.
    By an option, the compiler can generate immutable arrays, which dont allow modification
    of its elements. For clean code, you should enable this option during development.

    As mentioned above, this is experimental. If it is reported to be a useful feature,
    the immutable feature will be extended to strings, point-literals etc. in a future version
    of st/x.



    [Instance variables:]

        classToCompileFor   <Class>             the class (or nil) we are compiling for

        selfValue           <any>               value to use as self when interpreting

        contextToEvaluateIn <Context>           the context (or nil) when interpreting

        selector            <Symbol>            the selector of the parsed method
                                                (valid after parseMethodSpecification)
        methodArgs                              internal

        methodArgNames      <Collection>        the names of the arguments
                                                (valid after parseMethodSpecification)

        methodVars                              internal

        methodVarNames      <Collection>        the names of the method locals
                                                (valid after parseMethodBodyVarSpec)

        tree                <ParseTree>         the parse tree - valid after parsing

        currentBlock                            if currently parsing for a block

        usedInstVars                            set of all accessed instances variables
                                                (valid after parsing)

        usedClassVars                           same for classVars

        usedVars                                all used variables (inst, class & globals)

        modifiedInstVars                        set of all modified instance variables

        modifiedClassVars                       same for clasVars

        localVarDefPosition <Integer>           the character offset of the local variable
                                                def. (i.e. the first '|' if any)
                                                Not yet used - prepared for automatic add of
                                                undefined variables

        evalExitBlock                           internal for interpretation

        selfNode            <Node>              cached one-and-only 'self' node
        superNode           <Node>              cached one-and-only 'super' node

        hasPrimitiveCode    <Boolean>           true, if it contains ST/X style primitive code
        hasNonOptionalPrimitiveCode    
                            <Boolean>           true, if it contains ST/X style primitive code
                                                which is NOT flagged by the OPTIONAL directive.

        primitiveNr         <Integer>           the parsed ST-80 type primitive number (or nil)

        logged

        warnedUndefVars     <Set>               set of all variables which the parser has
                                                already output a warning (to avoid multiple
                                                warnings about the same variable)

    [Class variables:]

        PrevClass           <Class>             class, of which properties are
                                                cached in:

        PrevInstVarNames      <Collection>      instance variablenames of cached class
        PrevClassVarNames     <Collection>      class variablenames of cached class
        PrevClassInstVarNames <Collection>      class instance variablenames of cached class

        LazyCompilation       <Boolean>         EXPERIMENTAL: lazy compilation

        ArraysAreImmutable    <Boolean>         if true, create array literals
                                                as instances of ImmutableArray,
                                                which cannot be stored into.
                                                Default is false, for compatibility.
                                                Can be turned on while developping
                                                new code to make certain that side
                                                effects are avoided.

        StringsAreImmutable   <Boolean>         same as above for string literals

        WarnST80Directives    <Boolean>         if true, give warnings about
                                                ST-80 directives (resource defs)
                                                which are ignored in st/x.
                                                defaults to false.

        FoldConstants         <Symbol>          controls how constant folding should be
                                                done.
                                                Can be one of:
                                                        nil      - no constant folding
                                                        #level1  - numeric optimizations only
                                                        #level2  - secure optimizations only
                                                        #full    - full folding

                                                level1:   arithmetic on constant numbers

                                                level2:   above PLUS array conversions with #asFloatArray,
                                                          #asDoubleArray, string concatenation

                                                full:     constant points.
                                                          
    [see also:]
        ByteCodeCompiler Scanner ObjectFileLoader
        Workspace
        SystemBrowser

    [author:]
        Claus Gittinger
"
!

examples
"
                                                                        [exBegin]
    Parser 
        evaluate:'1+2*3' 
        in:nil 
        receiver:nil 
        notifying:nil 
        logged:false 
        ifFail:nil      
                                                                        [exEnd]
                                                                        [exBegin]
    Parser undefinedVariableNotification handle:[:ex |
        |badName|

        badName := ex variableName.
        ex proceedWith:(ConstantNode value:5).
    ] do:[
        ^ self compilerClass 
            evaluate:'foo * 3' 
            in:nil 
            receiver:nil 
            notifying:nil 
            logged:false 
            ifFail:nil 
    ]
                                                                        [exEnd]
"
! !

!Parser class methodsFor:'instance creation'!

for:aStringOrStream in:aClass
    "return a new parser, reading code for aClass from aStringOrStream"

    |parser|

    parser := self for:aStringOrStream.
    parser setClassToCompileFor:aClass.
    ^ parser
! !

!Parser class methodsFor:'Compatibility-ST80'!

parse:aString class:aClass
    "same as #parseMethod:in: for ST80 compatibility."

    |parser|

    parser := self parseMethod:aString in:aClass.
    parser notNil ifTrue:[^ parser tree].
    ^ nil

    "Modified: 19.6.1997 / 16:34:57 / cg"
! !

!Parser class methodsFor:'Compatibility-Squeak'!

evaluate:someString for:aReceiver logged:logged
    ^ self evaluate:someString receiver:aReceiver logged:logged
        


! !

!Parser class methodsFor:'Signal constants'!

parseErrorSignal
    ^ ParseErrorSignal
!

restartCompilationSignal
    ^ RestartCompilationSignal

    "Created: / 15.11.2001 / 22:57:05 / cg"
!

undefinedVariableNotification
    ^ UndefinedVariableNotification
! !

!Parser class methodsFor:'changes'!

flushNameCache
    "unconditional flush name caches"

    [
        PrevClass notNil ifTrue:[
            PrevClass removeDependent:Parser
        ].
        PrevClass := nil.
        PrevInstVarNames := nil.
        PrevClassVarNames := nil.
        PrevClassInstVarNames := nil.
    ] valueUninterruptably

    "Parser flushNameCache"
!

update:something with:someArgument from:changedObject
    "aClass has changed its definition - flush name caches if we have to"

    (changedObject == PrevClass) ifTrue:[
        something == #definition ifTrue:[
            self flushNameCache
        ]
    ].
    (changedObject == Smalltalk) ifTrue:[
        something == #classDefinition ifTrue:[
            self flushNameCache
        ]
    ]
! !

!Parser class methodsFor:'class initialization'!

initialize
    LazyCompilation := false.      "/ usually set to true in your .rc file

    FoldConstants := #level1.
    LineNumberInfo := false.

    ParseErrorSignal isNil ifTrue:[
        ParseErrorSignal := ParseError.
        ParseErrorSignal notifierString:'Parse error:'.

"/        ParseErrorSignal := Error newSignalMayProceed:true.
"/        ParseErrorSignal notifierString:'parse error'.
"/        ParseErrorSignal nameClass:self message:#parseErrorSignal.
    ].
    RestartCompilationSignal := Signal new.

    Smalltalk addDependent:self.

    "
     self initialize
    "

    "Modified: / 22-08-2006 / 13:41:51 / cg"
! !

!Parser class methodsFor:'controlling compilation'!

allowArrayIndexSyntaxExtension
    "experimental"

    ^ ParserFlags allowArrayIndexSyntaxExtension
!

allowArrayIndexSyntaxExtension:aBoolean
    "experimental"

    ParserFlags allowArrayIndexSyntaxExtension:aBoolean.

    "
     self allowArrayIndexSyntaxExtension:true
     self allowArrayIndexSyntaxExtension:false
    "
!

allowFunctionCallSyntaxForBlockEvaluation
    "experimental"

    ^ ParserFlags allowFunctionCallSyntaxForBlockEvaluation
!

allowFunctionCallSyntaxForBlockEvaluation:aBoolean
    "experimental"

    ParserFlags allowFunctionCallSyntaxForBlockEvaluation:aBoolean.

    "
     self allowFunctionCallSyntaxForBlockEvaluation:true
     self allowFunctionCallSyntaxForBlockEvaluation:false
    "
!

allowReservedWordsAsSelectors
    "return true, if self, super, thisContext, nil, true and false are to be allowed
     as unary message selectors."

    ^ ParserFlags allowReservedWordsAsSelectors
!

allowReservedWordsAsSelectors:aBoolean
    "enable/disable, if self, super, thisContext, nil, true and false are to be allowed
     as unary message selectors."

    ParserFlags allowReservedWordsAsSelectors:aBoolean.
    self setupActions

    "
     self allowReservedWordsAsSelectors:true
     self allowReservedWordsAsSelectors:false
    "
!

arraysAreImmutable
    "return true if arrays are immutable literals"

    ^ ParserFlags arraysAreImmutable
!

arraysAreImmutable:aBoolean
    "turn on/off immutable array literals - default is false for ST-80 compatibilty."

    ParserFlags arraysAreImmutable:aBoolean.

    "
     can be added to your private.rc file:

     Compiler arraysAreImmutable:true     
     Compiler arraysAreImmutable:false      
    "
!

compileLazy
    "return true if compiling lazy"

    ^ LazyCompilation.
!

compileLazy:aBoolean
    "turn on/off lazy compilation - return previous setting.
     Actually this flag belongs into the ByteCodeCompiler subclass,
     but it also controls the reporting of some errors here; therefore
     its located here"

    |oldLazy|

    oldLazy := LazyCompilation.
    LazyCompilation := aBoolean.
    ^ oldLazy

    "
     Compiler compileLazy:false         
     Compiler compileLazy:true          
    "
!

foldConstants
    "return a symbol describing how constants are to be folded"

    ^ FoldConstants

    "Created: 9.2.1996 / 17:40:13 / cg"
!

foldConstants:aSymbol
    "set the symbol describing how constants are to be folded.
     It can be:
        nil             - no constant folding
        #level1         - numeric constants only
        #level2         - level1 PLUS array conversions PLUS string concatenation
        #full           - level2 PLUS constant points, constant rectangles (dangerous)"

    FoldConstants := aSymbol

    "Created: 9.2.1996 / 17:40:34 / cg"
!

implicitSelfSends
    "return true if undefined variables with
     lowercase first character are to be turned
     into implicit self sends"

    ^ ParserFlags implicitSelfSends
!

implicitSelfSends:aBoolean
    "turn on/off implicit self sends"

    ParserFlags implicitSelfSends:aBoolean

    "
     ParserFlags implicitSelfSends:true
     ParserFlags implicitSelfSends:false 
    "
!

lineNumberInfo
    ^ LineNumberInfo
!

lineNumberInfo:aBoolean
    LineNumberInfo := aBoolean
!

stringsAreImmutable
    "return true if strings are immutable literals"

    ^ ParserFlags stringsAreImmutable

    "Created: / 3.8.1998 / 14:53:25 / cg"
!

stringsAreImmutable:aBoolean
    "turn on/off immutable string literals - default is false for ST-80 compatibilty."

    ParserFlags stringsAreImmutable:aBoolean.

    "
     can be added to your private.rc file:

     ParserFlags stringsAreImmutable:true     
     ParserFlags stringsAreImmutable:false      
    "

    "Created: / 3.8.1998 / 14:53:28 / cg"
!

warnAboutBadComments:aBoolean
    "controls generation of warning messages about empty comments"
    
    ParserFlags warnAboutBadComments:aBoolean
!

warnAboutVariableNameConventions 
    "controls generation of warning messages about wrong variable names"
    
    ^ ParserFlags warnAboutVariableNameConventions
!

warnAboutVariableNameConventions:aBoolean 
    "controls generation of warning messages about wrong variable names"
    
    ParserFlags warnAboutVariableNameConventions:aBoolean
!

warnAboutWrongVariableNames
    "controls generation of warning messages about wrong variable names"
    
    ^ ParserFlags warnAboutWrongVariableNames
!

warnAboutWrongVariableNames:aBoolean
    "controls generation of warning messages about wrong variable names"
    
    ParserFlags warnAboutWrongVariableNames:aBoolean
!

warnUnusedVars
    "controls generation of warning messages about unued method variables"

    ^ ParserFlags warnUnusedVars
!

warnUnusedVars:aBoolean
    "controls generation of warning messages about unued method variables"

    ParserFlags warnUnusedVars:aBoolean
! !

!Parser class methodsFor:'defaults'!

maxLineNumber
    "return the maximum lineNumber that is possibly
     encoded in a methods byteCode debugging information.
     Since lineNumber entries only have 1 byte available,
     this is 255 for byteCode methods."

    ^ 255

    "Created: 14.2.1997 / 16:52:54 / cg"
! !

!Parser class methodsFor:'error correction'!

findBest:nMax selectorsFor:aString in:aClassOrNil
    "collect known selectors with their spelling distances to aString;
     return the nMax best suggestions. If the argument, aClassOrNil is not nil,
     the message is assumed to be sent to instances of that class (i.e. offer
     corrections from that hierarchy only)"

    |info block lcSelector|

    info := SortedCollection new.
    info sortBlock:[:a :b | a value > b value].

    lcSelector := aString asLowercase.

    block := [:sym :mthd|
        |dist lcSym keepThis|

        lcSym := sym asLowercase.
        (info contains:[:i | i key == sym]) ifFalse:[
            dist := lcSelector spellAgainst:lcSym.

            (lcSym startsWith:lcSelector) ifTrue:[
                dist := dist + (aString size * 10).
            ].
        
            (dist > 20) ifTrue:[
                (info contains:[:entry | entry key = sym]) ifFalse:[
                    keepThis := true.
                    info size >= nMax ifTrue:[
                        "will remove last entry anyway - so check if this one will remain ..."
                        dist < info last value ifTrue:[
                            keepThis := false.
                        ]
                    ].
                    keepThis ifTrue:[
                        "expensive - therefore do this check at last"
                        mthd isObsolete ifFalse:[
                            info add:(sym -> dist).
                            info size > nMax ifTrue:[
                                info removeLast.
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ].

    aClassOrNil isNil ifTrue:[
        Smalltalk allClassesDo:[:cls |
            cls methodDictionary keysAndValuesDo:block.
            cls class methodDictionary keysAndValuesDo:block.
        ]
    ] ifFalse:[
        aClassOrNil withAllSuperclassesDo:[:cls |
            cls methodDictionary keysAndValuesDo:block.
            "/ cls class methodDictionary keysAndValuesDo:block.
        ]
    ].

    ^ info asOrderedCollection collect:[:a | a key]

    "Modified: / 15-05-2007 / 12:46:24 / cg"
!

findBestSelectorsFor:aString
    "collect known selectors with their spelling distances to aString;
     return the 10 best suggestions"

    ^ self findBestSelectorsFor:aString in:nil

    "
     Parser findBestSelectorsFor:'at'
     Parser findBestSelectorsFor:'at:pu'
    "
!

findBestSelectorsFor:aString in:aClassOrNil
    "collect known selectors with their spelling distances to aString;
     return the 15 best suggestions. If the argument, aClassOrNil is not nil,
     the message is assumed to be sent to instances of that class (i.e. offer
     corrections from that hierarchy only)"

    ^ self findBest:15 selectorsFor:aString in:aClassOrNil

    "Modified: / 15-05-2007 / 12:39:28 / cg"
! !

!Parser class methodsFor:'evaluating expressions'!

evaluate:aStringOrStream
    "return the result of evaluating an expression in aStringOrStream.
     No doit-entry is added to the changeLog."

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:nil 
        logged:false
        ifFail:nil 
        compile:true

    "
     Compiler evaluate:'1 + 2'
     Compiler evaluate:'''hello world'' asSortedCollection displayString printNL'
     Compiler evaluate:'''hello world'' asSortedCollection printNL'
    "
!

evaluate:aStringOrStream compile:compile
    "return the result of evaluating aString, 
     The compile argument specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self 
        evaluate:aStringOrStream
        in:nil
        receiver:nil 
        notifying:nil 
        logged:false
        ifFail:nil
        compile:compile 
!

evaluate:aStringOrStream ifFail:failBlock
    "return the result of evaluating an expression in aStringOrStream.
     In case of any syntax errors, return the value of failBlock.
     No doit-entry is added to the changeLog."

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:nil 
        logged:false
        ifFail:failBlock 
        compile:true
    "
     Compiler evaluate:'1 +' ifFail:['oops']   
    "
!

evaluate:aStringOrStream in:aContext receiver:anObject notifying:requestor ifFail:failBlock
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     No doIt entry is added to the change-file. 
     If the failBlock argument is non-nil, it is evaluated if an error occurs."

    ^ self 
        evaluate:aStringOrStream
        in:aContext
        receiver:anObject
        notifying:requestor
        logged:false
        ifFail:nil
        compile:true

    "Modified: / 17.1.1998 / 02:54:07 / cg"
!

evaluate:aStringOrStream in:aContext receiver:anObject notifying:requestor logged:logged ifFail:failBlock
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs."

    ^ self 
        evaluate:aStringOrStream
        in:aContext
        receiver:anObject
        notifying:requestor
        logged:logged 
        ifFail:failBlock 
        compile:true
!

evaluate:aStringOrStream in:aContext receiver:anObject notifying:requestor logged:logged ifFail:failBlock compile:compile
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self new
        evaluate:aStringOrStream 
        in:aContext 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:compile
        checkForEndOfInput:(aStringOrStream isStream not)
!

evaluate:aStringOrStream logged:logged
    "return the result of evaluating an expression in aStringOrStream.
     The argument log controls if an entry is added to the changeLog."

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:nil 
        logged:logged
        ifFail:nil 
        compile:true
    "
     Compiler evaluate:'''some string''' logged:false   
     Compiler evaluate:'''some string''' logged:true   
    "
!

evaluate:aStringOrStream notifying:requestor
    "return the result of evaluating aString, 
     errors are reported to requestor"

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:requestor
        logged:false
        ifFail:nil 
        compile:true
!

evaluate:aStringOrStream notifying:requestor compile:compile
    "return the result of evaluating aString, 
     errors are reported to requestor.
     The compile argument specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:requestor
        logged:false
        ifFail:nil 
        compile:compile
!

evaluate:aStringOrStream notifying:requestor logged:logged
    "return the result of evaluating aString, 
     errors are reported to requestor"

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:requestor
        logged:logged
        ifFail:nil 
        compile:true
!

evaluate:aStringOrStream receiver:anObject
    "return the result of evaluating aString, 
     errors are reported to requestor. Allow access to
     anObject as self and to its instVars "

    ^ self 
        evaluate:aStringOrStream
        in:nil
        receiver:anObject
        notifying:nil
        logged:false
        ifFail:nil
        compile:true

    "
     Compiler evaluate:'self x' receiver:(1 @ 2)
    "

    "Created: 1.7.1997 / 19:02:24 / cg"
    "Modified: 1.7.1997 / 19:02:33 / cg"
!

evaluate:aStringOrStream receiver:someOne logged:logged
    "return the result of evaluating an expression in aStringOrStream.
     The argument log controls if an entry is added to the changeLog."

    ^ self 
        evaluate:aStringOrStream 
        in:nil 
        receiver:someOne 
        notifying:nil 
        logged:logged
        ifFail:nil 
        compile:true
    "
     Compiler evaluate:'''some string''' logged:false   
     Compiler evaluate:'''some string''' logged:true   
     Compiler evaluate:'self class' receiver:nil logged:false
     Compiler evaluate:'self class' receiver:1 logged:false 
    "
!

evaluate:aStringOrStream receiver:anObject notifying:requestor
    "return the result of evaluating aString, 
     errors are reported to requestor. Allow access to
     anObject as self and to its instVars (used in the inspector)"

    ^ self 
        evaluate:aStringOrStream
        in:nil
        receiver:anObject
        notifying:requestor
        logged:false
        ifFail:nil
        compile:true

    "
     Compiler evaluate:'self x' receiver:(1 @ 2) notifying:nil 
    "
!

evaluate:aStringOrStream receiver:anObject notifying:requestor compile:compile
    "return the result of evaluating aString, 
     errors are reported to requestor. Allow access to
     anObject as self and to its instVars (used in the inspector).
     The compile argument specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self 
        evaluate:aStringOrStream
        in:nil
        receiver:anObject
        notifying:requestor
        logged:false
        ifFail:nil
        compile:compile 
!

evaluateFrom:aStringOrStream ifFail:failBlock
    "return the result of evaluating an expression from aStringOrStream.
     In case of any syntax errors, return the value of failBlock.
     No doit-entry is added to the changeLog."

    ^ self 
        evaluateFrom:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:nil 
        logged:false
        ifFail:failBlock 
        compile:true
    "
     Compiler evaluate:'1 + 2' ifFail:['oops']   
    "
!

evaluateFrom:aStringOrStream in:aContext receiver:anObject notifying:requestor logged:logged ifFail:failBlock compile:compile
    "return the result of evaluating the next expression from aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self new
        evaluate:aStringOrStream 
        in:aContext 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:compile
        checkForEndOfInput:false
! !

!Parser class methodsFor:'general helpers'!

argAndVarNamesForContext:aContext
    <resource:#obsolete>
    self obsoleteMethodWarning.
    ^ aContext argAndVarNames.
! !

!Parser class methodsFor:'parsing'!

blockAtLine:line in:aMethod orSource:aString numArgs:nA numVars:nV
    "given a lineNr in some method, 
     return the containing BlockNode or nil.
     The given lineNr must be within a block for this to work.
     This is used by the debugger, to guess reverse from a lineNumber,
     to the corresponding block, in order to find out the blocks
     variable names (mhmh - all of this wasnt't needed, if blocks stored
     their characterPosition internally)."

    |compiler tree mSource who mClass blocks 
     maxSoFar innerBlock m|

    (line isNil or:[line == self maxLineNumber]) ifTrue:[
        ^ nil
    ].

    aMethod notNil ifTrue:[
        m := aMethod.
        who := m who.
        who isNil ifTrue:[
            m isWrapped ifTrue:[
                m := m wrapper.
                m notNil ifTrue:[
                    who := m who.
                ]
            ]
        ].
        who notNil ifTrue:[
            mClass := who methodClass.
            mClass isNil ifTrue:[ ^ nil].
        ].

        mSource := m source.
        mSource isNil ifTrue:[^ nil].
    ] ifFalse:[
        aString notNil ifTrue:[
            mSource := aString.
            mClass := UndefinedObject
        ] ifFalse:[
            ^ nil
        ]
    ].

    "create a compiler, let it parse and create the parsetree"

    compiler := self for:(ReadStream on:mSource) in:mClass.
    compiler parseForCode.
    compiler notifying:nil.
    compiler ignoreWarnings:true.
    compiler ignoreErrors:true.
    compiler lineNumberInfo:#full.

    Notification 
        handle:
            [:ex |
                ex proceed
            ]
        do:[
            aMethod notNil ifTrue:[
                (compiler parseMethodSpec == #Error) ifTrue:[
                    ^ nil.
                ].

                who notNil ifTrue:[
                    compiler selector ~~ (who methodSelector) ifTrue:[
                        ^ nil
                    ]
                ].
            ] ifFalse:[
                compiler nextToken.
            ].

            tree := compiler parseMethodBody.
        ].

    (compiler errorFlag 
    or:[tree == #Error
    or:[tree isNil]]) ifTrue:[
        ^ nil
    ].

    blocks := OrderedCollection new.
    tree collectBlocksInto:blocks.

    blocks := blocks select:[:aBlock |
                                line between: aBlock lineNumber and:aBlock endLineNumber

                            ].
    blocks size == 1 ifTrue:[
        ^ blocks at:1
    ].

    nA notNil ifTrue:[
        blocks := blocks select:[:aBlock |
                                aBlock numArgs == nA
                                ].
        blocks size == 1 ifTrue:[
            ^ blocks at:1
        ].
    ].
    nV notNil ifTrue:[
        blocks := blocks select:[:aBlock |
                                aBlock numVars == nV
                                ].
        blocks size == 1 ifTrue:[
            ^ blocks at:1
        ].
    ].

    "/ look for the inner one

    maxSoFar := 0.
    blocks do:[:aBlock |
        aBlock lineNumber > maxSoFar ifTrue:[
            innerBlock := aBlock.
            maxSoFar := aBlock lineNumber
        ]
    ].
    ^ innerBlock.

    "Created: 11.1.1997 / 23:29:13 / cg"
    "Modified: 14.2.1997 / 16:51:25 / cg"
!

checkMethod:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings
    "parse a method in a given class.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors, modified instvars, referenced classvars etc.
     The noErrors and noWarnings arguments specify if error and warning 
     messages should be sent to the Transcript or suppressed."

    |parser tree|

    aString isNil ifTrue:[^ nil].
    parser := self for:(ReadStream on:aString) in:aClass.
    parser ignoreErrors:ignoreErrors.
    parser ignoreWarnings:ignoreWarnings.
    tree := parser parseMethod.
    (parser errorFlag or:[tree == #Error]) ifTrue:[^ nil].

    ReadBeforeWrittenTester searchForReadBeforeWrittenIn:tree

    "
     self
        checkMethod:'foo
                        |local1 local2 local3|

                        local1 := local2.
                        ^ local3
                    '
        in:UndefinedObject 
        ignoreErrors:true 
        ignoreWarnings:true 
    "

    "Modified: / 30.10.1997 / 16:38:31 / cg"
!

parseExpression:aString
    "parse aString as an expression; 
     Return the parseTree (if ok), nil (for an empty string 
     or comment only) or #Error (syntactic error).
     Error and warning messages are suppressed."

    ^ self 
        withSelf:nil 
        parseExpression:aString 
        onError:#Error
        notifying:nil 
        ignoreErrors:true       "silence on Transcript"
        ignoreWarnings:true
        inNameSpace:nil

    "
     Parser parseExpression:'self foo'
     Parser parseExpression:'self:123'
     Parser parseExpression:'self:123' onError:nil
    "
!

parseExpression:aString inNameSpace:aNameSpaceOrNil
    "parse aString as an expression; 
     Return the parseTree (if ok), nil (for an empty string 
     or comment only) or #Error (syntactic error).
     Error and warning messages are suppressed."

    ^ self 
        withSelf:nil 
        parseExpression:aString 
        onError:#Error
        notifying:nil 
        ignoreErrors:true       "silence on Transcript"
        ignoreWarnings:true
        inNameSpace:aNameSpaceOrNil

    "Modified: 24.6.1997 / 16:44:00 / cg"
    "Created: 24.6.1997 / 16:44:26 / cg"
!

parseExpression:aString inNameSpace:aNameSpaceOrNil onError:errorValue
    "parse aString as an expression; 
     Return the parseTree (if ok), nil (for an empty string 
     or comment only) or errorValue (syntactic error).
     Error and warning messages are suppressed."

    ^ self 
        withSelf:nil 
        parseExpression:aString 
        onError:errorValue
        notifying:nil 
        ignoreErrors:true       "silence on Transcript"
        ignoreWarnings:true
        inNameSpace:aNameSpaceOrNil

    "Modified: 24.6.1997 / 16:44:00 / cg"
    "Created: 24.6.1997 / 16:44:26 / cg"
!

parseExpression:aString onError:errorValue
    "parse aString as an expression; 
     Return the parseTree (if ok), nil (for an empty string 
     or comment only) or errorValue (syntactic error).
     Error and warning messages are suppressed."

    ^ self 
        withSelf:nil 
        parseExpression:aString 
        onError:errorValue
        notifying:nil 
        ignoreErrors:true       "silence on Transcript"
        ignoreWarnings:true
        inNameSpace:nil

    "Modified: 24.6.1997 / 16:44:00 / cg"
!

parseMethod:aString
    "parse a method.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors etc.
     Error and warning messages are sent to the Transcript."

    ^ self parseMethod:aString in:nil

    "
     |p|

     p := Parser 
             parseMethod:'
                 foo:arg1 bar:arg2 baz:arg3 
                     |l1 l2| 
                     l1 := 0. 
                     l2 := arg1. 
                     ^ self'.

     'nArgs:  ' print. p numberOfMethodArgs printNL.
     'args:   ' print. p methodArgs printNL.
     'sel:    ' print. p selector printNL.
     'nLocal: ' print. p numberOfMethodVars printNL.
     'locals: ' print. p methodVars printNL.
     'tree:   ' printNL. p tree printAllOn:Stdout. Stdout cr.
    "

    "Modified: 24.4.1996 / 13:18:02 / cg"
!

parseMethod:aString in:aClass
    "parse a method in a given class.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors, modified instvars, referenced classvars etc.
     Error and warning messages are sent to the Transcript."

    ^ self 
        parseMethod:aString 
        in:aClass 
        ignoreErrors:false 
        ignoreWarnings:false

    "Modified: 24.4.1996 / 13:18:34 / cg"
!

parseMethod:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings
    "parse a method in a given class.
     Return a parser (if ok) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors, modified instvars, referenced classvars etc.
     The noErrors and noWarnings arguments specify if error and warning 
     messages should be sent to the Transcript or suppressed."

    |parser|

    parser := self new. 
    parser parseMethod:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings.
    ^ parser

    "Modified: / 06-03-2007 / 18:33:39 / cg"
!

parseMethod:aString in:aClass warnings:warnBoolean
    "parse a method in a given class.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors, modified instvars, referenced classvars etc.
     The warnBoolean arguments specifies if warning 
     messages should be sent to the Transcript or suppressed.

     This method is OBSOLETE, and left in for backward compatibility."

    self obsoleteMethodWarning.
    ^ self
        parseMethod:aString 
        in:aClass 
        ignoreErrors:false 
        ignoreWarnings:warnBoolean not

    "Modified: 24.4.1996 / 13:28:05 / cg"
!

parseMethodArgAndVarSpecification:aString
    "parse a methods selector, arg and var spec (i.e. locals);
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc.
     Error and warning messages are sent to the Transcript.
     This method is OBSOLETE."

    self obsoleteMethodWarning.
    ^ self parseMethodArgAndVarSpecification:aString in:nil

    "
     |p|

     p := Parser 
             parseMethodArgAndVarSpecification:'
                      foo:arg1 bar:arg2 baz:arg3 
                      |l1 l2|'.

     'nArgs:  ' print. p numberOfMethodArgs printNL.
     'args:   ' print. p methodArgs printNL.
     'sel:    ' print. p selector printNL.
     'nLocal: ' print. p numberOfMethodVars printNL.
     'locals: ' print. p methodVars printNL.
    "

    "Modified: 24.4.1996 / 13:29:43 / cg"
!

parseMethodArgAndVarSpecification:aString in:aClass
    "parse a methods selector, arg and var spec in a given class;
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args and locals.
     Error and warning messages are sent to the Transcript.
     This method is OBSOLETE."

    self obsoleteMethodWarning.
    ^ self parseMethodArgAndVarSpecification:aString 
           in:aClass 
           ignoreErrors:false
           ignoreWarnings:false 
           parseBody:false

    "Modified: 24.4.1996 / 13:30:03 / cg"
!

parseMethodArgAndVarSpecification:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings parseBody:body
    "parse a methods selector, arg and var spec in a given class;
     If parseBody is true, also parse the statements 
     (for primitives & resourceSpecs).
     The noErrors and noWarnings arguments specify if error and warning 
     messages should be sent to the Transcript or suppressed.

     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args and locals"

    |parser|

    aString isNil ifTrue:[^ nil].
    parser := self for:(ReadStream on:aString) in:aClass.
    parser ignoreErrors:ignoreErrors.
    parser ignoreWarnings:ignoreWarnings.
"/    parser nextToken.
    (parser parseMethodSpec == #Error) ifTrue:[^ nil].
    "/
    "/ used to be #parseMethodBodyVarSpec
    "/ - now, alternatively parse body for resource & primitive specs ..
    "/
    body ifTrue:[
        parser parseMethodBodyOrEmpty
    ] ifFalse:[
        parser parseMethodBodyVarSpec
    ].
    parser errorFlag ifTrue:[^ nil].
    ^ parser

    "Created: 24.4.1996 / 13:13:06 / cg"
    "Modified: 27.4.1996 / 16:58:02 / cg"
!

parseMethodArgAndVarSpecificationSilent:aString
    "parse a methods selector, arg and var spec (i.e. locals);
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc.
     Like #parseMethodArgAndVarSpecification:, but does NOT
     display error/warning messages on the transcript."

    ^ self parseMethodArgAndVarSpecificationSilent:aString in:nil

    "Modified: 24.4.1996 / 13:30:54 / cg"
!

parseMethodArgAndVarSpecificationSilent:aString in:aClass
    "parse a methods selector, arg and var spec in a given class;
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args and locals.
     Like #parseMethodArgAndVarSpecification:in:, but does not
     display error/warning messages on the transcript."

    ^ self parseMethodArgAndVarSpecification:aString 
           in:aClass 
           ignoreErrors:true 
           ignoreWarnings:true 
           parseBody:false

    "Modified: 24.4.1996 / 13:14:27 / cg"
!

parseMethodSilent:aString
    "parse a method.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors etc.
     Like #parseMethod:, but warning/error messages are suppressed."

    ^ self parseMethodSilent:aString in:nil

    "Modified: 24.4.1996 / 13:32:44 / cg"
!

parseMethodSilent:aString in:aClass
    "parse a method in a given class.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors, modified instvars, referenced classvars etc.
     Like #parseMethod:in:, but warning/error messages are suppressed."

    ^ self 
        parseMethod:aString 
        in:aClass 
        ignoreErrors:true 
        ignoreWarnings:true

    "Modified: 24.4.1996 / 13:32:57 / cg"
!

parseMethodSpecification:aString
    "parse a methods selector & arg specification; 
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc."

    ^ self parseMethodSpecification:aString in:nil

    "
     |p|

     p := Parser parseMethodSpecification:'foo:arg1 bar:arg2 baz:arg3'.
     'nArgs: ' print. p numberOfMethodArgs printNL.
     'args:  ' print. p methodArgs printNL.
     'sel:   ' print. p selector printNL
    "
!

parseMethodSpecification:aString in:aClass
    "parse a methods selector & arg spec for a given class;
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc."

    ^ self parseMethodSpecification:aString 
           in:aClass 
           ignoreErrors:false
           ignoreWarnings:false 
!

parseMethodSpecification:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings 
    "parse a methods selector & arg spec for a given class;
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc.
     noErrors and noWarnings specify if error- and warningMessages are
     to be output onto the Transcript."

    |parser tree|

    aString isNil ifTrue:[^ nil].
    parser := self for:(ReadStream on:aString) in:aClass.
    parser ignoreErrors:ignoreErrors.
    parser ignoreWarnings:ignoreWarnings.
"/    parser nextToken.
    tree := parser parseMethodSpec.
    (parser errorFlag or:[tree == #Error]) ifTrue:[^ #Error].
    ^ parser

    "Modified: 20.4.1996 / 20:09:48 / cg"
!

parseMethodSpecificationSilent:aString
    "parse a methods selector & arg specification; 
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc.
     Like #parseMethodSpecification:, but does not display any error/warning Messages on the transcript."

    ^ self parseMethodSpecificationSilent:aString in:nil
!

parseMethodSpecificationSilent:aString in:aClass
    "parse a methods selector & arg spec for a given class;
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver etc.
     Like #parseMethodSpecification:in:, but does not display any error/warning Messages on the transcript."

    ^ self parseMethodSpecification:aString 
           in:aClass 
           ignoreErrors:true 
           ignoreWarnings:true

    "Created: 31.10.1995 / 14:37:49 / cg"
!

selectorInExpression:aString
    "parse an expression - return the selector. Even malformed expressions
     (such as missing receiver or missing arg are parsed.
     Used for the SystemBrowsers implementors/senders query-box initial text.
     Returns nil if unparsable."

    |tree parser sel|

    (aString size == 0) ifTrue:[^ nil].

    Error 
        handle:[:ex | ]
        do:[
            tree := self withSelf:nil 
                         parseExpression:aString 
                         notifying:nil 
                         ignoreErrors:true 
                         ignoreWarnings:true. 
        ].

    "
     special: take the expression of the right side, if its an
     assignment or return
    "
    (tree notNil and:[tree ~~ #Error]) ifTrue:[
        (tree isAssignment 
        or:[tree isReturnNode]) ifTrue:[
            tree expression isMessage ifTrue:[
                tree := tree expression
            ]
        ].
        tree isMessage ifTrue:[
            ^ tree selector
        ].
    ].

    "
     mhmh, try expression without receiver
    "
    parser := self for:(ReadStream on:aString).
    parser ignoreErrors:true.
    Error 
        handle:[:ex | ]
        do:[
            parser nextToken.
            sel := parser degeneratedKeywordExpressionForSelector
        ].
    ^ sel

"
    Parser selectorInExpression:'foo at:1 put:(5 * bar)'     
    Parser selectorInExpression:'(foo at:1) at:1'           
    Parser selectorInExpression:'a + 4'                     
    Parser selectorInExpression:'a negated'                 
    Parser selectorInExpression:'at:1 put:5'            
    Parser selectorInExpression:'at:1 put:'            
    Parser selectorInExpression:'a at:1 put:5'            
    Parser selectorInExpression:'a at:1 put:'            
    Parser selectorInExpression:'a := foo at:1 put:5'    
"

    "Modified: 17.12.1996 / 12:12:47 / cg"
!

withSelf:anObject parseExpression:aString notifying:someOne 
    "parse aString as an expression with self set to anObject;
     Return the parseTree (if ok), nil (for an empty string 
     or comment only ) or #Error (syntactic error).

     Errors and warnings are forwarded to someOne (usually some
     codeView) which can highlight it and show a popup box."

    ^ self 
        withSelf:anObject 
        parseExpression:aString 
        onError:#Error
        notifying:someOne 
        ignoreErrors:false 
        ignoreWarnings:false 
        inNameSpace:nil

    "Modified: 24.6.1997 / 16:43:37 / cg"
!

withSelf:anObject parseExpression:aString notifying:someOne ignoreErrors:ignore
    "parse aString as an expression with self set to anObject;
     Return the parseTree (if ok), nil (for an empty string 
     or comment only ) or #Error (syntactic error).

     Errors and warnings are forwarded to someOne (usually some
     codeView) which can highlight it and show a popup box."

    ^ self 
        withSelf:anObject
        parseExpression:aString 
        onError:#Error
        notifying:someOne 
        ignoreErrors:ignore 
        ignoreWarnings:ignore 
        inNameSpace:nil

    "Modified: 24.6.1997 / 16:43:26 / cg"
!

withSelf:anObject parseExpression:aString notifying:someOne ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings
    "parse aString as an expression with self set to anObject;
     Return the parseTree (if ok), nil (for an empty string 
     or comment only ) or #Error (syntactic error).

     Errors and warnings are forwarded to someOne (usually some
     codeView) which can highlight it and show a popup box,
     iff ignoreErrors/ignoreWarnings is true respectively."

    ^ self
        withSelf:anObject 
        parseExpression:aString
        onError:#Error
        notifying:someOne 
        ignoreErrors:ignoreErrors 
        ignoreWarnings:ignoreWarnings 
        inNameSpace:nil

    "Modified: 24.6.1997 / 16:43:12 / cg"
!

withSelf:anObject parseExpression:aString notifying:someOne ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings inNameSpace:aNameSpaceOrNil
    "parse aString as an expression with self set to anObject;
     Return the parseTree (if ok), nil (for an empty string 
     or comment only ) or #Error (syntactic error).

     Errors and warnings are forwarded to someOne (usually some
     codeView) which can highlight it and show a popup box,
     iff ignoreErrors/ignoreWarnings is true respectively."

    ^ self
        withSelf:anObject 
        parseExpression:aString 
        onError:#Error 
        notifying:someOne 
        ignoreErrors:ignoreErrors 
        ignoreWarnings:ignoreWarnings 
        inNameSpace:aNameSpaceOrNil
!

withSelf:anObject parseExpression:aString onError:errorValue notifying:someOne ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings inNameSpace:aNameSpaceOrNil
    "parse aString as an expression with self set to anObject;
     Return the parseTree (if ok), nil (for an empty string 
     or comment only ) or errorValue (syntactic error).

     Errors and warnings are forwarded to someOne (usually some
     codeView) which can highlight it and show a popup box,
     iff ignoreErrors/ignoreWarnings is true respectively."

    |parser tree|

    aString isNil ifTrue:[^ nil].

    parser := self for:(ReadStream on:aString).
    tree := parser 
        parseExpressionWithSelf:anObject 
        notifying:someOne 
        ignoreErrors:ignoreErrors 
        ignoreWarnings:ignoreWarnings 
        inNameSpace:aNameSpaceOrNil.
    tree == #Error ifTrue:[
        ^ errorValue value
    ].
    ^ tree

    "Modified: / 14.12.1999 / 15:12:16 / cg"
! !

!Parser class methodsFor:'private'!

implementedInAnyClass:aSelectorStringOrSymbol
    |selectorSymbol|

    selectorSymbol := aSelectorStringOrSymbol asSymbolIfInterned.
    selectorSymbol isNil ifTrue:[^ false].

    Smalltalk allClassesAndMetaclassesDo:[:cls |
        (cls includesSelector:selectorSymbol) ifTrue:[^ true].
    ].
    ^ false

    "Modified: / 22-10-2006 / 02:25:37 / cg"
!

makeImmutableArray:anArray
    |newArray|

    newArray := anArray copy.
    ImmutableArray notNil ifTrue:[
        newArray changeClassTo:ImmutableArray.
    ].
    newArray beImmutable.
    ^ newArray
!

makeImmutableString:aString
    |newString|

    newString := aString copy.
    ImmutableString notNil ifTrue:[
        newString changeClassTo:ImmutableString.
    ].
    newString beImmutable.
    ^ newString
! !

!Parser class methodsFor:'unparsing'!

methodSpecificationForSelector:aSelector
    "given a selector such as #foo:bar:, return a string that could
     serve as a methods specification source code.
     To be used for code generators"

    |argNames n|

    n := aSelector numArgs.
    n == 1 ifTrue:[
        argNames := #('arg')
    ] ifFalse:[
        n <= 15 ifTrue:[
            argNames := #('arg1' 'arg2' 'arg3' 'arg4' 'arg5' 'arg6'
                          'arg7' 'arg8' 'arg9' 'arg10' 'arg11' 'arg12'
                          'arg13' 'arg14' 'arg15')
        ] ifFalse:[
            argNames := (1 to:aSelector numArgs) collect:[:i | 'arg' , i printString].
        ].
    ].
    ^ self methodSpecificationForSelector:aSelector argNames:argNames

    "
     Parser methodSpecificationForSelector:#foo:   
     Parser methodSpecificationForSelector:#foo:bar:   
     Parser methodSpecificationForSelector:#foo:bar:baz:   
     Parser methodSpecificationForSelector:#+       
     Parser methodSpecificationForSelector:#negated   
    "

    "Modified: / 12.2.1999 / 13:12:44 / cg"
!

methodSpecificationForSelector:aSelector argNames:argNames
    "given a selector such as #foo:bar:, return a string that could
     serve as a methods specification source code.
     To be used for code generators"

    |s nargs parts part|

    s := WriteStream on:String new.
    nargs := aSelector numArgs.
    nargs == 0 ifTrue:[
        s nextPutAll:aSelector
    ] ifFalse:[
        parts := aSelector partsIfSelector.
        1 to:nargs do:[:i |
            part := parts at:i.
            s nextPutAll:part.
            (part endsWith:$:) ifFalse:[
                s space.
            ].
            s nextPutAll:(argNames at:i).
            i ~~ nargs ifTrue:[s space].
        ]
    ].
    ^ s contents

    "
     Parser methodSpecificationForSelector:#foo:bar: argNames:#('one' 'two' 'three')  
     Parser methodSpecificationForSelector:#+ argNames:#('one')  
     Parser methodSpecificationForSelector:#negated   
    "

    "Modified: / 12.2.1999 / 12:33:50 / cg"
! !

!Parser methodsFor:'Compatibility-ST80'!

evaluate:aString in:aClassOrContext to:to notifying:aRequestor ifFail:failBlock
    |parseTree value|

    aString isNil ifTrue:[^ nil].
    self initializeFor:(ReadStream on:aString).

    "/ stupid - there seem to be differences among the various
    "/ ST dialects ...
    aClassOrContext isBehavior ifTrue:[
        self setClassToCompileFor:aClassOrContext.
        selfValue := nil.
    ] ifFalse:[
        self setContext:aClassOrContext.
        aClassOrContext notNil ifTrue:[
            self setSelf:(aClassOrContext receiver)
        ].
    ].
    requestor := aRequestor.

    self nextToken.
    parseTree := self parseMethodBody.
    (errorFlag or:[tree == #Error]) ifTrue:[^ #Error].
    parseTree notNil ifTrue:[
        self evalExitBlock:[:value | ^ failBlock value].
        value := parseTree evaluate
    ].
    self release.
    ^ value
!

parse:methodSource in:aClass notifying:aRequestor
    "parse a methods source.
     Return the methods parseTree"

    self initializeFor:methodSource.
    classToCompileFor := aClass.
    requestor := aRequestor.
    self parseMethod.

    ^ MethodNode new
        selector:selector
        arguments:methodArgs
        locals:methodVars
        statements:tree asCollectionOfStatements

    "Created: / 17.10.1997 / 12:35:01 / cg"
    "Modified: / 5.11.2001 / 16:56:43 / cg"
!

parseSelector:aStringOrStream
    "parse a methods source for the methods selector.
     Return the selector"

    self initializeFor:aStringOrStream.
    self parseMethodSpec.
    ^ selector.

    "
     Parser new
        parseSelector:'
parseSelector:aStringOrStream
    self initializeFor:aStringOrStream.
    self parseMethodSpec.
    ^ selector.
'                 
    "

    "Modified: 17.10.1997 / 12:35:46 / cg"
! !

!Parser methodsFor:'accessing'!

correctedSource
    ^ correctedSource
!

doItTemporaries
    ^ doItTemporaries
!

endOfLastToken
    ^ tokenPosition
!

endOfSelectorPosition
    "return the sourcePosition of the last character of the methods selector spec"

    ^ endOfSelectorPosition
!

errorFlag
    "return true if there where any errors (valid after parsing)"

    ^ errorFlag
!

evalExitBlock:aBlock
    "when evaluating a return expression, this block is evaluated"

    evalExitBlock := aBlock
!

getNameSpace
    "retrieve the nameSpace, as found in a Namespace directive"

    ^ currentNamespace

    "Modified: 8.11.1996 / 13:45:35 / cg"
!

implicitSelfSends
    ^ parserFlags implicitSelfSends
!

implicitSelfSends:aBoolean
    "turn on/off implicit self sends"

    parserFlags implicitSelfSends:aBoolean
!

moreSharedPools
    ^ moreSharedPools
!

moreSharedPools:aCollection
    moreSharedPools := aCollection
!

primitiveNumber
    "return the ST-80 style primitiveNumber or nil (valid after parsing)"

    ^ primitiveNr
!

primitiveResources
    "return the ST-80 style resource info or nil (valid after parsing)."

    ^ primitiveResource

    "Created: 29.5.1996 / 17:28:00 / cg"
!

release
    methodArgs := methodVars := tree := selfNode := superNode := nilNode := nil.
    super release.

    "Modified: / 31.3.1998 / 19:45:58 / cg"
!

setNameSpace:aNameSpaceName
    currentNamespace := NameSpace fullName:aNameSpaceName

    "Modified: 8.11.1996 / 13:43:14 / cg"
!

setPackage:aPackageID
    currentPackage := aPackageID
!

targetClass
    ^ classToCompileFor
!

targetClass:aClass
    classToCompileFor := aClass
!

tree
    "return the parsetree"

    ^tree
!

tree:aTree
    "private: set the tree - for internal use only"

    tree := aTree
!

warnSTXHereExtensionUsed
    ^ parserFlags warnSTXHereExtensionUsed
!

warnSTXHereExtensionUsed:aBoolean
    parserFlags warnSTXHereExtensionUsed:aBoolean
! !

!Parser methodsFor:'coding style checks'!

checkBlockArgumentNameConventionsFor:aVariableName
    self shouldPerformCodingStyleChecks ifTrue:[
        self checkLocalVariableNameConventionsFor:aVariableName.
    ]
!

checkBlockVariableNameConventionsFor:aVariableName
    self shouldPerformCodingStyleChecks ifTrue:[
        self checkLocalVariableNameConventionsFor:aVariableName.
    ]
!

checkForLowercaseVariableName:aVariableName
    |msg|

    self shouldPerformCodingStyleChecks ifFalse:[^ self ].

    aVariableName isUppercaseFirst ifTrue:[
        msg := ('variable "' , aVariableName , '" should be lowercase (by convention)').
        self 
            warning:msg
            doNotShowAgainAction:[ ParserFlags warnAboutNonLowercaseLocalVariableNames:false]
            position:tokenPosition to:source position1Based - 1.

        Tools::ToDoListBrowser notNil ifTrue:[
            self
                notifyTodo:msg position:tokenPosition
                className:(self classToCompileFor name) selector:selector
                severity:#warning priority:#medium 
                equalityParameter:nil
                checkAction:nil. 
        ].
    ].

    "Modified: / 18-10-2006 / 19:38:20 / cg"
!

checkForProperUseOfArticleInVariableName:aVariableName
    |soundsLikeVowel firstCharacterAfterArticle rest whatShouldItBeNamed msg|

    self shouldPerformCodingStyleChecks ifFalse:[^ self ].

    soundsLikeVowel := [:word |
        |soundsLikeVowel firstCharacter|

        soundsLikeVowel := false.
        firstCharacter := word first.
        ('AEIX' includes:firstCharacter) ifTrue:[
            soundsLikeVowel := true.
        ] ifFalse:[
            firstCharacter := word first.
            "/ U and H sound like a vowel, if followed by two more non-vowels
        
            ('UH' includes:firstCharacter) ifTrue:[ 
                word size > 2 ifTrue:[
                    (word at:2) isVowel ifFalse:[
                        (word at:3) isVowel ifFalse:[
                            soundsLikeVowel := true.
                        ].
                    ].
                ].
            ].
            "/ O sound like a vowel, if not followed by 'ne'
            ('O' includes:firstCharacter) ifTrue:[ 
                word size > 2 ifTrue:[
                    (word copyTo:3) asLowercase = 'one' ifFalse:[
                        soundsLikeVowel := true.
                    ].
                ].
            ].
        ].
        soundsLikeVowel.
    ].

    aVariableName size > 4 ifTrue:[ 
        (aVariableName startsWith:'an') ifTrue:[
            firstCharacterAfterArticle := aVariableName at:3.
            firstCharacterAfterArticle isUppercase ifTrue:[
                rest := aVariableName copyFrom:3.
                (soundsLikeVowel value:rest) ifFalse:[
                    whatShouldItBeNamed := 'a' , rest.
                ]
            ].
        ] ifFalse:[
            (aVariableName startsWith:'a') ifTrue:[
                firstCharacterAfterArticle := aVariableName at:2.
                firstCharacterAfterArticle isUppercase ifTrue:[
                    rest := aVariableName copyFrom:2.
                    (soundsLikeVowel value:rest) ifTrue:[
                        whatShouldItBeNamed := 'an' , rest.
                    ].
                ].
            ].
        ].
        whatShouldItBeNamed notNil ifTrue:[
"/            self 
"/                warnCommonMistake:('variable "',aVariableName,'" should be named "',whatShouldItBeNamed,'" (by english language rules)')
"/                position:tokenPosition to:source position1Based - 1.
            msg := ('variable "',aVariableName,'" should be named "',whatShouldItBeNamed,'" (by english language rules)').
            self
                warning:msg
                doNotShowAgainAction:[ ParserFlags warnAboutWrongVariableNames:false]
                position:tokenPosition to:source position1Based - 1.

            Tools::ToDoListBrowser notNil ifTrue:[
                self
                    notifyTodo:msg position:tokenPosition
                    className:(self classToCompileFor name) selector:selector
                    severity:#warning priority:#low 
                    equalityParameter:nil
                    checkAction:nil. 
            ].
        ].
    ].

    "Modified: / 18-10-2006 / 19:41:00 / cg"
!

checkLocalVariableNameConventionsFor:aVariableName
    |msg|

    self shouldPerformCodingStyleChecks ifFalse:[^ self ].

    parserFlags warnAboutVariableNameConventions == true ifTrue:[
        parserFlags warnAboutNonLowercaseLocalVariableNames == true ifTrue:[
            self checkForLowercaseVariableName:aVariableName.
        ].
        parserFlags warnAboutShortLocalVariableNames == true ifTrue:[
            aVariableName size <= 2 ifTrue:[    
                (#(
                    'x' 'y'
                ) includes:aVariableName) 
                ifFalse:[
                    msg := ('short variable name: "' , aVariableName , '"').
                    self 
                        warning:('short variable name: "' , aVariableName , '"')
                        doNotShowAgainAction:[ ParserFlags warnAboutShortLocalVariableNames:false]
                        position:tokenPosition to:source position1Based - 1.

                    Tools::ToDoListBrowser notNil ifTrue:[
                        self
                            notifyTodo:msg position:tokenPosition
                            className:(self classToCompileFor name) selector:selector
                            severity:#warning priority:#medium 
                            equalityParameter:nil
                            checkAction:nil. 
                    ].
                ].
            ].
        ].                                                   
    ].
    parserFlags warnAboutWrongVariableNames == true ifTrue:[
        self checkForProperUseOfArticleInVariableName:aVariableName.
    ].
!

checkMethodArgumentNameConventionsFor:aVariableName
    self shouldPerformCodingStyleChecks ifFalse:[^ self ].

    self checkLocalVariableNameConventionsFor:aVariableName.
!

checkMethodVariableNameConventionsFor:aVariableName
    self shouldPerformCodingStyleChecks ifFalse:[^ self ].

    self checkLocalVariableNameConventionsFor:aVariableName.
!

checkReturnedValues
    | returnsSelf returnsBoolean returnsNonBooleanLiteral|

    self shouldPerformCodingStyleChecks ifFalse:[^ self ].
    parserFlags warnInconsistentReturnValues ifFalse:[^ self].
    returnedValues isNil ifTrue:[^ self].

    returnsBoolean := returnedValues contains:[:node | node isConstant and:[node value isBoolean]].
    returnsNonBooleanLiteral := returnedValues contains:[:node | node isConstant and:[node value isBoolean not]].
    returnsSelf := returnedValues contains:[:node | node isSelf].

    returnsBoolean ifTrue:[
        (returnsNonBooleanLiteral or:[returnsSelf]) ifTrue:[
            self 
                warning:'Possible Error Warning:\\Method returns both boolean and non-boolean values.' withCRs
                doNotShowAgainAction:[ ParserFlags warnInconsistentReturnValues:false ]
                position:1 to:tokenPosition
        ]
    ].

    "Created: / 17.11.2001 / 10:31:03 / cg"
    "Modified: / 17.11.2001 / 10:34:16 / cg"
!

checkSelector:selector for:receiver inClass:cls
    "check whether a method with selector exists in class cls and
     that the method is not obsolete.
     If cls is nil, check all classes for the selector.
     Return an error string on error or nil on success"

    |err mthd implementor implementors allowed|

    self shouldPerformCodingStyleChecks ifFalse:[^ nil ].

    cls isNil ifTrue:[
        SystemBrowser isNil ifTrue:[
            ^ nil
        ].
        "beware, this is sort of slow, especially for the SyntaxHighlighter"
        implementors := SystemBrowser 
                         findImplementorsOf:selector
                         in:(Smalltalk allClasses)
                         ignoreCase:false.
        implementors size == 0 ifTrue:[
            ^ 'is nowhere implemented'
        ].

        (implementors conform:[:eachMethod| eachMethod isObsolete]) ifTrue:[
            ^ 'each implementation of this selector in the system is deprecated'
        ].
        ^ nil
    ].

    mthd := cls lookupMethodFor:selector.
    mthd isNil ifTrue:[
        cls isBehavior ifTrue:[
            cls isMeta ifTrue:[
                mthd := Metaclass lookupMethodFor:selector.
            ].
        ].
    ].

    mthd isNil ifTrue:[
        cls == Boolean ifTrue:[
            mthd := True compiledMethodAt:selector.
            mthd isNil ifTrue:[
                mthd := False compiledMethodAt:selector.
            ].
        ]
    ].
    mthd isNil ifTrue:[
        "if it implements #doesNotUnderstand somewhere, assume it is ok"
        implementor := cls whichClassIncludesSelector:#doesNotUnderstand:.
"/      (implementor isNil or:[implementor == Object]) ifTrue:[
            err := 'is not implemented in ' , cls name allBold
"/      ].
    ] ifFalse:[
        (mthd sends:#shouldNotImplement) ifTrue:[
            mthd messagesSent size == 1 ifTrue:[
                allowed := (cls == classToCompileFor).      "methods in abstract classes may send messages to abstract methods in the same class"
                allowed ifFalse:[
                    err := 'is not (should not be) implemented'
                ]
            ]
        ] ifFalse:[
            (mthd sends:#subclassResponsibility) ifTrue:[
                allowed := (cls == classToCompileFor).      "methods in abstract classes may send messages to abstract methods in the same class"
                allowed ifFalse:[
                    "methods in abstract classes may send messages to abstract methods in meta class"
                    (cls == classToCompileFor class) ifTrue:[
                        allowed := receiver isMessage and:[receiver selector = 'class']    
                    ].
                ].
                allowed ifTrue:[
                    "/ not from cg to stefan: thats wrong - if not implemented in all subclasses,
                    "/ its a bug of the subclass not a bug here - that message send here
                    "/ is perfectly correct. (it is very annoying for a framework developped to get
                    "/ error messages for bugs which are not his...
"/                    (self checkIfAllSubclassesOf:cls implement:selector) ifFalse:[
"/                        "if not all subclasses implement the selector - this is a possible bug"
"/                        allowed := false
"/                    ].
                ].
                allowed ifFalse:[
                    err := 'is subclassResponsibility'
                ].
            ] ifFalse:[mthd isObsolete ifTrue:[
                err := 'is deprecated'.
            ]]
        ].
    ].
    ^ err.
!

checkUnusedMethodVars
    | unused|

    self shouldPerformCodingStyleChecks ifFalse:[^ self ].

    methodVars notNil ifTrue:[
        unused := methodVars select:[:var| var used ~~ true] thenCollect:[:var| var name].
    ].
    unused size > 0 ifTrue:[
        self warnUnused:unused.
    ].

    "Created: / 17.11.2001 / 10:23:47 / cg"
! !

!Parser methodsFor:'dummy-syntax detection'!

markArgumentIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markBadIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markBlockFrom:startPos to:endPos
    "intentionally left empty"

    "Created: / 15-01-2008 / 11:51:35 / cg"
!

markBooleanConstantFrom:pos1 to:pos2
    "intentionally left empty"
!

markBracketAt:pos
    "intentionally left empty"
!

markConstantFrom:pos1 to:pos2
    "intentionally left empty"
!

markGlobalClassIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markGlobalIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markHereFrom:pos1 to:pos2
    "intentionally left empty"
!

markIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markInstVarIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markLocalIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markMethodSelectorFrom:pos1 to:pos2
    "intentionally left empty"
!

markParenthesisAt:pos
    "intentionally left empty"
!

markReturnAt:pos
    "intentionally left empty"
!

markSelector:sel from:pos1 to:pos2 receiverNode:aNode
    "intentionally left empty"
!

markSelfFrom:pos1 to:pos2
    "intentionally left empty"
!

markSuperFrom:pos1 to:pos2
    "intentionally left empty"
!

markUnknownIdentifierFrom:pos1 to:pos2
    "intentionally left empty"
!

markVariable:v
    "intentionally left empty"
!

markVariable:v from:pos1 to:pos2
    "intentionally left empty"
! !

!Parser methodsFor:'error correction'!

addDoItTemporary:varName
    |holder|

    doItTemporaries isNil ifTrue:[
        doItTemporaries := IdentityDictionary new.
    ].
    doItTemporaries at:varName asSymbol put:(holder := ValueHolder new).
    ^ holder
!

alreadyWarnedUnimplementedSelectors
    alreadyWarnedUnimplementedSelectors isNil ifTrue:[
        alreadyWarnedUnimplementedSelectors := Set new
    ].
    ^ alreadyWarnedUnimplementedSelectors
!

askForCorrection:aString fromList:aList
    "launch a selection box, which allows user to enter correction.
     return newString or nil (for abort)"

    |box rslt|

    "in systems without widgets ..."
    ListSelectionBox isNil ifTrue:[
        ^ self confirm:aString
    ].
    box := ListSelectionBox title:aString.
    box initialText:(aList at:1).
    box list:aList.
    box okText:'Correct'.
    box action:[:aString | rslt := aString].
    box showAtPointer.
    box destroy.
    ^ rslt
!

askForCorrection:aString fromList:aList for:originalSelector
    "launch a selection box, which allows user to enter correction.
     return newString or nil (for abort)"

    |box rslt|

    "in systems without widgets ..."
    ListSelectionBox isNil ifTrue:[
        ^ self confirm:aString
    ].
    box := ListSelectionBox title:aString.
    box initialText:(aList at:1).
    box list:aList.
    box okText:'Correct'.
    box action:[:aString | rslt := aString].
    box addButton:(Button label:'Keep Selector' action:[rslt := originalSelector. box hide]) after:(box okButton).
    box showAtPointer.
    box destroy.
    ^ rslt
!

askForVariableTypeWhenDeclaringUndefined:varName
    |l how varNameIsLowercase choice holder newClass owningClass|

    l := #().
    how := #().

    varNameIsLowercase := (varName at:1) isLowercase.

    "/ BlockVar, InstVar and classInstVar not yet implemented
    varNameIsLowercase ifTrue:[
"/            currentBlock notNil ifTrue:[
"/                l := l , #( 'Block local' ).
"/                how := how , #( BlockVariable ).
"/            ].
        selector notNil ifTrue:[
            l := l , #( 'Method Local Variable' ).
            how := how , #( MethodVariable ).
        ].
        (classToCompileFor notNil
        and:[classToCompileFor isMeta not
        and:[classToCompileFor isBuiltInClass not 
        and:[(self isDoIt not)]]]) ifTrue:[
            l := l copyWith:'Instance Variable'.
            how := how copyWith: #InstanceVariable.
        ].
    ] ifFalse:[
        l := l , #( 'New Class' 'Global' 'NameSpace' ).
        how := how , #( NewClass GlobalVariable NameSpace ).

        (classToCompileFor notNil
        and:[classToCompileFor isBuiltInClass not
        and:[self isDoIt not]]) ifTrue:[
            classToCompileFor isMeta ifTrue:[
                l := l , #('Class Instance Variable').
                how := how , #( ClassInstanceVariable).
            ].
            l := l , #('Class Variable' ).
            how := how , #( ClassVariable).
            l := l , #('Private Class' ).
            how := how , #( PrivateClass).
        ]
    ].
    self isDoIt ifTrue:[
        l size > 0 ifTrue:[
            l := l ,  #( '-' ).
            how := how , #( nil ).
        ].
        l := l , #( 'Workspace Variable' 'DoIt Temporary').
        how := how , #( WorkspaceVariable DoItTemporary ).
    ].

    l size > 0 ifTrue:[
        l := (Array with:('Declare ' , varName allBold , ' as:') 
                    with:'-'
             ) , l.
        how := #(nil nil) , how.
        choice := (PopUpMenu labels:l) startUp.
        (choice notNil and:[choice > 0]) ifTrue:[
            choice := how at:choice.

            choice == #WorkspaceVariable ifTrue:[
                holder := Workspace addWorkspaceVariable:varName.
                ^ VariableNode type:#WorkspaceVariable holder:holder name:varName
            ].
            choice == #DoItTemporary ifTrue:[
                holder := self addDoItTemporary:varName.
                ^ VariableNode type:#DoItTemporary holder:holder name:varName
            ].

            choice == #GlobalVariable ifTrue:[
                Smalltalk at:varName asSymbol put:nil.
                ^ VariableNode globalNamed:varName
            ].

            choice == #NewClass ifTrue:[
                newClass := Object subclass:varName asSymbol
                       instanceVariableNames:''
                       classVariableNames:''
                       poolDictionaries:''
                       category:'* As yet uncategorized *'.
                ^ VariableNode globalNamed:newClass name
            ].

            choice == #PrivateClass ifTrue:[
                owningClass := classToCompileFor theNonMetaclass.
                newClass := Object subclass:varName asSymbol
                       instanceVariableNames:''
                       classVariableNames:''
                       poolDictionaries:''
                       privateIn:owningClass.
                ^ VariableNode type:#PrivateClass class:owningClass name:newClass name
            ].

            choice == #NameSpace ifTrue:[
                NameSpace name:varName.
                ^ VariableNode globalNamed:varName
            ].

            choice == #ClassVariable ifTrue:[
                classToCompileFor theNonMetaclass addClassVarName:varName.
                ^ VariableNode type:#ClassVariable class:classToCompileFor theNonMetaclass name:varName
            ].

            choice == #InstanceVariable ifTrue:[
                classToCompileFor theNonMetaclass addInstVarName:varName.
                "/ ST/X special - classToCompileFor is obsoleted
                classToCompileFor := Smalltalk classNamed:(classToCompileFor name).
                RestartCompilationSignal raise.    
                "/ not reached - restarted compile will not arrive here again
                self error:'restart compile failed'.
            ].

            choice == #ClassInstanceVariable ifTrue:[
                classToCompileFor theMetaclass addInstVarName:varName.
                "/ ST/X special - classToCompileFor is obsoleted
                classToCompileFor := Smalltalk classNamed:(classToCompileFor name).
                RestartCompilationSignal raise.    
                "/ not reached - restarted compile will not arrive here again
                self error:'restart compile failed'.
            ].

            choice == #MethodVariable ifTrue:[
                |varIndex var endLocalsPos posToInsert ins|

                localVarDefPosition size == 2 ifTrue:[
                    endLocalsPos := posToInsert := localVarDefPosition at:2.
                    ins := ' ' , varName.
                ] ifFalse:[
                    endOfSelectorPosition notNil ifTrue:[
                         posToInsert := beginOfBodyPosition.
                         ins := '|' , varName , '|' , Character cr asString , Character cr asString.
                         ins := ins , (String new:(requestor colOfCharacterPosition:posToInsert)-1).   
                    ]
                ].
                posToInsert notNil ifTrue:[
                    requestor 
                        insertString:ins
                        atCharacterPosition:posToInsert.

                    endLocalsPos notNil ifTrue:[
                        localVarDefPosition at:2 put:(endLocalsPos + varName size + 1).

                        methodVarNames := methodVarNames copyWith:varName.
                        methodVars := methodVars copyWith:(var := Variable new name:varName).
                    ] ifFalse:[
                        localVarDefPosition := Array with:posToInsert with:posToInsert+varName size+1.

                        methodVarNames := Array with:varName.
                        methodVars := Array with:(var := Variable new name:varName).
                    ].
                    correctedSource := requestor currentSourceCode.
                    source := (ReadStream on:correctedSource)
                                  position:(source position1Based + ins size).

                    varIndex := methodVarNames size.
                    var used:true.
                    ^ VariableNode type:#MethodVariable
                                   name:varName
                                   token:var
                                   index:varIndex
                ].
            ].
            self warning:'Sorry - unimplemented (adding ' , choice , ')'.
        ].
    ].
    ^ nil.

    "Modified: / 05-09-2006 / 12:26:13 / cg"
!

checkIfAllSubclassesOf:aClass implement:aSelector
    ^ aClass subclasses conform:[:cls | (cls implements:aSelector)]

    "Modified: / 13-09-2006 / 11:40:52 / cg"
!

correctByDeleting
    "correct (by deleting token) if user wants to;
     return #Error if there was no correction;
     nil if there was one."

    |selectionSize|

    (self confirm:'confirm deleting') ifFalse:[^ #Error].

    "
     tell requestor (i.e. CodeView) about the change
     this will update what the requestor shows.
    "
    selectionSize := requestor selection size.
    requestor deleteSelection.

    "
     get the updated source-string 
     which is needed, when we eventually install the new method
    "
    correctedSource := requestor currentSourceCode.
    "/ update the current source position
    source := (ReadStream on:correctedSource)
                  position:(source position1Based - selectionSize).

    ^ nil

    "Modified: / 22.1.1998 / 16:39:11 / stefan"
!

correctSelector:aSelectorString message:msg positions:posVector in:aClassOrNil for:receiverNode
    "notify error and correct if user wants to;
     return #Error if there was no correction 
     or a ParseNode as returned by variable"

    |correctIt suggestedNames newSelector className classToGenerateCode pos1 pos2|

    pos1 := posVector first start.
    pos2 := posVector last stop.

    (self alreadyWarnedUnimplementedSelectors includes:aSelectorString) ifTrue:[
        ^ aSelectorString
    ].

    "
     sorry, but I cannot handle keywords with more than one-part
     currently (too much work - maybe Ill do it later when everything else works :-)
    "
    (aSelectorString occurrencesOf:$:) > 1 ifTrue:[
        self warning:msg position:pos1 to:pos2.
        alreadyWarnedUnimplementedSelectors add:aSelectorString.
        ^ aSelectorString
    ].

    correctIt := self correctableSelectorWarning:msg position:pos1 to:pos2.
    correctIt == #generate ifTrue:[
        receiverNode isSelf ifTrue:[
            classToGenerateCode := classToCompileFor
        ] ifFalse:[
            receiverNode isVariable ifTrue:[
                receiverNode isGlobal ifTrue:[
                    classToGenerateCode := receiverNode evaluate.
                    classToGenerateCode isBehavior ifTrue:[
                        classToGenerateCode :=  classToGenerateCode theMetaclass.
                    ] ifFalse:[
                        classToGenerateCode := nil
                    ].
                ].
            ]
        ].
        classToGenerateCode isNil ifTrue:[
            className := Dialog request:'Generate code in class:' initialAnswer:classToCompileFor name.
            className size == 0 ifTrue:[
                ^ aSelectorString
            ].
            classToGenerateCode := Smalltalk at:className asSymbol.
            classToGenerateCode isNil ifTrue:[
                self warn:'No such class.'.
                ^ aSelectorString
            ].
        ].
        (classToGenerateCode includesSelector:aSelectorString asSymbol) ifFalse:[
            |code category wantSetter wantGetter|

            wantSetter := wantGetter := false.

            (aSelectorString isKeywordSelector 
            and:[aSelectorString numArgs == 1
            and:[classToGenerateCode instVarNames includes:(aSelectorString copyWithoutLast:1)]]) ifTrue:[
                "/ want a setter ?
                wantSetter := Dialog confirmWithCancel:('Create a setter for %1 ?' bindWith:(aSelectorString copyWithoutLast:1) allBold).
                wantSetter isNil ifTrue:[^ aSelectorString].                 
            ] ifFalse:[
                (aSelectorString isUnarySelector 
                and:[classToGenerateCode instVarNames includes:aSelectorString]) ifTrue:[
                    "/ want a getter ?
                    wantGetter := Dialog confirmWithCancel:('Create a getter for %1 ?' bindWith:aSelectorString allBold).
                    wantGetter isNil ifTrue:[^ aSelectorString].                 
                ]
            ].
            wantSetter ifTrue:[
                code := ('%1:something\    %1 := something.' bindWith:(aSelectorString copyWithoutLast:1)) withCRs.
                category := 'accessing'.
            ] ifFalse:[
                wantGetter ifTrue:[
                    code := ('%1\    ^ %1.' bindWith:aSelectorString) withCRs.
                    category := 'accessing'.
                ] ifFalse:[
                    code := (self class methodSpecificationForSelector:aSelectorString) , '\    self shouldImplement' withCRs.
                    category := Compiler defaultMethodCategory.
                ].
            ].

            "do not overwrite an already existant (deprecated) method"
            classToGenerateCode
                compile:code
                classified:category.
        ].
        correctIt := false.
    ].
    correctIt ifFalse:[
        alreadyWarnedUnimplementedSelectors add:aSelectorString.
        ^ aSelectorString
    ].

    suggestedNames := self findBestSelectorsFor:aSelectorString in:aClassOrNil.
    suggestedNames notNil ifTrue:[
        newSelector := self askForCorrection:'Correct Selector to: ' fromList:suggestedNames for:aSelectorString.
        newSelector isNil ifTrue:[AbortSignal raise "^ aSelectorString"].
    ] ifFalse:[
        self information:'no good correction found'.
        ^ aSelectorString
    ].

    "
     tell requestor (i.e. CodeView) about the change
     this will update what the requestor shows.
    "
    requestor replaceSelectionBy:newSelector keepCursor:false.
    "
     get the updated source-string 
     which is needed, when we eventually install the new method
    "
    correctedSource := requestor currentSourceCode.
    source := (ReadStream on:correctedSource)
                  position:(source position1Based + 1 + (newSelector size - aSelectorString size)).
"/ Parser murks.
    ^ newSelector

    "Modified: / 22.1.1998 / 16:36:04 / stefan"
    "Created: / 19.1.2000 / 16:34:01 / cg"
    "Modified: / 19.1.2000 / 16:34:55 / cg"
!

correctSourceByDeletingFrom:start to:stop
    "correct (by deleting token) if user wants to;
     return #Error if there was no correction;
     nil if there was one."

    |deleteSize localDefsStart localDefsStop newPos|

    "
     tell requestor (i.e. CodeView) about the change
     this will update what the requestor shows.
    "
    deleteSize := stop - start + 1.
    requestor deleteFromCharacterPosition:start to:stop.

    "
     get the updated source-string 
     which is needed, when we eventually install the new method
    "
    correctedSource := requestor currentSourceCode.

    "/ update the current source position
    source atEnd ifTrue:[
        newPos := correctedSource size.
    ] ifFalse:[
        source position1Based >= stop ifTrue:[
            newPos := source position1Based - deleteSize
        ] ifFalse:[
            source position1Based < start ifTrue:[
                newPos := source position1Based
            ] ifFalse:[
                newPos := start
            ].
        ]
    ].
    source := (ReadStream on:correctedSource) position1Based:newPos.

    localDefsStart := localVarDefPosition at:1.
    localDefsStop := localVarDefPosition at:2.

    localDefsStop <= start ifTrue:[^ self].
    localDefsStart >= stop ifTrue:[^ self].

    (localDefsStart >= start and:[localDefsStop <= stop]) ifTrue:[
        localVarDefPosition := nil.
        ^ self
    ].  

    "/ must update
    (start > localDefsStart and:[stop < localDefsStop]) ifTrue:[
        localVarDefPosition at:2 put:(localDefsStop - (stop-start+1)).
        ^ self.
    ].
    ^ self
!

correctVariable:varName atPosition:pos1 to:pos2
    "notify error and correct if user wants to;
     return #Error if there was no correction 
     or a ParseNode as returned by variable"

    |correctIt suggestedNames newName rslt
     varNameIsLowercase undeclared boldName|

    varNameIsLowercase := (varName at:1) isLowercase.

    correctIt := self undefError:varName position:pos1 to:pos2.
    correctIt == #Error ifTrue:[
        ^ #Error
    ].

    correctIt == #declare ifTrue:[
        "/ declare it
        rslt := self askForVariableTypeWhenDeclaringUndefined:varName.
        rslt notNil ifTrue:[
            ^ rslt
        ].
        correctIt := #continue. 
    ].
    (correctIt == false or:[correctIt == #continue]) ifTrue:[
        "/ no correction wanted.

        "/ lowerCase vars are added to the Undeclared dictionary,
        "/ allowing easy search for bad-spots later.
        boldName := varName allBold.

        varNameIsLowercase ifTrue:[
            undeclared := Smalltalk at:#Undeclared.
            ((undeclared notNil)
            and:[(undeclared includes:varName asSymbol)]) ifFalse:[ 
                self warning:('Adding ''' , boldName , ''' as Undeclared.\\Remember to fix that later.') withCRs position:pos1 to:pos2.
            ].
            ^ self defineAsUndeclaredVariable:varName
        ].

        "/ upperCase vars are declared as global
        parserFlags warnings ifTrue:[
            (warnedUndefVars isNil or:[(warnedUndefVars includes:varName) not]) ifTrue:[
                (warnedUnknownNamespaces isNil or:[(warnedUnknownNamespaces includes:varName) not]) ifTrue:[
                    self warning:('adding ''' , boldName , ''' as Global.') withCRs position:pos1 to:pos2.
                ]
            ].
        ].
        ^ VariableNode globalNamed:varName
    ].

    (correctIt isKindOf:ParseNode) ifTrue:[
        ^ correctIt
    ].

    suggestedNames := self findBestVariablesFor:varName.
    suggestedNames isNil ifTrue:[
        self information:'No good correction found'.
        ^ #Error
    ].

    newName := self askForCorrection:'Correct Variable to: ' fromList:suggestedNames.
    newName isNil ifTrue:[^ #Error].
"
        newName := suggestedNames at:1.
        (self confirm:('confirm correction to: ' , newName)) ifFalse:[^ #Error].
"

    "
     tell requestor (i.e. CodeView) about the change
     this will update what the requestor shows.
    "
    requestor replaceSelectionBy:newName.
    "
     get the updated source-string 
     which is needed, when we eventually install the new method
    "
    correctedSource := requestor currentSourceCode.
    source := (ReadStream on:correctedSource)
                  position:(source position1Based + newName size - tokenName size).

    "redo parse with new value"
    token := tokenName := newName.
    rslt := self variableOrError:tokenName.

    "/ failed again ?
    rslt == #Error ifTrue:[
        "/ install as Undeclared:<name>, remember in #undeclared

        rslt := self defineAsUndeclaredVariable:varName
    ].
    ^ rslt

    "Modified: / 22-01-1998 / 16:34:01 / stefan"
    "Modified: / 05-09-2006 / 12:27:38 / cg"
!

defineAsUndeclaredVariable:aName
    "define varName as undeclared variable
     (actually, it will be installed as a funny global named 'Undeclared:::<name>').
     You can browse for methods with undeclareds by searching for global accesses
     to 'Undeclared:::*' (or use the search-undeclared item in the launchers menu)."

    |varName undeclared|

    varName := aName.

    "/ install as Undeclared:<name>, remember in Undeclared

    undeclared := Smalltalk at:#Undeclared.
    undeclared isNil ifTrue:[
        Smalltalk at:#Undeclared put:(undeclared := IdentitySet new).
    ].
    undeclared add:tokenName asSymbol.
    varName := (Smalltalk undeclaredPrefix) , tokenName.
    varName := varName asSymbol.
    Smalltalk at:varName put:nil.

    parseForCode ifFalse:[self rememberGlobalUsed:aName].

    ^ VariableNode globalNamed:varName

    "Modified: / 31.10.1997 / 01:16:03 / cg"
!

deleteDefinitionOf:varName in:defStartPos to:defEndPos
    "this removes the definition of varName from the declaration part i.e.
     if the source was '... | foo bar baz |...'
     deleting the var 'bar' changes the source to '... | foo baz |...'.
     The code below tries to be somewhat smart w.r.t. spaces by
     trying to remove the whiteSpace around the removed variable also.
     However, this seems to not always work correctly"

    |source startSearch pos pos2 nextChar varSlot p p2|

    varSlot := methodVars detect:[:var | var name = varName].
    methodVars removeIdentical:varSlot.

    source := requestor currentSourceCode.
    startSearch := defStartPos+1.

    [true] whileTrue:[
        |prevChar isFirstVar didPassEndOfLine|

        "/ search this name's position in the declaration part ...
        pos := source indexOfSubCollection:varName startingAt:startSearch ifAbsent:0.
        (pos == 0 or:[pos >= defEndPos]) ifTrue:[
            self error:'should not happen' mayProceed:true.
            ^ self.
        ].

        pos2 := pos + varName size - 1.
        pos > 1 ifTrue:[
            prevChar := source at:pos-1.
        ].
        (prevChar isNil or:[prevChar isLetterOrDigit not]) ifTrue:[
            nextChar := source at:pos2+1.
            nextChar isLetterOrDigit ifFalse:[
                "/ halfway intuitive space-removal behavior;
                "/ if there was a space after/before the |-char,
                "/ leave it; otherwise remove it.
                isFirstVar := pos == (defStartPos+1).
                (source at:pos-1) isSeparator ifTrue:[
                    pos := pos - 1.
                    [ (source at:pos-1) isSeparator] whileTrue:[
                        pos := pos - 1.
                    ].
                    (source at:pos-1) == $| ifTrue:[
                        "/ there was a space before - leave it
                        pos := pos + 1.
                        isFirstVar := true.
                    ]
                ].

                (source at:pos2+1) isSeparator ifTrue:[
                    didPassEndOfLine := (source at:pos2+1) == Character cr.
                    pos2 := pos2 + 1.
                    [ (source at:pos2+1) isSeparator] whileTrue:[
                        (source at:pos2+1) == Character cr ifTrue:[ didPassEndOfLine := true ].
                        pos2 := pos2 + 1.
                    ].

                    didPassEndOfLine ifFalse:[    
                        (source at:pos2+1) == $" ifTrue:[
                            "/ comment follows - assume it belongs to the removed variable
                            pos2 := pos2 + 1.
                            (source at:pos2+1) == $/ ifTrue:[
                                "/ EOL comment
                                [ (source at:pos2+1) == Character cr ] whileFalse:[
                                    pos2 := pos2 + 1.
                                ].
                                pos2 := pos2 + 1.
                            ] ifFalse:[
                                "/ regular comment
                                [ (source at:pos2+1) == $" ] whileFalse:[
                                    pos2 := pos2 + 1.
                                ].
                                pos2 := pos2 + 1.
                            ].
                            [ (source at:pos2+1) isSeparator] whileTrue:[
                                (source at:pos2+1) == Character cr ifTrue:[ didPassEndOfLine := true ].
                                pos2 := pos2 + 1.
                            ].
                        ]
                    ].

                    (source at:pos2+1) == $| ifTrue:[
                        "/ there was a space after - leave it
                        pos2 := pos2 - 1.
                    ] ifFalse:[
                        isFirstVar ifFalse:[
                            pos2 := pos2 - 1.
                        ]
                    ].
                ].

                "/ if this was the last, remove empty var-declaration completely
                ((source at:pos-1) == $|
                and:[ (source at:pos2+1) == $| ]) ifTrue:[
                    pos := pos - 1.
                    pos2 := pos2 + 1.
                    "/ see if that gives us an empty line
                    p := pos.
                    p2 := pos2.

                    [(source at:p-1) == Character space] whileTrue:[ p := p - 1 ].
                    [(source at:p2+1) == Character space] whileTrue:[ p2 := p2 + 1 ].
                    ((source at:p-1) == Character cr and:[ (source at:p2+1) == Character cr]) ifTrue:[
                        pos := p-1.
                        pos2 := p2.
                        (((source at:pos-1) == Character cr) and:[((source at:pos-2) == Character cr)]) 
                            ifTrue:[ pos := pos - 1 ]
                            ifFalse:[ 
                                (((source at:pos2+1) == Character cr) and:[((source at:pos2+2) == Character cr)]) ifTrue:[ 
                                    pos2 := pos2 + 1 ]].
                    ].
                ].

                self correctSourceByDeletingFrom:pos to:pos2.
                ^ self.
            ].
        ].
        startSearch := pos2 + 1.
    ]

    "Modified: / 18-07-2006 / 08:56:25 / cg"
!

findBestSelectorsFor:aString
    "collect known selectors with their spelling distances to aString;
     return the 10 best suggestions"

    ^ self class findBestSelectorsFor:aString 

    "Time millisecondsToRun:[Parser new findBestSelectorsFor:'foo']"
    "Parser new findBestSelectorsFor:'findBestSel'"
    "Parser new findBestSelectorsFor:'fildBestSelectrFr'"
!

findBestSelectorsFor:aString in:aClassOrNil
    "collect known selectors with their spelling distances to aString;
     return the 10 best suggestions. If the argument, aClassOrNil is not nil,
     the message is assumed to be sent to instances of that class (i.e. offer
     corrections from that hierarchy only)"

    ^ self class findBestSelectorsFor:aString in:aClassOrNil
!

findBestVariablesFor:aString
    "collect known variables with their spelling distances to aString;
     return the 10 best suggestions"

    |names dists searchBlock args vars "aClass className baseClass" 
     n instVarNames classVarNames spellAgainstNodeAction spellAgainstAction|

    names := OrderedCollection new.
    dists := OrderedCollection new.

    spellAgainstAction := 
        [:givenName |
            |dist|

            names add:givenName.
            dist := aString spellAgainst:givenName.
            (aString startsWith:givenName) ifTrue:[
                dist := dist + (givenName size * 10).
            ].
            dists add:dist
        ].

    spellAgainstNodeAction := 
            [:aVarNode |
                spellAgainstAction value:(aVarNode name).
            ].

    "block arguments"
    searchBlock := currentBlock.
    [searchBlock notNil] whileTrue:[
        args := searchBlock arguments.
        args notNil ifTrue:[
            args do:spellAgainstNodeAction
        ].

        vars := searchBlock variables.
        vars notNil ifTrue:[
            vars do:spellAgainstNodeAction
        ].
        searchBlock := searchBlock home
    ].

    "method-variables"
    methodVars notNil ifTrue:[
        methodVarNames do:spellAgainstAction
    ].

    "method-arguments"
    methodArgs notNil ifTrue:[
        methodArgNames do:spellAgainstAction
    ].

    "instance-variables"
    classToCompileFor notNil ifTrue:[
        self classesInstVarNames do:spellAgainstAction
    ].

    "class-variables"
    classToCompileFor notNil ifTrue:[
        self classesClassVarNames do:spellAgainstAction.

"/        aClass := classToCompileFor.
"/        aClass isMeta ifTrue:[
"/            className := aClass name.
"/            className := className copyWithoutLast:5.
"/            baseClass := Smalltalk at:(className asSymbol).
"/            baseClass notNil ifTrue:[
"/                aClass := baseClass
"/            ]
"/        ].
"/        [aClass notNil] whileTrue:[
"/            (aClass classVarNames) do:[:classVarName |
"/                names add:classVarName.
"/                dists add:(aString spellAgainst: "levenshteinTo:"classVarName)
"/            ].
"/            aClass := aClass superclass
"/        ]

    ].

    "globals"
    Smalltalk keysDo:[:aKey |
        |globalVarName parts|

        globalVarName := aKey asString.

        "only compare strings where length is about right"
        ((globalVarName size - aString size) abs < 3) ifTrue:[
            spellAgainstAction value:globalVarName.
        ].
        (globalVarName includes:$:) ifTrue:[
            parts := globalVarName asCollectionOfSubCollectionsSeparatedByAll:'::'.
            parts size > 1 ifTrue:[
                parts do:[:eachPart |
                    |dist|
                    ((eachPart size - aString size) abs < 3) ifTrue:[
                        names add:globalVarName.
                        dist := aString spellAgainst:eachPart.
                        (aString startsWith:eachPart) ifTrue:[
                            dist := dist + (eachPart size * 10).
                        ].
                        dists add:dist
                    ].
                ].
            ].
        ].
    ].

    "misc"
    #('self' 'super' 'nil' 'thisContext') do:spellAgainstAction.

    (dists size ~~ 0) ifTrue:[
        dists sortWith:names.
        dists := dists reverse.             
        names := names reverse.
        n := names size min:10.
        names := names copyTo:n.

        "if it starts with a lower case character, add all local & instvar names"
        (aString at:1) isLowercase ifTrue:[
            methodVarNames size > 0 ifTrue:[
                names add:'---- method locals ----'.
                methodVarNames asSortedCollection do:[:methodVarName |
                    names add:methodVarName.
                ].
            ].


            methodArgs size > 0 ifTrue:[
                names add:'---- method arguments ----'.
                methodArgNames asSortedCollection do:[:methodArgName |
                    names add:methodArgName.
                ]
            ].
            classToCompileFor notNil ifTrue:[
                instVarNames := OrderedCollection new.
                self classesInstVarNames asSortedCollection do:[:instVarName |
                    (instVarNames includes:instVarName) ifFalse:[
                        instVarNames add:instVarName.
                    ]
                ].

                instVarNames size > 0 ifTrue:[
                    (classToCompileFor notNil and:[classToCompileFor isMeta]) ifTrue:[
                        names add:'---- class instance variables ----'.
                    ] ifFalse:[
                        names add:'---- instance variables ----'.
                    ].
                    instVarNames do:[:instVarName |
                        (names includes:instVarName) ifFalse:[
                            names add:instVarName.
                        ]
                    ]
                ].

                classVarNames := OrderedCollection new.
                self classesClassVarNames asSortedCollection do:[:classVarName |
                    (classVarNames includes:classVarName) ifFalse:[
                        classVarNames add:classVarName.
                    ]
                ].

                classVarNames size > 0 ifTrue:[
                    names add:'---- class variables ----'.
                    classVarNames do:[:classVarName |
                        (names includes:classVarName) ifFalse:[
                            names add:classVarName.
                        ]
                    ]
                ].
            ].
        ].

        ^ names
    ].
    ^ nil

    "Modified: 11.1.1997 / 21:28:28 / cg"
!

selectorCheck:aSelectorString for:receiver position:pos1 to:pos2
    ^ self selectorCheck:aSelectorString for:receiver positions:(Array with:(pos1 to:pos2)).
!

selectorCheck:aSelectorString for:receiver positions:posVector
    "just a quick check: if a selector is totally unknown as a symbol, 
     has the same name as a variable, cannot be understood or is obsolete.
     Simple, but catches many typos"

    |isSyntaxHighlighter err selectorSymbol rec names recType selClass newSelector nm nowhereImplemented 
     pos1 pos2 canDefine|

    isSyntaxHighlighter := self isSyntaxHighlighter.
    "
     if compiling lazy, or errors are to be ignored, or there
     is no requestor, do not check
    "
    isSyntaxHighlighter ifFalse:[
        (LazyCompilation == true) ifTrue:[^ aSelectorString].
        (ignoreErrors or:[ignoreWarnings]) ifTrue:[^ aSelectorString].
        (requestor isNil or:[requestor isStream]) ifTrue:[^ aSelectorString].
        parserFlags warnings ifFalse:[^ aSelectorString].
    ].
    "/ do not check messages to undefined variables...
    (receiver isVariable and:[receiver isUndeclared]) ifTrue:[
        ^ aSelectorString
    ].
    self isDoIt ifTrue:[
        ^ aSelectorString
    ].

    canDefine := false.

    pos1 := posVector first start.
    pos2 := posVector last stop.

    aSelectorString = '#' ifTrue:[
        self warnPossibleIncompatibility:'''#'' might not be a valid selector in other smalltalk systems' position:pos1 to:pos2.
    ].

    "
     check if the selector is known at all
     - if not, it cannot be understood
    "
    nowhereImplemented := false.

    selectorSymbol := aSelectorString asSymbolIfInterned.
    selectorSymbol isNil ifTrue:[
        nowhereImplemented := true.
    ] ifFalse:[
"/ temporarily disabled - too slow.
"/        self isSyntaxHighlighter ifTrue:[
"/            nowhereImplemented := (self class implementedInAnyClass:selectorSymbol) not.
"/        ]
    ].

    nowhereImplemented ifTrue:[
        isSyntaxHighlighter ifFalse:[
            self classToCompileFor notNil ifTrue:[
                Tools::ToDoListBrowser notNil ifTrue:[
                    "/ experimental
                    self 
                        notifyTodo:('"%1" is nowhere implemented' bindWith:aSelectorString) position:posVector first
                        className:(self classToCompileFor name) selector:selector
                        severity:#warning priority:#high 
                        equalityParameter:aSelectorString
                        checkAction:[:e |
                            e problemMethod notNil
                            and:[(e problemMethod sends:aSelectorString asSymbol)
                            and:[self class implementedInAnyClass:aSelectorString]] ]
                ].
            ].
        ].

        err := ' is currently nowhere implemented'.

        "
         if the selector has the name of a variable, use another message
        "
        ((methodVarNames notNil and:[methodVarNames includes:aSelectorString])
          or:[(methodArgNames notNil and:[methodArgNames includes:aSelectorString])
          or:[classToCompileFor notNil
              and:[((names := self classesInstVarNames) notNil and:[names includes:aSelectorString])
                   or:[((names := self classesClassInstVarNames) notNil and:[names includes:aSelectorString])
                   or:[(names := self classesClassVarNames) notNil and:[names includes:aSelectorString]
        ]]]]]) ifTrue:[
            err := ' is currently nowhere implemented ..
.. but a variable with that name is defined. 

Missing ''.'' after the previous expression 
or missing keyword/receiver before that word ?'.
        ].
    ] ifFalse:[
        receiver notNil ifTrue:[
            selClass := self typeOfNode:receiver.
            selClass notNil ifTrue:[
                "this could be performed if selClass isNil, but it is too slow"
                err := self checkSelector:selectorSymbol for:receiver inClass:selClass.
            ].

            err notNil ifTrue:[
                isSyntaxHighlighter ifFalse:[
                    self classToCompileFor notNil ifTrue:[
                        Tools::ToDoListBrowser notNil ifTrue:[
                            "/ experimental
                            self
                                notifyTodo:(selectorSymbol ,' ',err) position:posVector first
                                className:(self classToCompileFor name) selector:selector
                                severity:#warning priority:#high 
                                equalityParameter:selectorSymbol
                                checkAction:[:e |
                                    |selClass|

                                    selClass := self typeOfNode:receiver.
                                    e problemMethod notNil
                                    and:[(e problemMethod sends:aSelectorString asSymbol)
                                    and:[(self checkSelector:selectorSymbol for:receiver inClass:selClass) notNil]]].
                        ].
                    ].
                ].
            ].

            (receiver isConstant or:[receiver isBlock]) ifTrue:[
                err notNil ifTrue:[
                    err := err, ' in ' , selClass name , ' or any of its superclasses'.
                ].
            ] ifFalse:[(((recType := receiver type) == #GlobalVariable)
                        or:[recType == #PrivateClass]) ifTrue:[
                rec := receiver evaluate. 
                "/ dont check autoloaded classes - it may work after loading
                (rec isNil 
                 or:[rec isBehavior and:[rec isLoaded not]]) ifTrue:[
                    ^ aSelectorString
                ].

                err notNil ifTrue:[
                    (rec isBehavior
                     and:[rec theNonMetaclass name = receiver name]) ifTrue:[
                        err := err, ' in ' , rec theNonMetaclass name.
                    ] ifFalse:[
                        err := err, ' in currently assigned value (is currently ' , rec classNameWithArticle , ')'.
                    ]
                ].
            ] ifFalse:[receiver isSuper ifTrue:[
                receiver isHere ifFalse:[
                    err notNil ifTrue:[
                        err := err, ' in superclass chain'.
                    ].
                ] ifTrue:[
                    err notNil ifTrue:[
                        err := err, ' in this class or superclass chain'.
                    ].
                ]
            ] ifFalse:[receiver isSelf ifTrue:[
                err notNil ifTrue:[ 
                    |subErr|

                    "/ understood by all subclasses ?
                    classToCompileFor allSubclassesDo:[:eachSubclass |
                        subErr isNil ifTrue:[
                            selClass := eachSubclass.
                            subErr := self checkSelector:selectorSymbol for:receiver inClass:selClass.     
                        ].
                    ].   
                    subErr notNil ifTrue:[
                        err := subErr, ' in this class, superclass chain or all subclasses'
                    ] ifFalse:[
                        err := err, ' in this class or superclass chain'.
                    ].
                    canDefine := true.
                ].
            ] ifFalse:[(receiver isUnaryMessage
                        and:[receiver selector == #class
                        and:[receiver receiver isSelf]]) ifTrue:[
                "its a message to self class - can check this too ..."
                err notNil ifTrue:[
                    classToCompileFor isMeta ifTrue:[
                        err := err, ' for the classes class'.
                        (self checkSelector:selectorSymbol for:receiver inClass:classToCompileFor) isNil ifTrue:[
                            err := err, '...\\...but its implemented for the class itself. You probably do not want the #class message here.'.
                            err := err withCRs.
                        ].
                    ] ifFalse:[
                        err := err, ' for my class'.
                        (self checkSelector:selectorSymbol for:receiver inClass:classToCompileFor) isNil ifTrue:[
                            err := err, '...\\...but its implemented for instances. You may want to remove the #class message.'.
                            err := err withCRs.
                        ].
                    ].
                ].
            ] ifFalse:[(receiver isMethodVariable and:[receiver token type isNil]) ifTrue:[
                "if it is an uninitialized variable ..."
                ((modifiedLocalVars isNil or:[(modifiedLocalVars includes:receiver name) not])
                 and:[hasPrimitiveCode not
                 and:[currentBlock isNil
                 and:[alreadyWarnedUninitializedVars isNil 
                      or:[(alreadyWarnedUninitializedVars includes:receiver name) not]]]]) 
                ifTrue:[
                    ((#(at: at:put: basicAt: basicAt:put:) includes:selectorSymbol) 
                     or:[(nil respondsTo:selectorSymbol) not])ifTrue:[
                        "/ avoid trouble in miniTalk
                        "/ during bootstrap
                        nm := receiver name.    
                        Text notNil ifTrue:[
                            nm := nm allItalic
                        ].
                        err := 'sent to possibly uninitialized variable ''' , nm , ''' here (?)'.
                        alreadyWarnedUninitializedVars isNil ifTrue:[
                            alreadyWarnedUninitializedVars := Set new
                        ].
                        alreadyWarnedUninitializedVars add:receiver name
                    ]
                ]
            ] ifFalse:[
                (err notNil and:[selClass notNil]) ifTrue:[
                    err := err, ' (message to ' , selClass nameWithArticle , ')'.
                ].
            ]]]]]].
        ]
    ].

    err notNil ifTrue:[
        (receiver notNil
        and:[((recType := receiver type) == #GlobalVariable)
             or:[recType == #PrivateClass]]) ifTrue:[
            "/ dont check autoloaded classes 
            "/ - it may work after loading

            rec := receiver evaluate. 
            (rec notNil 
             and:[rec isBehavior
             and:[rec isLoaded not]]) ifTrue:[
                ^ aSelectorString
            ].
            rec class == UndefinedVariable ifTrue:[
                "/ dont check undefined vars;
                "/ it may work after loading/defining
                ^ aSelectorString
            ].
        ].
        Text notNil ifTrue:[
            err := '"' , aSelectorString allBold, '" ', err
        ] ifFalse:[
            err := aSelectorString , ' ', err
        ].
        "/ if its a recursive invocation of just that selector, do not complain
        (selector = aSelectorString and:[ receiver isSelf]) ifTrue:[
            ^ aSelectorString
        ].
        isSyntaxHighlighter ifTrue:[
            posVector do:[:p |
                self markUnknownIdentifierFrom:(p start) to:(p stop).
            ].
        ].
        isSyntaxHighlighter ifFalse:[
            err := err , '\\This is a warning from the compiler - the code has not yet been executed/compiled.'.
            newSelector := self correctSelector:aSelectorString 
                                message:err withCRs 
                                positions:posVector in:selClass for:receiver.
"/            self warning:('#' , aSelectorString , '\\' , err) withCRs position:pos1 to:pos2.
            ^ newSelector.
        ].
    ].
    ^ aSelectorString

    "Modified: / 05-09-1995 / 17:02:11 / claus"
    "Modified: / 10-02-2007 / 21:36:31 / cg"
!

typeOfNode:aNode
    |nodeVal nodeType classHint rClass|

    aNode isConstant ifTrue:[
        "if the receiver is a constant, we know its class..."
        nodeVal := aNode evaluate.
        ^ nodeVal class.
    ].

    aNode isBlock ifTrue:[
        "/ this should help with typos, sending #ifTrue to blocks ...
        ^ Block
    ].

    aNode isVariable ifTrue:[
        nodeType := aNode type.
        (nodeType == #GlobalVariable or:[nodeType == #PrivateClass]) ifTrue:[
            "if the receiver is a global, we check it too ..."

            nodeVal := aNode evaluate. 
            "/ dont check autoloaded classes 
            "/ - it may work after loading
            (nodeVal isNil 
             or:[nodeVal isBehavior and:[nodeVal isLoaded not]]) ifTrue:[
                ^ nil
            ].

            ^ nodeVal class.
        ].

        (aNode isLocal) ifTrue:[
            classHint := aNode token classHint.
            classHint notNil ifTrue:[ 
                ^ Smalltalk classNamed:classHint
            ].
        ].
    ].

    aNode isSuper ifTrue:[
        "if its a super- or here-send, we can do more checking"
        aNode isHere ifFalse:[
            ^ classToCompileFor superclass ? UndefinedObject.
        ].
        ^ classToCompileFor.
    ].
    aNode isSelf ifTrue:[
        ^ classToCompileFor.
    ].

    (aNode isUnaryMessage) ifTrue:[
        (aNode selector == #class) ifTrue:[
"/            aNode receiver isSelf ifTrue:[
"/                "its a message to self class - can check this too ..."
"/                ^ classToCompileFor class.
"/            ].
            rClass := self typeOfNode:aNode receiver.
            rClass notNil ifTrue:[
                ^ rClass class.
            ].
        ].
        ( #(#'isNil' #'notNil') includes:aNode selector) ifTrue:[
            ^ Boolean.
        ]
    ].
    aNode isBinaryMessage ifTrue:[
        ( #(#'<' #'>' #'>=' #'<=' #'=' #'==' #'~=' #'~~') includes:aNode selector) ifTrue:[
            ^ Boolean.
        ]
    ].

    ^ nil
! !

!Parser methodsFor:'error handling'!

blockArgRedefined:tokenName from:pos1 to:pos2
    "argname reuse"

    self isSyntaxHighlighter ifTrue:[
        self markBadIdentifierFrom:pos1 to:pos2.
    ] ifFalse:[
        self 
            syntaxError:'redefinition of ''' , tokenName , ''' in argument list.'
            position:pos1 to:pos2
    ].
!

errorMessageForUndefined:aName
    |idx implementors|

    classToCompileFor notNil ifTrue:[
        "/ is it an instance-variable marked inaccessable ?

        idx := (self classesInstVarNames) indexOf:(aName , '*') startingAt:1.
        idx ~~ 0 ifTrue:[
            ^ '''%1'' is a hidden instvar (not accessable from ST-code)'.
        ].

        "/ is it an instance variable, while evaluateing for the class ?
        classToCompileFor isMeta ifTrue:[
            (classToCompileFor soleInstance allInstVarNames includes:aName) ifTrue:[
                ^ 'Warning: ''%1'' is an instvar\(hint: you are evaluating/compiling in the classes context)'.
            ]
        ]
    ].
    self isDoIt ifTrue:[
        SystemBrowser notNil ifTrue:[
            implementors := SystemBrowser
                findImplementorsOf:aName
                in:(Smalltalk allClasses)
                ignoreCase:false.
            implementors size > 0 ifTrue:[
                ^ '''%1'' is undefined but known as a message selector.\(hint: did you forget to select the receiver ?)'.
            ].
        ].
    ].
    ^ '''%1'' is undefined'.
!

exitWith:something
    "this is the longjump out of evaluation via a return expression"

    evalExitBlock value:something
!

identifierExpectedIn:what
    |msg|

    (#(True False Self Nil Super ThisContext) includes:tokenType) ifTrue:[
        msg := 'Reserved keyword in ' 
    ] ifFalse:[
        msg := 'Identifier expected in ' 
    ].
    self syntaxError:(msg , what , ' (got ''' , tokenType printString, ''')')
         position:tokenPosition to:source position1Based - 1.
    ^ #Error
!

methodArgRedefined:tokenName from:pos1 to:pos2
    "argname reuse"

    self isSyntaxHighlighter ifTrue:[
        self markBadIdentifierFrom:pos1 to:pos2.
    ] ifFalse:[
        self 
            syntaxError:'redefinition of ''' , tokenName , ''' in argument list.'
            position:pos1 to:pos2
    ].
!

showErrorMessage:aMessage position:pos
    "redefined since parser can give more detailed info about
     the class & selector where the error occured."

    |msg|

    ignoreErrors ifFalse:[
        Smalltalk silentLoading ifFalse:[
            msg := ''.
            pos notNil ifTrue:[
                msg := msg , (pos printString).
                msg := msg , ' '.
            ].
            msg := msg , aMessage.
            selector notNil ifTrue:[
                msg := msg , ' in '.
                classToCompileFor notNil ifTrue:[
                    msg := msg , classToCompileFor name , '>>'
                ].
                msg := msg , selector.
            ] ifFalse:[
                classToCompileFor notNil ifTrue:[
                    msg := msg , ' (' , classToCompileFor name , ')'
                ]
            ].

            UserInformation isHandled ifTrue:[
                UserInformation raiseErrorString:msg
            ] ifFalse:[
                Transcript showCR:msg.
            ]
        ]
    ]

    "Modified: 18.5.1996 / 15:44:15 / cg"
!

showErrorMessageForClass:aClass
"/        compiler parseError:'syntax error'.
    Transcript show:'    '.
    aClass notNil ifTrue:[
        Transcript show:aClass name , '>>'
    ].
    selector notNil ifTrue:[
        Transcript show:(selector)
    ].
    Transcript showCR:' -> Error'.

    "Created: 13.12.1995 / 20:24:34 / cg"
    "Modified: 18.5.1996 / 15:44:17 / cg"
!

undefError:aName position:pos1 to:pos2
    "report an undefined variable error - return true, if it should be
     corrected. If not corrected, only one warning is made per undefined
     variable."

    |ex doCorrect boldName errMsg|

    ex := UndefinedVariableNotification newException.
    ex parser:self.
    ex parameter:aName.
    ex suspendedContext:thisContext.
    doCorrect := ex raiseRequest.
    doCorrect notNil ifTrue:[
        ^ doCorrect
    ].

    "
     already warned about this one ?
    "
    warnedUndefVars notNil ifTrue:[
        (warnedUndefVars includes:aName) ifTrue:[
            "already warned about this one"
            ^ false
        ].
    ].

"/    ignoreWarnings ifTrue:[^ false].
    parserFlags warnUndeclared ifFalse:[^ false].

"/    (classToCompileFor notNil 
"/    and:[classToCompileFor superclass notNil
"/    and:[classToCompileFor superclass instanceVariableString isNil]]) ifTrue:[
"/      self showErrorMessage:'Error: no source information (instvar names)' position:pos1.
"/      ^ false
"/    ].

    boldName := aName allBold.

    (requestor isNil or:[requestor isStream]) ifTrue:[
        errMsg := 'Error: "%1" is undefined' bindWith:boldName.
        aName isUppercaseFirst ifFalse:[
            self showErrorMessage:errMsg position:pos1.
        ].
        doCorrect := false.
    ] ifFalse:[
        "
         ask requestor for correct/continue/abort ...
         it is supposed to raise abort or return true/false.
         True return means that correction is wanted.
        "
        errMsg := (self errorMessageForUndefined:aName) bindWith:boldName.
        doCorrect := self 
                        correctableError:errMsg withCRs
                        position:pos1 to:pos2
    ].

    doCorrect == false ifTrue:[
        warnedUndefVars isNil ifTrue:[
            warnedUndefVars := Set new.
        ].
        warnedUndefVars add:aName.
        self classToCompileFor notNil ifTrue:[
            Tools::ToDoListBrowser notNil ifTrue:[
                "/ experimental
                self
                    notifyTodo:errMsg position:pos1
                    className:(self classToCompileFor name) selector:selector
                    severity:#error priority:#high 
                    equalityParameter:aName
                    checkAction:[:e |
                        e problemMethod notNil
                        and:[(e problemMethod usedGlobals includes:aName)
                        and:[(Smalltalk includesKey:aName) not]] ]. 
            ].
        ].
    ].

    ^ doCorrect

    "Modified: / 10-02-2007 / 21:36:45 / cg"
!

warnSTXHereExtensionUsedAt:position
    ignoreWarnings ifFalse:[
        didWarnAboutSTXHereExtensionUsed ifFalse:[
            parserFlags warnSTXHereExtensionUsed ifTrue:[
                self warning:'here-sends are a nonstandard feature of ST/X' 
                     position:position to:position+3.
                "
                 only warn once
                "
                didWarnAboutSTXHereExtensionUsed := true
            ].
        ].
    ].
!

warnSTXNameSpaceUseAt:position
    ignoreWarnings ifFalse:[
        didWarnAboutSTXNameSpaceUse ifFalse:[
            parserFlags warnSTXNameSpaceUse ifTrue:[
                self warning:'NameSpaces are a nonstandard feature of ST/X' 
                     doNotShowAgainAction:[ ParserFlags warnSTXSpecials:false ]
                     position:position to:(source position1Based).
                "
                 only warn once
                "
                didWarnAboutSTXNameSpaceUse := false
            ]
        ]
    ].
!

warnUnused:aNameCollection
    "report an unused method variable"

    |msg answer lineLength first|

    (ignoreErrors not 
    and:[ignoreWarnings not 
    and:[parserFlags warnUnusedVars]]) ifTrue:[
        msg := 'Unused method variable(s): '.
        lineLength := msg size.
        first := true.
        aNameCollection asSortedCollection do:[:name|
            first ifTrue:[ first := false ] ifFalse:[msg := msg , ', '].
            msg := msg , ('"',name allBold,'"').
            lineLength := lineLength + 2 + name size + 1.
            lineLength > 60 ifTrue:[
                msg := msg , '\' withCRs.
                lineLength := 0.
            ].
        ].

        (requestor isNil or:[requestor isStream]) ifTrue:[
            self showErrorMessage:('Warning: ', msg) position:nil.
        ] ifFalse:[
            answer := requestor 
                unusedVariableWarning:msg
                position:(localVarDefPosition first) to:(localVarDefPosition last) from:self.

            answer == true ifTrue:[
                "/ delete the definitions ...
                aNameCollection do:[:eachName |
                    self deleteDefinitionOf:eachName in:(localVarDefPosition first) to:(localVarDefPosition last).
                ].
                RestartCompilationSignal raise
            ].
        ].

        Tools::ToDoListBrowser notNil ifTrue:[
            "/ experimental
            self
                notifyTodo:msg position:(localVarDefPosition first)
                className:(self classToCompileFor name) selector:selector
                severity:#warning priority:#low 
                equalityParameter:nil
                checkAction:nil. 
        ].

    ].

    "Modified: / 17.11.2001 / 10:30:47 / cg"
! !

!Parser methodsFor:'evaluating expressions'!

evaluate:aStringOrStream
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:requestor 
        logged:logged 
        ifFail:[ self error:'error in eval' ] 
        compile:false 
        checkForEndOfInput:true
!

evaluate:aStringOrStream compile:compile
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:requestor 
        logged:logged 
        ifFail:[ self error:'error in eval' ] 
        compile:compile
        checkForEndOfInput:true

    "Created: / 07-12-2006 / 19:30:04 / cg"
!

evaluate:aStringOrStream ifFail:failBlock
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:nil 
        receiver:nil 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:false 
        checkForEndOfInput:true
!

evaluate:aStringOrStream in:aContext receiver:anObject
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:aContext 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:[ self error:'error in eval' ] 
        compile:false 
        checkForEndOfInput:true
!

evaluate:aStringOrStream in:aContext receiver:anObject ifFail:failBlock
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:aContext 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:false 
        checkForEndOfInput:true
!

evaluate:aStringOrStream in:aContext receiver:anObject notifying:requestor logged:logged ifFail:failBlock
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:aContext 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:true 
!

evaluate:aStringOrStream in:aContext receiver:anObject notifying:requestor logged:logged ifFail:failBlock compile:compile
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:aContext 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:compile 
        checkForEndOfInput:true
!

evaluate:aStringOrStream in:aContext receiver:anObject notifying:requestor logged:logged ifFail:failBlock compile:compile checkForEndOfInput:checkForEndOfInput
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    |tree mustBackup loggedString chgStream value s sReal spc
     nameSpaceQuerySignal compiler|

    aStringOrStream isNil ifTrue:[
        EmptySourceNotificationSignal raiseRequest.
        ^ nil
    ].
    (mustBackup := aStringOrStream isStream) ifTrue:[
        s := aStringOrStream.
    ] ifFalse:[
        loggedString := aStringOrStream.
        s := ReadStream on:aStringOrStream.
    ].

    self source:s.

    self parseForCode.
    self foldConstants:nil.
    self setSelf:anObject.
    self setContext:aContext.
    aContext notNil ifTrue:[
        self setSelf:(aContext receiver).
"/        aContext method notNil ifTrue:[
"/            cls := aContext method mclass
"/        ].
"/        self setClassToCompileFor:(cls ? aContext receiver class).
        self setClassToCompileFor:(aContext receiver class).
    ].
    self notifying:requestor.
    self nextToken.
    self evalExitBlock:[:value | self release. ^ value].
    tree := self parseMethodBodyOrEmpty.

    checkForEndOfInput ifTrue:[self checkForEndOfInput].

    "if reading from a stream, backup for next expression"
    mustBackup ifTrue:[
        self backupPosition
    ].

    (self errorFlag or:[tree == #Error]) ifTrue:[
        failBlock notNil ifTrue:[
            ^ failBlock value
        ].
        ^ #Error
    ].

    tree isNil ifTrue:[
        EmptySourceNotificationSignal raiseRequest.
        ^ nil
    ].

    (logged
    and:[loggedString notNil
    and:[Smalltalk logDoits]]) ifTrue:[
        Class updateChangeFileQuerySignal query ifTrue:[
            chgStream := Class changesStream.
            chgStream notNil ifTrue:[
                chgStream nextChunkPut:loggedString.
                chgStream cr.
                chgStream close
            ]
        ].
        Project notNil ifTrue:[
            Class updateChangeListQuerySignal query ifTrue:[
                Project addDoIt:loggedString
            ]
        ]
    ].

    "
     during the evaluation, handle nameSpace queries
     from the value as defined by any namespace directive.
     This, if its a class definition expression, the class will
     be installed there.
    "
    nameSpaceQuerySignal := Class nameSpaceQuerySignal.

    spc := self getNameSpace.
    spc isNil ifTrue:[
        (requestor respondsTo:#currentNameSpace) ifTrue:[
            spc := requestor currentNameSpace
        ] ifFalse:[
            spc := nameSpaceQuerySignal query.
        ]
    ].

    nameSpaceQuerySignal answer:spc
    do:[
        |method|

        "
         if compile is false, or the parse tree is that of a constant, 
         or a variable, quickly return its value.
         This is used for example, when reading simple objects
         via #readFrom:. 
         The overhead of compiling a method is avoided in this case.
        "
        ((SuppressDoItCompilation == true)
         or:[compile not 
         or:[tree isSimpleConstant
         or:[tree isSimpleVariable
         or:[aStringOrStream isStream
         or:[aContext notNil]]]]]) ifTrue:[
            ^ tree evaluate
        ].

        "
         if I am the ByteCodeCompiler,
         generate a dummy method, execute it and return the value.
         otherwise, just evaluate the tree; slower, but not too bad ...

         This allows systems to be delivered without the ByteCodeCompiler,
         and still evaluate expressions 
         (needed to read resource files or to process .rc files).
        "
        self == Parser ifTrue:[
            self evalExitBlock:[:value | self release. ^ value].
            value := tree evaluate.
            self evalExitBlock:nil.
        ] ifFalse:[
            s := self correctedSource.
            s isNil ifTrue:[    
                aStringOrStream isStream ifTrue:[
                    s := self collectedSource.  "/ does not work yet ...
                ] ifFalse:[
                    s := aStringOrStream
                ].
            ].

            "/ actually, its a block, to allow
            "/ easy return ...

            sReal := 'doIt ^[ ' , s , '\] value' withCRs.

            compiler := ByteCodeCompiler new.
            compiler initializeFlagsFrom:self.
            method := compiler
                    compile:sReal 
                    forClass:anObject class
                    inCategory:'_temporary_' 
                    notifying:requestor 
                    install:false 
                    skipIfSame:false 
                    silent:true
                    foldConstants:false.

            method notNil ifTrue:[
                method ~~ #Error ifTrue:[
                    "
                     fake: patch the source string, to what the user expects
                     in the browser
                    "
                    method source:"'        ' , "s string.
                    "
                     dont do any just-in-time compilation on it.
                    "
                    method checked:true.

                    value := method 
                                valueWithReceiver:anObject 
                                arguments:nil  "/ (Array with:m) 
                                selector:(requestor isNil ifTrue:#'doItX' ifFalse:#'doIt') "/ #doIt: 
                                search:nil
                                sender:nil.
                ] ifFalse:[
                    self evalExitBlock:[:value | self release. ^ value].
                    value := tree evaluate.
                    self evalExitBlock:nil.
                ]
            ].
        ]
    ].
    self release.
    ^ value

    "Created: / 8.2.1997 / 19:34:44 / cg"
    "Modified: / 18.3.1999 / 18:25:40 / stefan"
    "Modified: / 6.2.2000 / 15:01:57 / cg"
!

evaluate:aStringOrStream receiver:anObject
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:nil 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:[ self error:'error in eval' ] 
        compile:false 
        checkForEndOfInput:true
!

evaluate:aStringOrStream receiver:anObject ifFail:failBlock
    "return the result of evaluating aStringOrStream, errors are reported to requestor. 
     Allow access to anObject as self and to its instVars (used in the inspector).
     If logged is true, an entry is added to the change-file. If the failBlock argument
     is non-nil, it is evaluated if an error occurs.
     Finally, compile specifies if the string should be compiled down to 
     bytecode or instead be interpreted from the parseTree.
     The first should be done for doIts etc, where a readable walkback is
     required.
     The latter is better done for constants, styleSheet and resource
     reading and simple sends, where the overhead of compilation is bigger
     than the interpretation overhead."

    ^ self
        evaluate:aStringOrStream 
        in:nil 
        receiver:anObject 
        notifying:requestor 
        logged:logged 
        ifFail:failBlock 
        compile:false 
        checkForEndOfInput:true
! !

!Parser methodsFor:'initialization'!

initializeFlagsFrom:aParser
    "initialize flags from another scanner"

    super initializeFlagsFrom:aParser.

    moreSharedPools := aParser moreSharedPools.
    doItTemporaries := aParser doItTemporaries.
    selector := aParser selector.
! !

!Parser methodsFor:'parsing'!

block
    "parse a block; return a node-tree, nil or #Error"

    |startPos endPos node args argNames arg pos pos2 lno|

    startPos := tokenPosition.

    lno := tokenLineNr.
    self nextToken.
    (tokenType == $: ) ifTrue:[
        [tokenType == $:] whileTrue:[
            pos := tokenPosition.
            self nextToken.

            (pos == (tokenPosition - 1)) ifFalse:[
                self warnPossibleIncompatibility:'space(s) between colon and identifier may be non-portable' position:pos to:tokenPosition.
            ].
            (tokenType ~~ #Identifier) ifTrue:[
                ^ self identifierExpectedIn:'block-arg declaration'
            ].

            pos2 := tokenPosition + tokenName size - 1.
            self markArgumentIdentifierFrom:tokenPosition to:pos2.
            self checkBlockArgumentNameConventionsFor:tokenName.
            arg := Variable name:tokenName.
            args isNil ifTrue:[
                args := Array with:arg.
                argNames := Array with:tokenName.
            ] ifFalse:[
                (argNames includes:tokenName) ifTrue:[
                    self blockArgRedefined:tokenName from:tokenPosition to:pos2
                ].
                args := args copyWith:arg.
                argNames := argNames copyWith:tokenName.
            ].
            self nextToken.
        ].
        (tokenType ~~ $| ) ifTrue:[
            "ST-80 allows [:arg ]"
            (tokenType == $] ) ifTrue:[
                node := BlockNode arguments:args home:currentBlock variables:nil.
                node lineNumber:lno.
                ^ node
            ].
            self syntaxError:'| expected after block-arg declaration'.
            ^ #Error
        ].
        self nextToken
    ].
    node := self blockBody:args.
    (node notNil and:[node ~~ #Error]) ifTrue:[
        node lineNumber:lno.
    ].

    endPos := tokenPosition.
    self markBlockFrom:startPos to:endPos.

    ^ node

    "Modified: / 15-01-2008 / 11:51:39 / cg"
!

blockBody:args
    "parse a blocks body; return a node-tree, nil or #Error"

    |stats node var vars lno pos2|

    lno := tokenLineNr.
    (tokenType == $| ) ifTrue:[
        self nextToken.
        [tokenType == $|] whileFalse:[
            (tokenType == #Identifier) ifFalse:[
                ^ self identifierExpectedIn:'block-var declaration'
            ].
            pos2 := tokenPosition + tokenName size - 1.
            self markLocalIdentifierFrom:tokenPosition to:pos2.
            self checkBlockVariableNameConventionsFor:tokenName.
            var := Variable name:tokenName.
            vars isNil ifTrue:[
                vars := Array with:var.
            ] ifFalse:[
                (vars contains:[:var | var name = tokenName]) ifTrue:[
                    "/ varname reuse
                    self isSyntaxHighlighter ifTrue:[
                        self markBadIdentifierFrom:tokenPosition to:pos2.
                    ] ifFalse:[
                        self 
                            parseError:'redefinition of ''' , tokenName , ''' in local variables'
                            position:tokenPosition to:pos2.
                    ]
                ] ifFalse:[
                    vars := vars copyWith:var.
                ]
            ].
            self nextToken.

            parserFlags allowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
                ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
                    self nextToken.
                    "/ Q: should we allow literals only, or arbitrary expressions ?
                    self shouldImplement.
                ]
            ].
            parserFlags allowDomainVariables == true ifTrue:[
                (tokenType == $() ifTrue:[
                    self variableTypeDeclarationFor:var.
                ].
            ].
        ].
        self nextToken
    ].

    node := BlockNode arguments:args home:currentBlock variables:vars.
    node lineNumber:lno.
    currentBlock := node.
    stats := self blockStatementList.
    (stats == #Error) ifTrue:[^ #Error].

    lineNumberInfo == #full ifTrue:[
        node endLineNumber:tokenLineNr
    ].
    node statements:stats.
    currentBlock := node home.
    ^ node

    "Modified: / 31.3.1998 / 22:46:09 / cg"
!

blockExpression
    "parse a blockExpression; return a node-tree, nil or #Error.
     Not used by ST/X's parser, but added for ST-80 compatibility."

    tokenType ~~ $[ ifTrue:[
        self syntaxError:'[ expected'.
        ^ #Error.
    ].
    ^ self block
!

blockStatementList
    "parse a blocks statementlist; return a node-tree, nil or #Error"

    |thisStatement prevStatement firstStatement eMsg|

    (tokenType == $] ) ifTrue:[^ nil].
    thisStatement := self statement.
    (thisStatement == #Error) ifTrue:[^ #Error].
    firstStatement := thisStatement.
    [tokenType == $] ] whileFalse:[
        (tokenType == $.) ifFalse:[
            (tokenType == #EOF) ifTrue:[
                self syntaxError:'missing '']'' in block' position:(source position1Based) to:(source position1Based).
                ^ #Error.
            ].

            (tokenType == $) ) ifTrue:[
                eMsg := 'missing '']'' or bad '')'' in block'
            ] ifFalse:[
                eMsg := 'missing ''.'' between statements (i.e. ''' , tokenType printString , '''-token unexpected)'
            ].
            self syntaxError:eMsg position:tokenPosition to:tokenPosition.
            ^ #Error
        ].
        prevStatement := thisStatement.
        self nextToken.

        tokenType == $] ifTrue:[
            "
            *** I had a warning here (since it was not defined
            *** in the blue-book; but PD-code contains a lot of
            *** code with periods at the end so that the warnings
            *** became annoying

            self warning:'period after last statement in block'.
            "
            self markBracketAt:tokenPosition.
            ^ firstStatement
        ].
        thisStatement := self statement.
        (thisStatement == #Error) ifTrue:[^ #Error].
        prevStatement nextStatement:thisStatement
    ].
    self markBracketAt:tokenPosition.
    ^ firstStatement

    "Modified: / 16.7.1998 / 20:38:25 / cg"
!

checkForEndOfInput
    |what msg endPos|

    (tokenType ~~ #EOF) ifTrue:[
        "/ just for the nicer error message
        (#(Self Nil True False Super Here) includes:tokenType) ifTrue:[
            msg := '"',tokenName allBold,'" unexpected (missing "." or ":" before ' , tokenName , ' ?)'. 
            endPos := tokenPosition + tokenName size - 1.
        ] ifFalse:[
            tokenType isCharacter ifTrue:[
                what := '"' , tokenType asString allBold, '"'.
            ] ifFalse:[
                what := tokenType printString allBold.
            ].
            msg := what , ' unexpected. (missing ".", ":" or selector before it ?)'. 
            endPos := source position1Based-1.
        ].
        self parseError:msg position:tokenPosition to:endPos.
        ^#Error
    ]

    "Modified: / 22-08-2006 / 14:22:45 / cg"
!

emptyStatement
    (parserFlags allowEmptyStatements 
    or:[parserFlags allowSqueakExtensions == true]) ifTrue:[
        self warnAboutEmptyStatement.
        self nextToken.
    ].

    "Created: / 20-11-2006 / 14:04:14 / cg"
    "Modified: / 10-02-2007 / 21:35:34 / cg"
!

parseExpressionWithSelf:anObject notifying:someOne ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings inNameSpace:aNameSpaceOrNil
    "parse aString as an expression with self set to anObject;
     Return the parseTree (if ok), nil (for an empty string 
     or comment only ) or #Error (syntactic error).

     Errors and warnings are forwarded to someOne (usually some
     codeView) which can highlight it and show a popup box,
     iff ignoreErrors/ignoreWarnings is true respectively."

    |tree token|

    aNameSpaceOrNil notNil ifTrue:[
        self currentNameSpace:aNameSpaceOrNil
    ].
    self setSelf:anObject.
    self notifying:someOne.
    self ignoreErrors:ignoreErrors.
    self ignoreWarnings:ignoreWarnings.
    token := self nextToken.
    (token == $^) ifTrue:[
        self nextToken.
    ].
    (token == #EOF) ifTrue:[
        ^ nil
    ].
    tree := self expression.
    (self errorFlag or:[tree == #Error]) ifTrue:[^ #Error].
"/    tokenType ~~ #EOF ifTrue:[
"/        self parseError:'nothing more expected' position:tokenPosition
"/    ].
    ^ tree

    "Created: / 14.12.1999 / 15:11:37 / cg"
!

parseExtendedMethodSpec
    |pos1 pos2 var|

    "/ EXPERIMENTAL
false ifTrue:[
    (tokenType == #Symbol) ifTrue:[
        pos1 := tokenPosition.
        selector := token asSymbol.
        self nextToken.
        self markMethodSelectorFrom:pos1 to:(tokenPosition-1).
        beginOfBodyPosition := tokenPosition.

        tokenType == $( ifTrue:[
            self nextToken.
            [ tokenType ~~ $) ] whileTrue:[

                (tokenType ~~ #Identifier) ifTrue:[^ #Error].
                pos2 := tokenPosition+tokenName size-1.
                self markArgumentIdentifierFrom:tokenPosition to:pos2.
                var := Variable name:tokenName.
                methodArgs isNil ifTrue:[
                    methodArgs := Array with:var.
                    methodArgNames := Array with:tokenName
                ] ifFalse:[
                    (methodArgNames includes:tokenName) ifTrue:[
                        self methodArgRedefined:tokenName from:tokenPosition to:pos2
                    ].
                    methodArgs := methodArgs copyWith:var.
                    methodArgNames := methodArgNames copyWith:tokenName
                ].
                self nextToken.
            ].
            self nextToken.
        ].

        ^ self
    ].
].
    ^ #Error
!

parseMethod
    "parse a method.
     Return the parseTree or #Error.

     method ::= methodSpec methodBody
    "

    |parseTree|

"/    self nextToken.
    (self parseMethodSpec == #Error) ifTrue:[^ #Error].
    parseTree := self parseMethodBody.
    (parseTree == #Error) ifFalse:[
        self tree:parseTree
    ].
    self checkForEndOfInput.
    ^ parseTree

    "Modified: 20.4.1996 / 20:09:26 / cg"
!

parseMethod:aString in:aClass ignoreErrors:ignoreErrors ignoreWarnings:ignoreWarnings
    "parse a method in a given class.
     Return a parser (if ok), nil (empty) or #Error (syntax).
     The parser can be queried for selector, receiver, args, locals,
     used selectors, modified instvars, referenced classvars etc.
     The noErrors and noWarnings arguments specify if error and warning 
     messages should be sent to the Transcript or suppressed."

    |parser tree|

    aString isNil ifTrue:[^ nil].

    self initializeFor:(ReadStream on:aString).
    self setClassToCompileFor:aClass.
    self ignoreErrors:ignoreErrors.
    self ignoreWarnings:ignoreWarnings.
    tree := self parseMethod.
    (self errorFlag or:[tree == #Error]) ifTrue:[^ nil].
    ^ tree

    "Created: / 21-08-2006 / 18:26:36 / cg"
!

parseMethodBody
    "parse a methods body (locals & statements). 
     No more tokens may follow.
     Return a node-tree, or #Error

     methodBody ::= '<' st80Primitive '>' #EOF
                    | '<' st80Primitive '>' methodBodyVarSpec statementList #EOF

    "
    |stats|

    tokenType == $. ifTrue:[
        self emptyStatement.
    ].
    stats := self parseMethodBodyOrEmpty.
    (stats == #Error) ifFalse:[
        self checkForEndOfInput.
    ].
    ignoreWarnings ifFalse:[
        parserFlags warnings ifTrue:[
            self checkUnusedMethodVars.
            self checkReturnedValues.
        ]
    ].
    ^ stats

    "Modified: / 20-11-2006 / 14:04:24 / cg"
!

parseMethodBodyOrEmpty
    "parse a methods body (locals & statements);
     return  a node-tree, nil or #Error. 
     empty (or comment only) input is accepted and returns nil.

     methodBodyOrNil ::= '<' st80Primitive '>'
                         | '<' st80Primitive '>' methodBodyVarSpec statementList
                         | <empty>
    "

    |stats|

    (self parseMethodBodyVarSpec == #Error) ifTrue:[^ #Error].

    tokenType == $. ifTrue:[
        self emptyStatement.
    ].
    (tokenType ~~ #EOF) ifTrue:[
        stats := self statementList
    ].
"/    (tokenType ~~ #EOF) ifTrue:[
"/        self parseError:'nothing more expected here' position:tokenPosition to:tokenPosition.
"/        ^ #Error
"/    ].
    (stats notNil
    and:[stats ~~ #Error]) ifTrue:[
        (self isStatementAnUnconditionalReturn:stats last) ifFalse:[
            "/ remember a returned self here.
            self rememberReturnedValue:(self selfNode)
        ].
    ].
    tree notNil ifTrue:[
        tree last nextStatement:stats.
        ^ tree.
    ].
    ^ stats

    "Modified: / 20-11-2006 / 14:04:40 / cg"
!

parseMethodBodyVarSpec
    "parse a methods local variable specification, handling
     possible primitive or resourceSpecs.
     . 
     Leave spec of locals in methodLocals as a side effect.
     Return #Error or nil.

     methodBodyVarSpec ::= '|' { IDENTIFIER } '|'
                            | <empty>
    "

    |var pos pos2 msg classHint|

    ((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
        self parsePrimitiveOrResourceSpecOrEmpty.
    ].

    (tokenType == $|) ifTrue:[
        "memorize position for declaration in correction"

        localVarDefPosition := Array with:tokenPosition with:nil.
        self nextToken.
        pos := tokenPosition.
        [tokenType == #Identifier] whileTrue:[
            pos2 := tokenPosition + tokenName size - 1.
            self markLocalIdentifierFrom:tokenPosition to:pos2.
            self checkMethodVariableNameConventionsFor:tokenName.
            var := Variable name:tokenName.

            methodVars isNil ifTrue:[
                methodVars := OrderedCollection with:var.
                methodVarNames := OrderedCollection with:tokenName
            ] ifFalse:[
                (methodVarNames includes:tokenName) ifTrue:[
                    "/ redefinition
                    self isSyntaxHighlighter ifTrue:[
                        self markBadIdentifierFrom:tokenPosition to:pos2.
                    ] ifFalse:[
                        self 
                            parseError:'redefinition of ''' , tokenName , ''' in local variables.'
                            position:tokenPosition to:pos2.
                    ]
                ] ifFalse:[
                    methodVars add:var.
                    methodVarNames add:tokenName
                ]
            ].

            parserFlags warnHiddenVariables ifTrue:[
                methodArgNames notNil ifTrue:[
                    (methodArgNames includes:tokenName) ifTrue:[
                        self 
                            warning:'local variable "' , tokenName allBold , '" hides method argument.'
                            doNotShowAgainAction:[ ParserFlags warnHiddenVariables:false ]
                            position:tokenPosition to:pos2
                    ]
                ].
                classToCompileFor notNil ifTrue:[
                    (self classesInstVarNames includes:tokenName) ifTrue:[
                        classToCompileFor isMeta ifTrue:[
                            self 
                                warning:'local variable "' , tokenName allBold , '" hides class instance variable.'
                                doNotShowAgainAction:[ ParserFlags warnHiddenVariables:false ]
                                position:tokenPosition to:pos2
                        ] ifFalse:[
                            self 
                                warning:'local variable "' , tokenName allBold , '" hides instance variable.'
                                doNotShowAgainAction:[ ParserFlags warnHiddenVariables:false ]
                                position:tokenPosition to:pos2
                        ]
                    ]
                ].
            ].

            self nextToken.

            classHint := nil.
            lastDirective notNil ifTrue:[
                lastDirective isClassHintDirective ifTrue:[
                    var classHint:lastDirective className.
                ].
                lastDirective := nil.
            ].

            parserFlags allowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
                ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
                    self nextToken.
                    "/ Q: should we allow literals only, or arbitrary expressions ?
                    self shouldImplement.
                ]
            ].
            parserFlags allowDomainVariables == true ifTrue:[
                (tokenType == $() ifTrue:[
                    self variableTypeDeclarationFor:var.
                ].
            ].
            pos := tokenPosition
        ].

        (tokenType ~~ $|) ifTrue:[
            (#(True False Self Nil Super ThisContext) includes:tokenType) ifTrue:[
                msg := 'reserved keyword "',tokenName allBold,'" in local var declaration'. 
                pos2 := tokenPosition + tokenName size - 1.
                self markBadIdentifierFrom:tokenPosition to:pos2.
            ] ifFalse:[
                pos2 := source position1Based-1.
                msg := 'Identifier or | expected in local var declaration' 
            ].
            self syntaxError:msg position:tokenPosition to:pos2.
            ^ #Error
        ].
        localVarDefPosition at:2 put:tokenPosition.
        self nextToken
    ].

    (parserFlags allowSqueakPrimitives
    or:[ parserFlags allowSqueakExtensions
    or:[ parserFlags allowVisualAgePrimitives
    or:[ parserFlags allowSTVPrimitives ]]]) ifTrue:[
        "/ allow for primitiveSpec after local-var decl.

        ((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
            self parsePrimitiveOrResourceSpecOrEmpty.
        ]
    ].

    ^ nil

    "Modified: / 31.3.1998 / 17:30:33 / cg"
!

parseMethodSpec
    "parse a methods selector & arg specification;
     Set selector and methodArgs in the receiver as a side effect.
     Return the receiver or #Error.

     methodSpec ::= { KEYWORD IDENTIFIER }
                    | binaryOperator IDENTIFIER
                    | IDENTIFIER
    "

    |arg pos2|

    tokenType isNil ifTrue:[
        self nextToken.
    ].

    (tokenType == #Keyword) ifTrue:[
        selector := ''.
        [tokenType == #Keyword] whileTrue:[
            self markMethodSelectorFrom:tokenPosition to:(tokenPosition+tokenName size-1).
            selector := selector , tokenName.
            self nextToken.

            (tokenType ~~ #Identifier) ifTrue:[
                "/ ^ #Error].
                ^ self identifierExpectedIn:'method-arg declaration'
            ].

            pos2 := tokenPosition+tokenName size-1.
            self markArgumentIdentifierFrom:tokenPosition to:pos2.
            self checkMethodArgumentNameConventionsFor:tokenName.
            arg := Variable name:tokenName.
            methodArgs isNil ifTrue:[
                methodArgs := Array with:arg.
                methodArgNames := Array with:tokenName
            ] ifFalse:[
                (methodArgNames includes:tokenName) ifTrue:[
                    self methodArgRedefined:tokenName from:tokenPosition to:pos2
                ].
                methodArgs := methodArgs copyWith:arg.
                methodArgNames := methodArgNames copyWith:tokenName
            ].
            parserFlags warnHiddenVariables ifTrue:[
                classToCompileFor isClass ifTrue:[
                    (self classesInstVarNames includes:tokenName) ifTrue:[
                        self 
                            warning:'argument "' , tokenName allBold , '" hides instance variable.'
                            position:tokenPosition to:pos2
                    ]
                ].
            ].
            self nextToken.
"/            ((tokenType == #BinaryOperator) and:[token = '#']) ifTrue:[
"/                self nextToken.
"/                arg domain:nil.
"/            ].
        ].
        selector := selector asSymbol.
        endOfSelectorPosition := pos2.
        beginOfBodyPosition := tokenPosition.
        ^ self
    ].

    (self isValidUnarySelector:tokenType) ifTrue:[
        pos2 := tokenPosition+tokenName size-1.
        self markMethodSelectorFrom:tokenPosition to:pos2.
        selector := tokenName asSymbol.
        endOfSelectorPosition := pos2.
        self nextToken.
        beginOfBodyPosition := tokenPosition.
        ^ self
    ].

    "/ special handling for |, which is also a lexical token
    tokenType == $| ifTrue:[
        tokenType := #BinaryOperator.
        token := tokenName := '|'
    ].

    (tokenType == #BinaryOperator) ifTrue:[
        self markMethodSelectorFrom:tokenPosition to:(tokenPosition+tokenName size-1).
        selector := tokenName asSymbol.
        self nextToken.
        (tokenType ~~ #Identifier) ifTrue:[^ #Error].
        pos2 := tokenPosition+tokenName size-1.
        self markArgumentIdentifierFrom:tokenPosition to:pos2.
        self checkMethodArgumentNameConventionsFor:tokenName.
        arg := Variable name:tokenName.

        methodArgs := Array with:arg.
        methodArgNames := Array with:tokenName.

        endOfSelectorPosition := pos2.
        self nextToken.
        beginOfBodyPosition := tokenPosition.
"/            ((tokenType == #BinaryOperator) and:[token = '#']) ifTrue:[
"/                self nextToken.
"/                arg domain:nil.
"/            ].
        ^ self
    ].

    ^ self parseExtendedMethodSpec

    "Modified: / 17-07-2006 / 00:44:26 / cg"
!

statement
    "parse a statement; return a node-tree or #Error.

     statement ::= '^' expression
                   | PRIMITIVECODE
                   | expression
    "

    |expr node lnr code|

    (tokenType == $^) ifTrue:[
        self markReturnAt:tokenPosition.
        lnr := tokenLineNr.
        self nextToken.
        expr := self expression.
        (expr == #Error) ifTrue:[^ #Error].
        node := ReturnNode expression:expr.
        node home:self blockHome:currentBlock.
        true "(lineNumberInfo == #full)" ifTrue:[node lineNumber:lnr].

        self rememberReturnedValue:expr.
        ^ node
    ].

    (tokenType == #Primitive) ifTrue:[
        code := tokenValue.
        self nextToken.
        node := PrimitiveNode code:code.
        node isOptional ifFalse:[
            hasNonOptionalPrimitiveCode := true
        ].
        hasPrimitiveCode := true.
        ^ node
    ].

    (tokenType == #EOF) ifTrue:[
        currentBlock notNil ifTrue:[
            self syntaxError:'missing '']'' at end of block'.
        ] ifFalse:[
            self syntaxError:'period after last statement'.
        ].
        ^ #Error
    ].

    (tokenType == $.) ifTrue:[
        (parserFlags allowEmptyStatements 
        or:[parserFlags allowSqueakExtensions == true]) ifTrue:[
            "/ allow empty statement
            self warnAboutEmptyStatement.
            ^ StatementNode expression:nil.
        ].
    ].

    expr := self expression.
    (expr == #Error) ifTrue:[^ #Error].

"/    classToCompileFor notNil ifTrue:[
"/        currentBlock isNil ifTrue:[
"/            expr isPrimary ifTrue:[
"/                self warning:'useless computation - missing ^ ?'
"/            ]
"/        ]
"/    ].

    node := StatementNode expression:expr.
    (lineNumberInfo == #full) ifTrue:[node lineNumber:lnr].
    ^ node

    "Modified: / 16-11-2006 / 14:37:06 / cg"
!

statementList
    "parse a statementlist; return a node-tree, nil or #Error.
     Statements must be separated by periods.

     statementList ::= <statement>
                       | <statementList> . <statement>
    "

    |thisStatement prevStatement firstStatement periodPos prevExpr|

    thisStatement := self statement.
    (thisStatement == #Error) ifTrue:[^ #Error].
    firstStatement := thisStatement.
    [tokenType == $.] whileTrue:[
        prevExpr := thisStatement expression.
        (prevExpr notNil 
        and:[prevExpr isMessage
        and:[thisStatement isReturnNode not]]) ifTrue:[
            (#(#'=' #'==') includes:prevExpr selector) ifTrue:[
                self warning:'useless computation - mistyped assignment (i.e. did you mean '':='') ?' position:prevExpr selectorPosition
            ].
        ].

        periodPos := tokenPosition.
        self nextToken.
        tokenType == $. ifTrue:[
            self emptyStatement.
        ].
        (tokenType == $]) ifTrue:[
            currentBlock isNil ifTrue:[
                self parseError:''']'' unexpected (block nesting error)'.
            ].
            ^ firstStatement
        ].
        (tokenType == #EOF) ifTrue:[
            currentBlock notNil ifTrue:[
                self parseError:''']'' expected (block nesting error)'.
            ].
            ^ firstStatement
        ].

        prevStatement := thisStatement.
        prevStatement isReturnNode ifTrue:[
            self warning:'statements after return' position:tokenPosition
        ].

        thisStatement := self statement.
        (thisStatement == #Error) ifTrue:[^ #Error].
        prevStatement nextStatement:thisStatement
    ].
    ^ firstStatement

    "Modified: / 20-11-2006 / 14:05:52 / cg"
!

variableTypeDeclarationFor:aVariable
    "experimental support for Domain variables (constraint programming support):
     a variable-declaration of the form
        |var (domain) ... |
     declares var as a domainVariable.
     Valid domains are:
        min %% max      - integer range domain
        Bool            - boolean domain
        Nat             - positive integer domain
        Int             - integer domain
        #sym1 ... #sym2 - enumerated symbolic domain
    "

    |min max domain enumValues|

    (tokenType == $() ifFalse:[
        self syntaxError:'''('' expected' position:tokenPosition.
        ^ #Error
    ].    
    self nextToken.

    (tokenType == #Integer) ifTrue:[
        min := token.
        self nextToken.
        ((tokenType == #BinaryOperator) and:[token = '%%']) ifFalse:[
            self syntaxError:'''%%'' expected' position:tokenPosition.
        ].
        self nextToken.
        (tokenType == #Integer) ifFalse:[
            self syntaxError:'Integer (upper bound) expected' position:tokenPosition.
        ].
        max := token.
        self nextToken.
        domain := IntegerDomain min:min max:max.
    ] ifFalse:[
        ((tokenType == #Identifier) and:[token isUppercaseFirst]) ifTrue:[
            token = 'Bool' ifTrue:[
                self nextToken.
                domain := BooleanDomain new.
            ].
            token = 'Nat' ifTrue:[
                self nextToken.
                domain := IntegerDomain min:0 max:(SmallInteger maxVal).
            ].
            token = 'Int' ifTrue:[
                self nextToken.
                domain := IntegerDomain min:(SmallInteger minVal) max:(SmallInteger maxVal).
            ].
        ] ifFalse:[
            ((tokenType == #Symbol) or:[(tokenType == #Identifier)]) ifTrue:[
                enumValues := OrderedCollection new.
                [((tokenType == #Symbol) or:[(tokenType == #Identifier)])] whileTrue:[
                    enumValues add:token.
                    self nextToken.
                ].
                domain := EnumeratedDomain new values:enumValues.
            ].
        ].
    ].
    domain isNil ifTrue:[
        self syntaxError:'invalid domain' position:tokenPosition.
    ].
    aVariable domain:domain.

    (tokenType == $)) ifFalse:[
        self syntaxError:''')'' expected' position:tokenPosition.
        ^ #Error
    ].    
    self nextToken.
!

warnAboutEmptyStatement
    parserFlags warnAboutPossibleSTCCompilationProblems ifTrue:[
        self
            warning:'stc will not compile empty statements'
            line:lineNr.

        Tools::ToDoListBrowser notNil ifTrue:[
            self
                notifyTodo:'stc will not compile empty statements' position:tokenPosition
                className:(self classToCompileFor name) selector:selector
                severity:#warning priority:#medium 
                equalityParameter:nil
                checkAction:nil. 
        ].
    ].
! !

!Parser methodsFor:'parsing-expressions'!

array
    |arr elements elem pos1|

    pos1 := tokenPosition.
    elements := OrderedCollection new:20.
    [tokenType ~~ $) ] whileTrue:[
        elem := self arrayConstant.

"/        (elem == #Error) ifTrue:[
"/            (tokenType == #EOF) ifTrue:[
"/                self syntaxError:'unterminated array-constant; '')'' expected' 
"/                        position:pos1 to:tokenPosition
"/            ].
"/            ^ #Error
"/        ].
        elem isSymbol ifTrue:[
            self markSymbolFrom:tokenPosition to:(source position1Based-1).
        ].
        elements add:elem.
        self nextToken.
        tokenType == $. ifTrue:[
            self emptyStatement.
        ].
    ].
    arr := Array withAll:elements.

    parserFlags arraysAreImmutable ifTrue:[
        ^ self makeImmutableArray:arr
    ].
    ^ arr

    "Modified: / 20-11-2006 / 14:07:39 / cg"
!

arrayConstant
    |val|

    (tokenType == #Nil) ifTrue:[
        self warnPossibleIncompatibility:'nil in array constant is interpreted as #nil (symbol) in other smalltalks' position:tokenPosition to:tokenPosition+token size - 1.
        ^ tokenValue
    ].
    (tokenType == #True) ifTrue:[
        self warnPossibleIncompatibility:'true in array constant is interpreted as #true (symbol) in other smalltalks' position:tokenPosition to:tokenPosition+token size - 1.
        ^ tokenValue
    ].
    (tokenType == #False) ifTrue:[
        self warnPossibleIncompatibility:'false in array constant is interpreted as #false (symbol) in other smalltalks' position:tokenPosition to:tokenPosition+token size - 1.
        ^ tokenValue
    ].
    ((tokenType == #Integer) 
    or:[tokenType == #Float]) ifTrue:[
        ^ tokenValue
    ].
    (tokenType == #String) ifTrue:[
        parserFlags stringsAreImmutable ifTrue:[^ self makeImmutableString:tokenValue].
        ^ tokenValue
    ].
    (tokenType == #Character) ifTrue:[
        ^ tokenValue
    ].
    (tokenType == #Error) ifTrue:[
        ^ ParseErrorSignal raise.
    ].
    (tokenType == #BinaryOperator) ifTrue:[
        val := tokenName asSymbol.
        parseForCode ifFalse:[
            self rememberSymbolUsed:val.
        ].
        ^ val
    ].

    "/ some more special symbol consts ...
    (tokenType == $| ) ifTrue:[
        ^ #| 
    ].
    (tokenType == #Self ) ifTrue:[
        ^ #'self' 
    ].
    (tokenType == #Super ) ifTrue:[
        ^ #'super' 
    ].
    (tokenType == #Here ) ifTrue:[
        ^ #'here' 
    ].
    (tokenType == #ThisContext ) ifTrue:[
        ^ #'thisContext' 
    ].

    ((tokenType == #Keyword) 
    or:[tokenType == #Identifier]) ifTrue:[
        val := tokenName asSymbol.
        parseForCode ifFalse:[
            self rememberSymbolUsed:val.
        ].
        ^ val
    ].
    ((tokenType == $()
    or:[tokenType == #HashLeftParen]) ifTrue:[
        self nextToken.
        ^ self array
    ].
    ((tokenType == $[) 
    or:[tokenType == #HashLeftBrack]) ifTrue:[
        self nextToken.
        ^ self byteArray
    ].
    (tokenType == #HashLeftBrace) ifTrue:[
        val := self qualifiedName.
        "/ val := QualifiedName for:val name.
        val := val value.
        ^ val
    ].                         
    (tokenType == #Symbol) ifTrue:[
        parseForCode ifFalse:[
            self rememberSymbolUsed:tokenValue.
        ].
        ^ tokenValue
    ].
    (tokenType == #EOF) ifTrue:[
        "just for the better error-hilight; let caller handle error"
        self syntaxError:'EOF unexpected in array-constant'. 
        ^ ParseErrorSignal raise.
    ].
    self syntaxError:('"' 
                      , tokenType printString 
                      , '" unexpected in array-constant').
    ^ ParseErrorSignal raise.

    "Modified: / 22-08-2006 / 14:21:16 / cg"
!

arrayIndexingExpression
    "parse an array index expression; this is a squeak/stx extension.
     foo[idx] is syntactic sugar for foo matrixAt:x
     and foo[idx] := expr is syntactic sugar for foo matrixAt:x put:expr"

    |receiver argList selectorStream valNode|

    receiver := self functionCallExpression.
    tokenType == $[ ifFalse:[^ receiver].
    parserFlags allowArrayIndexSyntaxExtension == true ifFalse:[^ receiver.].
    (receiver == #Error) ifTrue:[^ #Error].

    selectorStream := WriteStream on: (String new: 32).
    argList := OrderedCollection new.

    [
        [      
            |indexNode|

            self nextToken.
            indexNode := self primary.
            argList isEmpty ifTrue:[selectorStream nextPutAll:'_'].
            selectorStream nextPutAll:'at:'.
            argList add: indexNode.
            (tokenType == #BinaryOperator ) and:[ token = ',']  
        ] whileTrue.

        tokenType == $] ifFalse:[ 
            self parseError:''']'' expected'.
            ^ #Error
        ].
        self nextToken.
        
        tokenType == $[ ifTrue:[
            receiver := MessageNode 
                    receiver:receiver 
                    selector:(selectorStream contents)
                    args:argList.
            selectorStream := WriteStream on: (String new: 32).
        ].
        tokenType == $[ 
    ] whileTrue.

    tokenType == #':=' ifTrue:[
        self nextToken.
        selectorStream nextPutAll:'put:'.
        valNode := self expression.
        valNode == #Error ifTrue:[
            ^ valNode
        ].
"/ this was found in squeak - why make it a block ?
"/        (valNode isKindOf: BlockNode) ifFalse:[
"/                valNode _ BlockNode new
"/                                        arguments: #()
"/                                        statements: (OrderedCollection with: valNode)
"/                                        returns: false
"/                                        from: encoder.
"/        ].
        argList add: valNode
    ].

    ^ MessageNode 
            receiver:receiver 
            selector:selectorStream contents
            args:argList.

    "
     AllowArrayIndexSyntaxExtension := true.
     AllowArrayIndexSyntaxExtension := false.
    "

    "
     |foo|

     foo := Array new:10 withAll:2.
     1 + foo[1].     
    "
    "
     |foo|

     foo := Array new:10.
     foo[1] := 'hello'.     
     foo[2].     
     foo[1].     
    "
!

binaryExpression
    "parse a binary-expression; return a node-tree, nil or #Error"

    |receiver|

    receiver := self unaryExpression.
    (receiver == #Error) ifTrue:[^ #Error].
    ^ self binaryExpressionFor:receiver
!

binaryExpressionFor:receiverArg
    "parse a binary-expression; return a node-tree, nil or #Error"

    |receiver expr arg sel pos1 pos2 lno note|

    receiver := receiverArg.
    (receiver == #Error) ifTrue:[^ #Error].

    "special kludge: since Scanner cannot know if -digit is a binary
     expression or a negative constant, handle cases here"

    [(tokenType == #BinaryOperator) 
     or:[(tokenType == $|)
         or:[((tokenType == #Integer) or:[tokenType == #Float])
             and:[tokenValue < 0]]]
    ] whileTrue:[
        "/ kludge alarm: in a function-call argList, #, is not a binarySelector
        inFunctionCallArgument == true ifTrue:[
            ((tokenType == #BinaryOperator) and:[tokenName = ',']) ifTrue:[
                ^ receiver
            ].
        ].

        pos1 := tokenPosition.
        lno := tokenLineNr.

        "/ kludge alarm: bar and minus are not scanned as binop
        (tokenType == $|) ifTrue:[
            sel := '|'.
            sel := self selectorCheck:sel for:receiver position:tokenPosition to:tokenPosition.
            self nextToken
        ] ifFalse:[
            (tokenType == #BinaryOperator) ifTrue:[
                sel := tokenName.
                sel := self selectorCheck:sel for:receiver position:tokenPosition to:(tokenPosition + tokenName size - 1).
                self nextToken
            ] ifFalse:[
                sel := '-'.
                token := tokenValue := tokenValue negated.
                tokenPosition := tokenPosition + 1. "/ to skip the sign
            ]
        ].

        pos2 := pos1 + sel size - 1.
        self markSelector:sel from:pos1 to:pos2 receiverNode:receiver.

        arg := self unaryExpression.
        (arg == #Error) ifTrue:[^ #Error].

        expr := BinaryNode receiver:receiver selector:sel arg:arg fold:foldConstants.
        expr isErrorNode ifTrue:[
            self parseError:(expr errorString) position:pos1 to:tokenPosition.
            errorFlag := false. "ok, user wants it - so he'll get it"
            expr := BinaryNode receiver:receiver selector:sel arg:arg fold:nil.
        ].
        expr lineNumber:lno.
        expr selectorPosition:pos1.

        (ignoreErrors or:[ignoreWarnings]) ifFalse:[
            note := self plausibilityCheck:expr.
            note notNil ifTrue:[
                self warning:note position:pos1 to:pos2
            ].
        ].
        parseForCode ifFalse:[
            self rememberSelectorUsed:sel receiver:receiver
        ].
        receiver := expr.   "/ for next message
    ].
    ^ receiver

    "Modified: / 9.1.1998 / 19:05:18 / stefan"
    "Modified: / 19.1.2000 / 16:22:04 / cg"
!

byteArray
    "started with ST-80 R4 - allow byteArray constants as #[ ... ]"

    |bytes index limit newArray elem pos1 pos2|

    pos1 := tokenPosition.
    bytes := ByteArray uninitializedNew:5000.
    index := 0. limit := 5000.
    [tokenType ~~ $] ] whileTrue:[
        pos2 := tokenPosition.
        "
         this is not good programming style, but speeds up
         reading of huge byte arrays (i.e. stored Images ...)
        "
        (tokenType == #Integer) ifTrue:[
            elem := tokenValue
        ] ifFalse:[
            elem := self arrayConstant.
            (elem == #Error) ifTrue:[
                (tokenType == #EOF) ifTrue:[
                    self syntaxError:'unterminated bytearray-constant; '']'' expected' 
                            position:pos1 to:tokenPosition
                ].
                ^ #Error
            ].
        ].
        ((elem isMemberOf:SmallInteger) and:[elem between:0 and:255]) ifTrue:[
            index := index + 1.
            bytes at:index put:elem.
            index == limit ifTrue:[
                newArray := ByteArray uninitializedNew:(limit * 2).
                newArray replaceFrom:1 to:limit with:bytes startingAt:1.
                limit := limit * 2.
                bytes := newArray
            ].
        ] ifFalse:[
            self parseError:'invalid ByteArray element' position:pos2 to:tokenPosition - 1
        ].
        self nextToken.
    ].
    newArray := ByteArray uninitializedNew:index.
    newArray replaceFrom:1 to:index with:bytes startingAt:1.
    ^ newArray
!

degeneratedKeywordExpressionForSelector
    "parse a keyword-expression without receiver - for the selector only. 
     Return the selector or nil (if it cannot be determined). 
     This is not used in normal parsing, but instead to extract the selector from a code fragment.
     (for example, the system browsers 'implementors'-function uses this to extract a selector from
      the selection)"

    |sel arg rec|

    (tokenType == #Keyword) ifTrue:[
        sel := tokenName.
        self nextToken.
        arg := self binaryExpression.
        (arg == #Error) ifTrue:[^ sel].
        [tokenType == #Keyword] whileTrue:[
            sel := sel , tokenName.
            self nextToken.
            arg := self binaryExpression.
            (arg == #Error) ifTrue:[^ sel].
        ].
        ^ sel
    ].

    (rec := self arrayIndexingExpression) == #Error ifTrue:[ ^ nil].
    sel := self degeneratedKeywordExpressionForSelector.
    sel notNil ifTrue:[ ^ sel].

    rec isAssignment ifTrue:[
        rec := rec expression
    ].
    rec isMessage ifTrue:[
        ^ rec selector
    ].        
    ^ nil

    "
     (self new source:'hello:world:') nextToken; degeneratedKeywordExpressionForSelector   
     (self new source:'hello:world') nextToken; degeneratedKeywordExpressionForSelector     
     (self new source:'hello:') nextToken; degeneratedKeywordExpressionForSelector  
    "
!

expression
    "parse a cascade-expression; return a node-tree, nil or #Error.

     expression ::= keywordExpression
                    | keywordExpression cascade

     cascade ::= ';' expressionSendPart
                 | cascade ';' expressionSendPart

     expressionSendPart ::= { KEYWORD binaryExpression }
                            | BINARYOPERATOR unaryExpression
                            | IDENTIFIER
    "

    |receiver arg sel args pos pos2 lno tokenEnd realReceiver positions|

    pos := tokenPosition.
    receiver := self keywordExpression.
    (receiver == #Error) ifTrue:[^ #Error].
    (tokenType == $;) ifTrue:[
        receiver isMessage ifFalse:[
            self syntaxError:'left side of cascade must be a message expression'
                    position:pos to:tokenPosition.
            realReceiver := receiver. "/ only to allow continuing.
        ] ifTrue:[
            realReceiver := receiver receiver.
        ].
        [tokenType == $;] whileTrue:[
            self nextToken.
            (tokenType == #Identifier) ifTrue:[
                tokenEnd := tokenPosition + tokenName size - 1.
                self markSelector:tokenName from:tokenPosition to:tokenEnd receiverNode:realReceiver.
                sel := tokenName.
                sel := self selectorCheck:tokenName for:realReceiver position:tokenPosition to:tokenEnd.
                receiver := CascadeNode receiver:receiver selector:sel.
                receiver lineNumber:tokenLineNr.
                parseForCode ifFalse:[
                    self rememberSelectorUsed:sel
                ].
                self nextToken.
            ] ifFalse:[
                (tokenType == #BinaryOperator) ifTrue:[
                    tokenEnd := tokenPosition + tokenName size - 1.
                    self markSelector:tokenName from:tokenPosition to:tokenEnd receiverNode:realReceiver.
                    sel := tokenName.
                    sel := self selectorCheck:tokenName for:realReceiver position:tokenPosition to:tokenEnd.
                    lno := tokenLineNr. 
                    self nextToken.
                    arg := self unaryExpression.
                    (arg == #Error) ifTrue:[^ #Error].
                    receiver := CascadeNode receiver:receiver selector:sel arg:arg.
                    receiver lineNumber:lno.
                    parseForCode ifFalse:[
                        self rememberSelectorUsed:sel
                    ].
                ] ifFalse:[
                    (tokenType == #Keyword) ifTrue:[
                        tokenEnd := tokenPosition + tokenName size - 1.
                        positions := OrderedCollection with:(tokenPosition to:tokenEnd).
                        pos := tokenPosition.
                        pos2 := tokenEnd.
                        lno := tokenLineNr. 
                        sel := tokenName.
                        self nextToken.
                        arg := self binaryExpression.
                        (arg == #Error) ifTrue:[^ #Error].
                        args := Array with:arg.
                        [tokenType == #Keyword] whileTrue:[
                            tokenEnd := tokenPosition + tokenName size - 1.
                            positions add:(tokenPosition to:tokenEnd).
                            sel := sel , tokenName.
                            self nextToken.
                            arg := self binaryExpression.
                            (arg == #Error) ifTrue:[^ #Error].
                            args := args copyWith:arg.
                            pos2 := tokenEnd
                        ].
                        positions do:[:p |
                            self markSelector:sel from:p start to:p stop receiverNode:realReceiver.
                        ].

                        sel := self selectorCheck:sel for:realReceiver position:pos to:pos2.

                        receiver := CascadeNode receiver:receiver selector:sel args:args.
                        receiver lineNumber:lno.
                        parseForCode ifFalse:[
                            self rememberSelectorUsed:sel
                        ].
                    ] ifFalse:[
                        (tokenType == #Error) ifTrue:[^ #Error].
                        self syntaxError:('invalid cascade; ' , tokenType printString , ' unexpected')
                                position:tokenPosition to:source position1Based - 1.
                        ^ #Error
                    ]
                ]
            ]
        ].

        "obscure (unspecified ?) if selector follows; Question:

        is
                'expr sel1; sel2 sel3'

        to be parsed as: 
                (t := expr.
                 t sel1.
                 t sel2) sel3

         or:
                (t := expr.
                 t sel1.
                 t sel2 sel3)
        "
        ((tokenType == #Identifier) 
         or:[(tokenType == #BinaryOperator)
             or:[tokenType == #Keyword]]) ifTrue:[
            self syntaxError:'ambigous cascade - please group using (...)'
                    position:tokenPosition to:source position1Based - 1.
            ^ #Error
"/            self warning: "syntaxError:" 'possibly ambigous cascade - please group using (...)'
"/                    position:tokenPosition to:source position - 1.
"/            tokenType == #Identifier ifTrue:[
"/                ^ self unaryExpressionFor:receiver
"/            ].
"/            tokenType == #BinaryOperator ifTrue:[
"/                ^ self binaryExpressionFor:receiver
"/            ].
"/            ^ self keywordExpressionFor:receiver
        ]
    ].
    ^ receiver

    "Modified: / 19.1.2000 / 16:22:16 / cg"
!

functionCallArgList
    |argList arg prevInFunctionCallArgument|

    self nextToken.
    tokenType == $) ifTrue:[ self nextToken. ^ #() ].

    argList := OrderedCollection new.
    [ true ] whileTrue:[
        prevInFunctionCallArgument := inFunctionCallArgument.
        inFunctionCallArgument := true.

        arg := self expression.
        argList add:arg.

        inFunctionCallArgument := prevInFunctionCallArgument.

        tokenType == $) ifTrue:[
            self nextToken.
            ^ argList 
        ].
        ((tokenType == #BinaryOperator) and:[tokenName = ',']) ifFalse:[
            self parseError:'"," or ")" expected'.
        ].
        self nextToken.
    ].
!

functionCallExpression
    "parse a functionCall; 
     this is an st/x extension.
        foo(x) 
     is syntactic sugar for 
        foo value:x
    "

    |receiver numArgs argList evalSelectors evalSelector|

    receiver := self primary.
    tokenType == $( ifFalse:[^ receiver].
    parserFlags allowFunctionCallSyntaxForBlockEvaluation ifFalse:[^ receiver.].

    (receiver == #Error) ifTrue:[^ #Error].

    receiver isVariable ifFalse:[
        ((receiver isMessage or:[receiver isAssignment]) and:[receiver parenthesized]) ifFalse:[
            receiver isBlock ifFalse:[
                ^ receiver
            ]
        ].
    ].

    argList := self functionCallArgList.

    "/ make it a block evaluation
    numArgs := argList size.
    numArgs == 0 ifTrue:[
        ^ UnaryNode receiver:receiver selector:#value
    ].
    evalSelectors := #(#'value:'
                       #'value:value:'
                       #'value:value:value:'
                       #'value:value:value:value:'
                       #'value:value:value:value:value:'
                       #'value:value:value:value:value:value:'
                       #'value:value:value:value:value:value:value:'
                       #'value:value:value:value:value:value:value:value:'
                     ).

    numArgs <= evalSelectors size ifTrue:[
        evalSelector := evalSelectors at:numArgs.
        ^ MessageNode 
                receiver:receiver 
                selector:evalSelector
                args:argList.
    ].
    "/ gen argument vector
    ^ MessageNode 
            receiver:receiver 
            selector:#valueWithArguments:
            args:(self genMakeArrayWith:argList).

    "
     Parser allowFunctionCallSyntaxForBlockEvaluation:true.
    "

    "
     |foo|

     foo := [:x | x + 1].
     1 + foo(1).     
     foo(1).     
    "
    "
     |addN add1|

     addN := [:n | [:x | x + n]].
     add1 := addN(1).
     add1(10).       
    "
    "AllowFunctionCallSyntaxForBlockEvaluation := false."
    "
     |addN add1|

     addN := [:n | [:x | x + n]].
     add1 := addN value:1.
     add1 value:10       
    "
!

keywordExpression
    "parse a keyword-expression; return a node-tree, nil or #Error.

     keywordExpression ::= binaryexpression
                           | { KEYWORD-PART binaryExpression }
    "

    |receiver|

    receiver := self binaryExpression.
    (receiver == #Error) ifTrue:[^ #Error].
    ^ self keywordExpressionFor:receiver
!

keywordExpressionFor:receiverArg
    "parse a keyword-expression; return a node-tree, nil or #Error.

     keywordExpression ::= binaryexpression
                           | { KEYWORD-PART binaryExpression }
    "

    |expr receiver sel arg args posR1 posR2 pos1 pos2 lno note positions|

    receiver := receiverArg.
    posR1 := tokenPosition.
    (tokenType == #Keyword) ifFalse:[^ receiver].

    pos1 := posR2 := tokenPosition.
    pos2 := tokenPosition + tokenName size - 1.
    positions := OrderedCollection with:(pos1 to:pos2).
    sel := tokenName.
    lno := tokenLineNr.
    self nextToken.
    arg := self binaryExpression.
    (arg == #Error) ifTrue:[^ #Error].
    args := Array with:arg.
    [tokenType == #Keyword] whileTrue:[
        sel := sel , tokenName.
        pos2 := tokenPosition + tokenName size - 1.
        positions add:(tokenPosition to:pos2).
        self nextToken.
        arg := self binaryExpression.
        (arg == #Error) ifTrue:[^ #Error].
        args := args copyWith:arg.
    ].

    positions do:[:p |
        self markSelector:sel from:p start to:p stop receiverNode:receiver.
    ].
    sel := self selectorCheck:sel for:receiver positions:positions.

    ignoreWarnings ifFalse:[
        (Class definitionSelectors includes:sel) ifTrue:[
            (receiver isVariable and:[receiver isUndeclared]) ifTrue:[
                "this is not an error - the undefined class may be loaded after this code!!"
                self warning:('as yet undefined superclass: ' , receiver name) position:pos1 to:pos2.
            ].
        ].
    ].

    expr := MessageNode receiver:receiver selector:sel args:args fold:foldConstants.
    expr isErrorNode ifTrue:[
        self parseError:(expr errorString) position:pos1 to:pos2.
        errorFlag := false. "ok, user wants it - so he'll get it"
        expr := MessageNode receiver:receiver selector:sel args:args fold:nil.
    ].
    expr lineNumber:lno.
    (ignoreErrors or:[ignoreWarnings]) ifFalse:[
        note := self plausibilityCheck:expr.
        note notNil ifTrue:[
            self warning:note position:pos1 to:pos2
        ].
    ].
    parseForCode ifFalse:[
        self rememberSelectorUsed:sel receiver:receiver
    ].

"/        (contextToEvaluateIn isNil and:[selfValue isNil]) ifTrue:[    "/ do not check this for doits
"/            receiver isSuper ifTrue:[
"/                sel ~= selector ifTrue:[
"/                    self warnCommonMistake:'possible bad super message (selector should be same as in current method) ?'
"/                                  position:posR1 to:posR2-1
"/                ].
"/            ].
"/        ].
"/
    (ignoreErrors or:[ignoreWarnings]) ifFalse:[
        (sel = #and: or:[sel = #or:]) ifTrue:[
            expr arg1 isBlock ifFalse:[
                (expr arg1 isVariable
                and:[ (expr arg1 name asLowercase includesString:'block')]) ifFalse:[
                    self warnCommonMistake:'(possible common mistake) missing block brackets ?'
                              position:pos2+1 to:tokenPosition-1
                ]
            ].
            ^ expr.
        ].

        (sel = #whileTrue: or:[sel = #whileFalse:]) ifTrue:[
            expr receiver isBlock ifFalse:[
                (expr receiver isVariable
                and:[ (expr receiver name asLowercase includesString:'block')]) ifFalse:[
                    self warnCommonMistake:'(possible common mistake) missing block brackets ?'
                              position:posR1 to:posR2-1
                ]
            ].
            ^ expr.
        ].

        (sel = #ifTrue: or:[sel = #ifFalse:]) ifTrue:[
            expr receiver isMessage ifTrue:[
                (expr receiver selector = #whileTrue or:[expr receiver selector = #whileFalse]) ifTrue:[
                    self warnCommonMistake:'strange receiver expression'
                              position:posR1 to:posR2-1
                ].
            ].
            ^ expr
        ].
    ].

    ^ expr.

    "Modified: / 19.1.2000 / 16:22:22 / cg"
!

primary
    "parse a primary-expression; return a node-tree, nil or #Error.
     This also cares for namespace-access-pathes."

    |val pos node eMsg endPos|

    (tokenType == #Self) ifTrue:[
        ^ self primary_self.
    ].

    pos := tokenPosition.
    (tokenType == #Identifier) ifTrue:[
        "
         must check for variable first, to be backward compatible
         with other smalltalks. 
        "
        tokenName = 'here' ifTrue:[
            (self variableOrError:tokenName) == #Error ifTrue:[
                self warnSTXHereExtensionUsedAt:pos.
                tokenType := #Here.
                ^ self primary_here.
            ]
        ].
        ^ self primary_identifier
    ].

    ((tokenType == #Integer) 
     or:[(tokenType == #String)
     or:[(tokenType == #Character) 
     or:[(tokenType == #Float)
     or:[(tokenType == #Symbol)
     or:[(tokenType == #ESSymbol)]]]]]) ifTrue:[
        ^ self primary_simpleLiteral.
    ].

    (tokenType == #FixedPoint) ifTrue:[
        parserFlags allowFixedPointLiterals == true ifFalse:[
            self parseError:'non-Standard literal: FixedPoint. Please enable in settings.' position:pos to:tokenPosition.
            ^ #Error
        ].
        ^ self primary_simpleLiteral.
    ].
    (tokenType == #Nil) ifTrue:[
        ^ self primary_nil.
    ].
    (tokenType == #True) ifTrue:[
        ^ self primary_true
    ].
    (tokenType == #False) ifTrue:[
        ^ self primary_false
    ].
    (tokenType  == #Super) ifTrue:[
        ^ self primary_super.
    ].

    (tokenType == #ThisContext) ifTrue:[
        ^ self primary_thisContext
    ].

    (tokenType == #HashLeftParen) ifTrue:[
        self nextToken.
        self inArrayLiteral:true.
        ParseErrorSignal handle:[:ex |
            self inArrayLiteral:false.
            ^ #Error
        ] do:[
            val := self array.
        ].
        self inArrayLiteral:false.
        self nextToken.
        (self noAssignmentAllowed:'assignment to a constant' at:pos) ifFalse:[
            ^ #Error
        ].
        ^ ConstantNode type:#Array value:val
    ].

    (tokenType == #HashLeftBrace) ifTrue:[
        val := self qualifiedName.
        self nextToken.
        ^ val.
    ].

    (tokenType == #HashLeftBrack) ifTrue:[
        self nextToken.
        val := self byteArray.
        self nextToken.
        (self noAssignmentAllowed:'assignment to a constant' at:pos) ifFalse:[
            ^ #Error
        ].
        ^ ConstantNode type:#ByteArray value:val
    ].

    (tokenType == $() ifTrue:[
        parenthesisLevel := parenthesisLevel + 1.
        self markParenthesisAt:tokenPosition.
        ^ self primary_expression.
    ].

    (tokenType == $[ ) ifTrue:[
        self markBracketAt:tokenPosition.
        val := self block.
        self nextToken.
        (self noAssignmentAllowed:'invalid assignment' at:pos) ifFalse:[
            ^ #Error
        ].
        ^ val
    ].

    "/ EXPERIMENTAL - may be in next release
    parserFlags allowVariableReferences == true ifTrue:[
        ((tokenType == #BinaryOperator) and:[token = '&']) ifTrue:[
            self nextToken.
            node := self primary_identifier.
            "/ generate a Reference
            ^ self makeReferenceFor:node
        ].
    ].

    (tokenType == ${ ) ifTrue:[
        parserFlags allowSqueakExtensions == true ifFalse:[
            didWarnAboutSqueakExtensions~~ true ifTrue:[ 
                didWarnAboutSqueakExtensions := true.
                "/ self parseError:'non-Standard Squeak extension: Brace Computed Array. Enable in settings.' position:pos to:tokenPosition.
                self 
                    warning:('non-Standard Squeak extension: Brace Computed Array. Enable in settings.')
                    doNotShowAgainAction:[ ParserFlags allowSqueakExtensions:true ]
                    position:pos to:tokenPosition.

                "/ errorFlag := false.
            ].
        ].
        ^ self primary_squeakComputedArray.
    ].

    (tokenType == #Primitive) ifTrue:[
        self nextToken.
        node := PrimitiveNode code:tokenValue.
        hasNonOptionalPrimitiveCode := true.
        hasPrimitiveCode := true.
        ^ node
    ].

    tokenType == #HashHashLeftParen ifTrue:[
        self nextToken.
        parserFlags allowDolphinExtensions == true ifFalse:[
            self parseError:'non-Standard Dolphin extension: ##(..). Enable in settings.' position:pos to:tokenPosition.
            ^ #Error
        ].
        ^ self primary_dolphinComputedLiteral.
    ].
    tokenType == #ExclaLeftBrack ifTrue:[
        self nextToken.
        parserFlags allowLazyValueExtension == true ifFalse:[
            self parseError:'non-Standard LazyValue extension. Enable in classVariable.' position:pos to:tokenPosition.
            ^ #Error
        ].
        ^ self primary_lazyValue.
    ].
    tokenType == #HashHash ifTrue:[
        self warnPossibleIncompatibility:'''##'' might be interpreted differently in other smalltalk systems' position:pos to:tokenPosition.
        tokenType := #Symbol.
        token := tokenValue := tokenName := '#'.
        ^ self primary_simpleLiteral.
    ].

    parserFlags allowSqueakExtensions == true ifTrue:[
        ((tokenType == #BinaryOperator) and:[token = '#']) ifTrue:[
            self nextToken.
            (tokenType == $( ) ifFalse:[
                self parseError:'''('' expected after #.' position:pos to:tokenPosition.
                ^ #Error.
            ].
            self nextToken.
            self inArrayLiteral:true.
            ParseErrorSignal handle:[:ex |
                self inArrayLiteral:false.
                ^ #Error
            ] do:[
                val := self array.
            ].
            self inArrayLiteral:false.
            self nextToken.
            (self noAssignmentAllowed:'assignment to a constant' at:pos) ifFalse:[
                ^ #Error
            ].
            ^ ConstantNode type:#Array value:val
        ].
    ].

    ((tokenType == #BinaryOperator) and:[token = '-']) ifTrue:[
        self nextToken.
        ((tokenType == #Integer) 
        or:[(tokenType == #Float)]) ifFalse:[
            self parseError:'number expected after sign.' position:pos to:tokenPosition.
            ^ #Error.
        ].
        ((parserFlags allowSqueakExtensions == true)
        or:[parserFlags allowSTVExtensions == true]) ifFalse:[
            self parseError:'non-Standard Squeak (or ST/V) extension: space between sign and number. Enable in settings.' position:pos to:tokenPosition.
            errorFlag := false.
        ].

        node := self primary_simpleLiteral.
        node isConstant ifFalse:[
            self parseError:'number expected after sign.' position:pos to:tokenPosition.
            ^ #Error.
        ].
        ^ ConstantNode type:(node type) value:(node value negated).
    ].

    (tokenType == #Error) ifTrue:[^ #Error].
    tokenType isCharacter ifTrue:[
        eMsg := '"',tokenType printString,'" unexpected in primary.'.
        endPos := tokenPosition.
    ] ifFalse:[
        (#(BinaryOperator Keyword) includes:tokenType) ifTrue:[
            eMsg := tokenType printString,' ("' , tokenName , '") ',' unexpected in primary. (missing receiver ?)'
        ] ifFalse:[
            (#(Integer Float) includes:tokenType) ifTrue:[
                eMsg := tokenType printString,' (' , tokenValue , ') ',' unexpected in primary. (missing receiver ?)'
            ] ifFalse:[
                eMsg := '"',(token ? ''),'" (',tokenType printString,') unexpected in primary.' 
            ]
        ].
        endPos :=source position1Based - 1.
    ].
    self syntaxError:eMsg position:tokenPosition to:endPos.
    ^ #Error

    "Created: / 13-09-1995 / 12:50:50 / claus"
    "Modified: / 18-10-2006 / 19:37:50 / cg"
!

primary_dolphinComputedLiteral
    "parse a dolphin computed literal; return a node-tree, or raise an Error.
     In dolphin, these are written as: ##( expression )
     and create a literal constant for the expressions value.
     Right now, only a subset is supported - Strings, ByteArrays and Characters.
     WARNING: this is only supported to allow filing in dolphin code.
     since stc cannot handle this (at the moment), you should rewrite the code
     if you ever plan to stc-compile it into a shared library"

    |pos expr val|

    pos := tokenPosition.

    expr := self expression.

    tokenType ~~ $) ifTrue:[
        self parseError:''')'' expected' position:tokenPosition.
        ^ #Error
    ].
    self nextToken.

    (self noAssignmentAllowed:'invalid assignment' at:pos) ifFalse:[
        ^ #Error
    ].

    val := expr evaluate.

    val isLiteral ifTrue:[
        val isString ifTrue:[
            ^ ConstantNode type:#String value:val
        ].
        val isByteArray ifTrue:[
            ^ ConstantNode type:#ByteArray value:val
        ].
        val isCharacter ifTrue:[
            ^ ConstantNode type:#Character value:val
        ].
        val isInteger ifTrue:[
            ^ ConstantNode type:#Integer value:val
        ].
        val isLimitedPrecisionReal ifTrue:[
            ^ ConstantNode type:#Float value:val
        ].
        val isArray ifTrue:[
            ^ ConstantNode type:#Array value:val
        ].
    ] ifFalse:[
        self parseError:'must be representable as a literal (for now)' position:pos.
        ^ #Error
    ].
self shouldImplement.
"/    "/ make it an array creation expression ...
"/    expr := MessageNode 
"/            receiver:(VariableNode globalNamed:#Array)
"/            selector:#new:
"/            arg:(ConstantNode type:#Integer value:(exprList size)).
"/
"/    exprList size == 0 ifTrue:[
"/        ^ expr.
"/    ].
"/    exprList keysAndValuesDo:[:idx :e |
"/        expr := (idx == 1 ifTrue:[MessageNode] ifFalse:[CascadeNode])
"/                    receiver:expr
"/                    selector:#at:put:
"/                    arg1:(ConstantNode type:#Integer value:idx)
"/                    arg2:e
"/                    fold:false.
"/    ].
"/    expr := CascadeNode
"/                receiver:expr
"/                selector:#yourself.
"/    ^ expr
!

primary_expression
    "parse a parentized expression primary; return a node-tree, or raise an Error."

    |pos val eMsg|

    pos := tokenPosition.

    self nextToken.
    val := self expression.
    (val == #Error) ifTrue:[^ #Error].
    (tokenType == $) ) ifFalse:[
        tokenType isCharacter ifTrue:[
            eMsg := 'missing '')'' (i.e. ''' , tokenType asString , ''' unexpected)'.
        ] ifFalse:[
            eMsg := 'missing '')'''.
        ].
        self syntaxError:eMsg withCRs position:pos to:tokenPosition.
        ^ #Error
    ].
    self markParenthesisAt:tokenPosition.
    parenthesisLevel := parenthesisLevel - 1.
    self nextToken.
    (self noAssignmentAllowed:'invalid assignment' at:pos) ifFalse:[
        ^ #Error
    ].
    val parenthesized:true.
    ^ val
!

primary_false
    "parse a false primary; return a node-tree, or raise an Error."

    |pos|

    pos := tokenPosition.

    self nextToken.
    (self noAssignmentAllowed:'assignment to ''false''' at:pos) ifFalse:[
        ^ #Error
    ].
    self markBooleanConstantFrom:pos to:pos+4.
    ^ ConstantNode type:#False value:false
!

primary_here
    "parse a here primary; return a node-tree, nil or #Error."

    |pos|

    pos := tokenPosition.

    self nextToken.
    (self noAssignmentAllowed:'assignment to pseudo variable ''here''' at:pos) ifFalse:[
        ^ #Error
    ].
    classToCompileFor isNil ifTrue:[
        self warning:'in which class are you ?' position:pos to:(pos + 3).
    ].
    self markSelfFrom:pos to:pos+3.
    ^ SuperNode value:selfValue inClass:classToCompileFor here:true
!

primary_identifier
    "parse a primary; return a node-tree, or raise an Error."

    |pos1 pos2 expr varName rawName var globlName nameSpace nameSpaceGlobal
     t cls lnr node holder autoHow assignmentAllowed|

    pos1 := tokenPosition.
    pos2 := tokenPosition + tokenName size - 1.

    varName := tokenName.

    (self isDoIt 
    and:[currentBlock isNil
    and:[(requestor askFor:#isWorkspace)
    and:[(autoHow := requestor autoDefineVariables) notNil]]]) ifTrue:[
        var := self variableOrError:varName.
        self nextToken.
        (var == #Error) ifTrue:[
            ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
                autoHow == #workspace ifTrue:[
                    holder := Workspace addWorkspaceVariable:varName.
                    var := VariableNode type:#WorkspaceVariable holder:holder name:varName
                ] ifFalse:[
                    holder := self addDoItTemporary:varName.
                    var := VariableNode type:#DoItTemporary holder:holder name:varName
                ].
            ] ifFalse:[
                var := self correctVariable:varName atPosition:pos1 to:pos2.
            ].
        ]
    ] ifFalse:[
        var := self variable.
        self nextToken.
    ].

    "/ errorFlag == true ifTrue:[self halt].
    (var == #Error) ifTrue:[
        errorFlag := true
    ].

    (tokenType == #'::') ifTrue:[
        globlName := rawName := varName.

        "is it in a namespace ?"
        nameSpace := self findNameSpaceWith:globlName.
        nameSpace notNil ifTrue:[
            globlName := nameSpace name , '::' , globlName
        ].

        [tokenType == #'::'] whileTrue:[
            nameSpace := globlName.

            self nextToken.
            (tokenType == #Identifier) ifTrue:[
                self warnSTXNameSpaceUseAt:pos1.
                varName := tokenName.

                globlName := (nameSpace , '::' , varName).
                rawName := (rawName , '::' , varName).

                nameSpaceGlobal := Smalltalk at:nameSpace asSymbol ifAbsent:nil.
                nameSpaceGlobal isNil ifTrue:[
                    warnedUnknownNamespaces isNil ifTrue:[
                        warnedUnknownNamespaces := Set new.
                    ].
                    (warnedUnknownNamespaces includes:nameSpace) ifFalse:[
                        self warning:('unknown nameSpace: ', nameSpace) 
                             position:pos1 to:tokenPosition-1.
"/                            self parseError:('unknown nameSpace: ', nameSpace) position:pos to:tokenPosition-1.
                        warnedUnknownNamespaces add:nameSpace.
                    ]
                ] ifFalse:[
                    nameSpaceGlobal isNameSpace ifTrue:[
                        "/ for now: only Smalltalk is allowed
                        nameSpaceGlobal ~~ Smalltalk ifTrue:[
"/                                self parseError:('(currently) the only valid nameSpace is `Smalltalk''') position:pos to:tokenPosition-1.
                        ] ifFalse:[
                            globlName := varName
                        ].
                    ] ifFalse:[
                        nameSpaceGlobal isBehavior ifFalse:[
                            self parseError:('invalid nameSpace: ' , nameSpace)  position:pos1 to:tokenPosition-1.
                        ] ifTrue:[
                            nameSpaceGlobal isLoaded ifTrue:[
                                (nameSpaceGlobal privateClassesAt:varName asSymbol) isNil ifTrue:[
                                    (Smalltalk at:rawName asSymbol) notNil ifTrue:[
                                        self warning:('Possible name clash (global: ' , rawName , ' vs. private: ' , (nameSpace , '::', varName) , ') - assume globl.') 
                                             position:pos1 to:source position "tokenPosition-1".
                                        globlName := rawName asSymbol.
                                    ] ifFalse:[
                                        self warning:('no private class: ' , varName allBold , ' in class: ' , nameSpace) 
                                             position:pos1 to:source position "tokenPosition-1".
"/                                        self parseError:('no private class: ' , name , ' in class: ' , nameSpace)  position:pos to:tokenPosition-1.                                
                                    ]
                                ] ifFalse:[
                                    "/ reference to a private class
                                    nameSpaceGlobal ~~ classToCompileFor ifTrue:[
                                        self classToCompileFor notNil ifTrue:[
                                            self isDoIt ifFalse:[
                                                parserFlags warnAboutReferenceToPrivateClass ifTrue:[
                                                    self warning:('Referring to private class ''' , varName allBold , ''' here.') 
                                                         doNotShowAgainAction:[ ParserFlags warnAboutReferenceToPrivateClass:false ]
                                                         position:pos1 to:source position " tokenPosition-1".
                                                ].
                                                Tools::ToDoListBrowser notNil ifTrue:[
                                                    self
                                                        notifyTodo:('Referring to private class ''' , varName allBold , ''' here.') position:pos1
                                                        className:(self classToCompileFor name) selector:selector
                                                        severity:#warning priority:#medium 
                                                        equalityParameter:nil
                                                        checkAction:nil. 
                                                ].
                                            ].
                                        ].
                                    ]
                                ].
                            ]
                        ]
                    ].
                ].
                self nextToken.
            ].
            var := VariableNode globalNamed:globlName.
            parseForCode ifFalse:[self rememberGlobalUsed:globlName].
        ].
        self markVariable:var from:pos1 to:pos1 + rawName size - 1.
    ].

    var == #Error ifTrue:[
        ^ #Error
    ].

    errorFlag ~~ true ifTrue:[
        self markVariable:var from:pos1 to:pos1 + varName size - 1.
    ].
    (ignoreErrors or:[parseForCode not and:[ignoreWarnings]]) ifTrue:[
        errorFlag := false.
    ].

    ((tokenType ~~ $_) and:[tokenType ~~ #':=']) ifTrue:[
        parseForCode ifFalse:[
            var isInstanceVariable ifTrue:[ self rememberInstVarRead:var name].
            var isClassVariable ifTrue:[ self rememberClassVarRead:var name].
        ].
        ^ var
    ].

    "/ assignment...

    "/ careful: it could already be an implicit self send
    parserFlags implicitSelfSends ifTrue:[
        var isMessage ifTrue:[
            self nextToken.
            expr := self expression.
            self isSyntaxHighlighter ifFalse:[
                (errorFlag or:[expr == #Error]) ifTrue:[^ #Error].
            ].
            ^ MessageNode receiver:(self selfNode) selector:('__' , varName , ':') asSymbol arg:expr.
        ].
    ].

    assignmentAllowed := true.

    (var ~~ #Error) ifTrue:[
        t := var type.
        t == #MethodVariable ifTrue:[
            modifiedLocalVars isNil ifTrue:[
                modifiedLocalVars := Set new.
            ].
            modifiedLocalVars add:var name.
        ] ifFalse:[ (t == #InstanceVariable) ifTrue:[
            varName := self classesInstVarNames at:(var index).

            "/ ca once did this to "name" and wondered what happened to his class ...
            "/ (not really a beginners bug, but may happen as a typo or missing local variable;
            "/  and is hard to track down later)

            ignoreWarnings ifFalse:[
                parserFlags warnings ifTrue:[
                    parserFlags warnCommonMistakes ifTrue:[
                        classToCompileFor isMeta ifTrue:[
                            (classToCompileFor isSubclassOf:Class) ifTrue:[
                                (Class allInstVarNames includes:(var name)) ifTrue:[
                                    self warning:'assignment to a classInstanceVariable\(see hierarchy of "Class")' withCRs position:pos1 to:pos2.
                                ]
                            ]
                        ]
                    ].
                ].
            ].

            parseForCode ifFalse:[
                self rememberInstVarModified:varName
            ]
        ] ifFalse:[ (t == #ClassVariable) ifTrue:[
            varName := var name.
            varName := varName copyFrom:((varName indexOf:$:) + 1).
            parseForCode ifFalse:[
                self rememberClassVarModified:varName
            ]
        ] ifFalse:[ (t == #GlobalVariable) ifTrue:[
            (cls := Smalltalk classNamed:var name) notNil ifTrue:[
                cls name = var name ifTrue:[
                    self warning:'assignment to global which refers to a class' position:pos1 to:pos2.
                ]
            ].
            parseForCode ifFalse:[
                self rememberGlobalModified:var name
            ]
        ] ifFalse:[ 
            (t == #PrivateClass) ifTrue:[
                assignmentAllowed := false.
                self parseError:'assignment to private class' position:pos1 to:pos2.
            ] ifFalse:[ (t == #MethodArg) ifTrue:[
                assignmentAllowed := false.
                self parseError:'assignment to method argument' position:pos1 to:pos2.
            ] ifFalse:[ (t == #BlockArg) ifTrue:[
                assignmentAllowed := false.
                self parseError:'assignment to block argument' position:pos1 to:pos2.
            ] ifFalse:[ (t == #PoolVariable) ifTrue:[
                self isDoIt ifTrue:[
                    self warning:'assignment to pool variable' position:pos1 to:pos2.
                    assignmentAllowed := true.
                ] ifFalse:[
                    self parseError:'assignment to pool variable' position:pos1 to:pos2.
                ]
            ]]]]]]]
        ].
    ].

    lnr := tokenLineNr.

    self nextToken.
    pos2 := tokenPosition.
    expr := self expression.

    "/ a typical beginner error:
    "/   expr ifTrue:[
    "/      var := super
    "/   ] ifFalse:[
    "/      var := something-else
    "/   ].
    "/   var messageSend
    "/
    "/   does not what a beginner might think.

    self isSyntaxHighlighter ifTrue:[
        (expr == #Error) ifTrue:[^ #Error].
    ] ifFalse:[
        parserFlags warnings ifTrue:[
            parserFlags warnCommonMistakes ifTrue:[
                (expr ~~ #Error and:[expr isSuper]) ifTrue:[
                    self warning:'followup messageSends to "' , var name , '" will have normal send semantics\(i.e. NO super- or here-sends). Use self to avoid confusion.' withCRs position:pos1 to:pos2.
                ].
            ].
        ].

        (errorFlag or:[expr == #Error]) ifTrue:[^ #Error].
        expr isVariable ifTrue:[
            expr name = var name ifTrue:[
                self warning:('useless assignment to "' , var name, '"' ) position:pos1 to:pos2-1.
            ].
        ].
    ].
    assignmentAllowed ifTrue:[
        node := AssignmentNode variable:var expression:expr.
        (lineNumberInfo == #full) ifTrue:[node lineNumber:lnr].
    ] ifFalse:[
        self parseError:('assignment to "' , var name, '" suppressed' ) position:pos1 to:pos2-1.
        node := expr.
    ].
    ^ node

    "Modified: / 05-09-2006 / 12:36:01 / cg"
!

primary_lazyValue
    |pos block expr|

    pos := tokenPosition.

    (tokenType == $: ) ifTrue:[
        self parseError:'lazyValues have no arguments' position:tokenPosition.
        ^ #Error
    ].

    block := self blockBody:#().
    self nextToken.

    expr := MessageNode 
                receiver:(VariableNode globalNamed:#LazyValue)
                selector:#'block:'
                arg:block.
    ^ expr
!

primary_nil
    "parse a nil primary; return a node-tree, nil or #Error."

    |pos|

    pos := tokenPosition.

    self nextToken.
    (self noAssignmentAllowed:'assignment to ''nil''' at:pos) ifFalse:[
        ^ #Error
    ].
"/        self markConstantFrom:pos to:pos+2.
    nilNode isNil ifTrue:[ 
        nilNode := ConstantNode type:#Nil value:nil
    ].
    ^ nilNode
!

primary_self
    "parse a self primary; return a node-tree, nil or #Error."

    |pos|

    pos := tokenPosition.

    self nextToken.
    (self noAssignmentAllowed:'assignment to pseudo variable ''self''' at:pos) ifFalse:[
        ^ ParseError raiseErrorString:'Assignment to self'.
    ].
    self markSelfFrom:pos to:pos+3.
    ^ self selfNode

    "Modified: / 22-08-2006 / 13:42:44 / cg"
!

primary_simpleLiteral
    "parse a simple literal primary; return a node-tree, or raise an Error."

    |pos val|

    pos := tokenPosition.

    "/
    "/ ImmutableStrings are experimental
    "/
    ((tokenType == #String)
    and:[(parserFlags stringsAreImmutable)]) ifTrue:[
        token := tokenValue := self makeImmutableString:tokenValue.
    ].

    ((tokenType == #Symbol) or:[tokenType == #ESSymbol]) ifTrue:[
        parseForCode ifFalse:[
            self rememberSymbolUsed:tokenValue
        ].
    ].
    val := ConstantNode type:tokenType value:tokenValue.

    ((tokenType == #Symbol) or:[tokenType == #ESSymbol]) ifTrue:[
        self markSymbolFrom:tokenPosition to:tokenPosition+tokenValue size-1.
    ] ifFalse:[
        tokenType == #String ifTrue:[
            self markStringFrom:pos to:source position1Based-1.
        ] ifFalse:[
            self markConstantFrom:pos to:source position1Based-1.
        ].
    ].

    self nextToken.
    (self noAssignmentAllowed:'assignment to a constant' at:pos) ifFalse:[
        ^ #Error
    ].
    ^ val
!

primary_squeakComputedArray
    "parse a squeak computed array literal; return a node-tree, or raise an Error.
     In squeak, these are written as: { expr1 . expr2 . ... exprN )
     and create a message to construct an Array containing the exprI values.
     WARNING: this is only supported to allow filing in squeak code.
     since stc cannot handle this (at the moment), you should rewrite the code
     if you ever plan to stc-compile it into a shared library"


    |pos exprList|

    pos := tokenPosition.

    self nextToken.
    exprList := self squeakComputedArray.
    (exprList == #Error) ifTrue:[ ^ #Error ].

    tokenType ~~ $} ifTrue:[
        self parseError:'"." or "}" expected' position:tokenPosition.
        ^ #Error
    ].
    self nextToken.
    (self noAssignmentAllowed:'invalid assignment' at:pos) ifFalse:[
        ^ #Error
    ].

    "/ make it an array creation expression ...
    ^ self genMakeArrayWith:exprList

    "
     Compiler allowSqueakExtensions:true.
    "

    "
     { 1@2. 10 factorial. Date today }.     
    "

    "
     Compiler allowSqueakExtensions:false.
    "
!

primary_super
    "parse a super primary; return a node-tree, nil or #Error."

    |pos|

    pos := tokenPosition.

    usesSuper := true.
    self nextToken.
    (self noAssignmentAllowed:'assignment to pseudo variable ''super''' at:pos) ifFalse:[
        ^ #Error
    ].
    (classToCompileFor isNil or:[classToCompileFor superclass isNil]) ifTrue:[
        self warning:'superclass is (currently ?) nil' position:pos to:(pos + 4).
    ].
    superNode isNil ifTrue:[
        superNode := SuperNode value:selfValue inClass:classToCompileFor
    ].
    self markSelfFrom:pos to:pos+4.
    ^ superNode
!

primary_thisContext
    "parse a thisContext primary; return a node-tree, or raise an Error."

    |pos|

    pos := tokenPosition.

    self nextToken.
    (self noAssignmentAllowed:'assignment to pseudo variable ''thisContext''' at:pos) ifFalse:[
        ^ #Error
    ].
    self markIdentifierFrom:pos to:pos+10.
    ^ VariableNode type:#ThisContext context:contextToEvaluateIn. "/ often nil
!

primary_true
    "parse a true primary; return a node-tree, or raise an Error."

    |pos|

    pos := tokenPosition.

    self nextToken.
    (self noAssignmentAllowed:'assignment to ''true''' at:pos) ifFalse:[
        ^ #Error
    ].
    self markBooleanConstantFrom:pos to:pos+3.
    ^ ConstantNode type:#True value:true
!

qualifiedName
    "a vw3.x (and later) feature: QualifiedName is #{ id ... id }
     and mapped to a global variable here.
     The initial #{ is supposed to be not yet skipped."

    |elements elem pos1 nm|

    pos1 := tokenPosition.
    self nextToken.
    elements := OrderedCollection new.
    [ tokenType ~~ $} ] whileTrue:[
        (tokenType == #Identifier) ifFalse:[
            self syntaxError:'bad qualifiedName; Identifier expected' 
                    position:pos1 to:tokenPosition
        ].
        elem := tokenName.
        elements add:elem.

        self nextToken.
        tokenType = $} ifTrue:[
        ] ifFalse:[
            tokenType == #'::' ifTrue:[
                "/ notice that Foo.Bar has already been scanned as Foo::Bar
                "/(which is a kludge)
                self nextToken.
            ] ifFalse:[
                self syntaxError:'bad qualifiedName syntax; ''.'' or ''}'' expected' 
                        position:pos1 to:tokenPosition.
            ].
        ].

"/        elem := self variable.
"/        (elem == #Error) ifTrue:[
"/            (tokenType == #EOF) ifTrue:[
"/                self syntaxError:'unterminated qualifiedName; ''}'' expected' 
"/                        position:pos1 to:tokenPosition
"/            ].
"/            ^ #Error
"/        ].
"/        errorFlag := false.
"/        (elem isVariable and:[elem isGlobal]) ifFalse:[
"/            self warning:'elements of a qualifiedName should be globalIdentifiers' 
"/                    position:pos1 to:tokenPosition
"/        ].
"/        elements add:elem.
"/
"/        self nextToken.
"/        tokenType == #'::' ifTrue:[
"/            "/ notice that Foo.Bar has already been scanned as Foo::Bar
"/            "/(which is a kludge)
"/            self nextToken.
"/        ] ifFalse:[
"/            tokenType ~~ $} ifTrue:[
"/                self syntaxError:'bad qualifiedName syntax; ''.'' or ''}'' expected' 
"/                        position:pos1 to:tokenPosition.
"/                ^ #Error
"/            ].
"/        ].
    ].

    parserFlags flattenVisualWorksNamespaces ifTrue:[
        "/ temporary kludge when loading VW UIBuilder code...
        ( #('UI' 'Core' 'Graphics') includes:elements first) ifTrue:[
            elements := elements copyFrom:2.
        ].
    ].

    nm := (elements asStringWith:'::') asSymbol.
    ^ ConstantNode type:#Symbol value:nm

"/    elements size > 1 ifTrue:[
"/        self syntaxError:'Sorry: qualified names are not yet implemented.'.
"/    ].
"/    ^ elements first.

    "Modified: / 14.4.1998 / 17:03:29 / cg"
!

squeakComputedArray
    |expressions elem pos1|

    tokenType == $} ifTrue:[
        ^ #()
    ].

    pos1 := tokenPosition.
    expressions := OrderedCollection new:20.
    [true] whileTrue:[
        elem := self expression.
        (elem == #Error) ifTrue:[
            (tokenType == #EOF) ifTrue:[
                self syntaxError:'unterminated computed-array-element; ''}'' expected' 
                        position:pos1 to:tokenPosition
            ].
            ^ #Error
        ].
        expressions add:elem.
        tokenType == $. ifFalse:[
            ^ expressions
        ].
        self nextToken.
        tokenType == $} ifTrue:[
            ^ expressions
        ].
    ].
    "/ not reached
!

unaryExpression
    "parse a unary-expression; return a node-tree, nil or #Error"

    |receiver|

    receiver := self arrayIndexingExpression.
    (receiver == #Error) ifTrue:[^ #Error].
    ^ self unaryExpressionFor:receiver
!

unaryExpressionFor:receiverArg
    "parse a unary-expression; return a node-tree, nil or #Error"

    |receiver expr sel pos pos2 note lNr arguments|

    receiver := receiverArg.
    (receiver == #Error) ifTrue:[^ #Error].

    [ self isValidUnarySelector:tokenType ] whileTrue:[
        pos := tokenPosition.
        pos2 := pos + tokenName size - 1.
        lNr := tokenLineNr.
        sel := tokenName.

        self markSelector:sel from:pos to:pos2 receiverNode:receiver.

        self nextToken.
        tokenType == $( ifTrue:[
            parserFlags allowSqueakExtensions == true ifTrue:[
                "/ croquet/squeak extension - c/java-style arguments
                arguments := self functionCallArgList.
                "/ synthetic selector: foo[:[with:[with:[...]]]]
                arguments notEmpty ifTrue:[
                    sel := sel , ':'.
                    arguments size - 1 timesRepeat:[ sel := sel , 'with:' ].
                ].
                sel := self selectorCheck:sel for:receiver position:pos to:pos2.
                expr := MessageNode receiver:receiver selector:sel args:arguments fold:foldConstants.
                expr isErrorNode ifTrue:[
                    self parseError:(expr errorString) position:pos to:pos2.
                    errorFlag := false. "ok, user wants it - so he'll get it"
                    expr := MessageNode receiver:receiver selector:sel args:arguments fold:nil.
                ].
                expr lineNumber:lNr.
                (ignoreErrors or:[ignoreWarnings]) ifFalse:[
                    note := self plausibilityCheck:receiver.
                    note notNil ifTrue:[
                        self warning:note position:pos to:pos2
                    ].
                ].
                parseForCode ifFalse:[
                    self rememberSelectorUsed:sel receiver:receiver
                ].
                ^ expr.
            ].
        ].

        sel := self selectorCheck:sel for:receiver position:pos to:pos2.
        expr := UnaryNode receiver:receiver selector:sel fold:foldConstants.
        expr isErrorNode ifTrue:[
            self warning:(expr errorString , '.\\If you proceed, that error will happen at runtime.') withCRs position:pos to:pos2.
            errorFlag := false. "ok, user wants it - so he'll get it"
            expr := UnaryNode receiver:receiver selector:sel fold:nil.
        ].
        expr lineNumber:lNr.

        (ignoreErrors or:[ignoreWarnings]) ifFalse:[
            note := self plausibilityCheck:expr.
            note notNil ifTrue:[
                self warning:note position:pos to:pos2
            ].
        ].
        parseForCode ifFalse:[
            self rememberSelectorUsed:sel receiver:receiver
        ].

        receiver := expr.   "/ for next message
    ].
    ^ receiver

    "Modified: / 16-07-2006 / 16:15:22 / cg"
!

variable
    "parse a simple (i.e. non-namespace-access path) variable; 
     return a node-tree, nil or #Error.
     Does not advance to next token.
     If undefined, notify error and correct if user wants to"

    |v pos1 pos2|

    v := self variableOrError:tokenName.
    (v ~~ #Error) ifTrue:[
        (v isMemberOf:VariableNode) ifTrue:[
            self markVariable:v.
        ].
        ^ v
    ].

    pos1 := tokenPosition.
    pos2 := pos1+tokenName size-1.
    self markUnknownIdentifierFrom:pos1 to:pos2.

    parseForCode == true ifTrue:[    
        v := self correctVariable:tokenName atPosition:pos1 to:pos2.
        (v ~~ #Error) ifTrue:[^ v].
    ].

    parseForCode ifFalse:[
        self rememberGlobalUsed:(Smalltalk undeclaredPrefix) , tokenName.
        self rememberGlobalUsed:tokenName.
    ] ifTrue:[
        self errorFlag:true.

        tokenName first isLowercase ifTrue:[
            parserFlags implicitSelfSends ifTrue:[
                ^ UnaryNode receiver:(self selfNode) selector:('__' , tokenName) asSymbol.
            ].
            ^ #Error
        ]
    ].

"/    self markGlobalIdentifierFrom:pos1 to:pos2.
    ^ VariableNode globalNamed:tokenName

    "Modified: / 21-11-2006 / 16:25:03 / cg"
!

variableOrError
    "parse a simple (i.e. non-namespace-access path) variable; 
     return a node-tree, nil or #Error.
     Does not advance to next token."

    ^ self variableOrError:tokenName
!

variableOrError:varName
    "parse a simple (i.e. non-namespace-access path) variable; 
     return a node-tree, nil or #Error.
     Does not advance to next token."

    |varIndex aClass searchBlock args vars 
     tokenSymbol space classVarIndex holder node
     checkSharedPoolAction|

    checkSharedPoolAction :=
        [:eachPoolName |
            |sharedPool|

            sharedPool := Smalltalk classNamed:eachPoolName.
            sharedPool isNil ifTrue:[
                Transcript showCR:'No such pool: ' , eachPoolName.
                "/ self warning:('No such pool: ' , eachPoolName).
            ] ifFalse:[
                (sharedPool includesKey:varName) ifTrue:[
                    parseForCode ifFalse:[self rememberGlobalUsed:(sharedPool name , ':' , varName)].
                    ^ VariableNode type:#PoolVariable class:sharedPool name:varName
                ].
            ].
        ].

    "is it a block-arg or block-var ?"
    searchBlock := currentBlock.
    [searchBlock notNil] whileTrue:[
        vars := searchBlock variables.
        vars notNil ifTrue:[
            varIndex := vars findFirst:[:aBlockVar | aBlockVar name = varName].
            varIndex ~~ 0 ifTrue:[
                ^ VariableNode type:#BlockVariable
                               name:varName
                              token:(vars at:varIndex)
                              index:varIndex
                              block:searchBlock
                               from:currentBlock
            ].
        ].

        args := searchBlock arguments.
        args notNil ifTrue:[
            varIndex := args findFirst:[:aBlockArg | aBlockArg name = varName].
            varIndex ~~ 0 ifTrue:[
                ^ VariableNode type:#BlockArg
                               name:varName
                              token:(args at:varIndex)
                              index:varIndex
                              block:searchBlock
                               from:currentBlock 
            ].

        ].

        searchBlock := searchBlock home
    ].

    "is it a method-variable ?"
    (node := self nodeForMethodVariable:varName) notNil
    ifTrue:[
        ^ node
    ].

    "is it a method-argument ?"
    (node := self nodeForMethodArg:varName) notNil
    ifTrue:[
        ^ node
    ].

    contextToEvaluateIn notNil ifTrue:[
        |con varNames|

        "/ 
        "/ search names of the context.
        "/ 
        con := contextToEvaluateIn.
        [con notNil] whileTrue:[
            varNames := con argAndVarNames.
            varNames size > 0 ifTrue:[
                varIndex := varNames lastIndexOf:varName.
                varIndex ~~ 0 ifTrue:[
                    ^ VariableNode type:#ContextVariable
                                   name:varName
                                context:con
                                  index:varIndex
                ].
            ].
            con := con home.
        ].
    ].

    classToCompileFor notNil ifTrue:[
        "is it an instance-variable ?"

        varIndex := (self classesInstVarNames) lastIndexOf:varName.
        varIndex ~~ 0 ifTrue:[
            classToCompileFor isMeta ifTrue:[
                classVarIndex := (self classesClassVarNames) lastIndexOf:varName.
                classVarIndex ~~ 0 ifTrue:[
                    "/ give a warning - that maybe a common error
                    alreadyWarnedClassInstVarRefs isNil ifTrue:[
                        alreadyWarnedClassInstVarRefs := Set new
                    ].
                    (alreadyWarnedClassInstVarRefs includes:varName) ifFalse:[
                        self warning:('there is both a class variable and a class-instance variable named ''' , varName , '''.\\Refering to the class-instance variable here.') withCRs.
                        alreadyWarnedClassInstVarRefs add:varName.
                    ].
                ].
            ].
            parseForCode ifFalse:[self rememberInstVarUsed:varName].
            ^ VariableNode type:#InstanceVariable 
                           name:varName
                          index:varIndex
                      selfValue:selfValue
        ].

        "/ see if there is a corresponding classVar (for the warning)
        classVarIndex := (self classesClassVarNames) lastIndexOf:varName.

        "/      "is it a class-instance-variable ?"
        "/
        "/ Notice:
        "/ it is no longer allowed to fetch class-instance variables
        "/ from instance methods ...
        "/ (used to be in previous ST/X versions)
        "/
        varIndex := (self classesClassInstVarNames) lastIndexOf:varName.
        varIndex ~~ 0 ifTrue:[
            aClass := self inWhichClassIsClassInstVar:varName.
            aClass notNil ifTrue:[
                classToCompileFor isMeta ifFalse:[
                    classVarIndex == 0 ifTrue:[
                        "/ there is no corresponding classVar;
                        "/ wants to access classInstVar ?
                        contextToEvaluateIn notNil ifTrue:[
                            "/ allow it in a doIt ...

                            ^ VariableNode type:#ClassInstanceVariable
                                           name:varName
                                          index:varIndex
                                      selfClass:aClass
                        ].
                        self parseError:'access to class-inst-var from inst method is not allowed'.
                        ^ #Error.
                    ] ifFalse:[
                        "/ give a warning - that maybe a common error
                        self warning:('there is both a class variable and a class-instance variable named ''' , varName , '''.\\Refering to the class variable here (instMethods dont see classInstVars).') withCRs.
                    ]
                ].

"/ OLD CODE:
"/ self warning:'access to class-inst-var from inst method will soon be no longer supported'.
"/
"/                    parseForCode ifFalse:[self rememberClassVarUsed:varName].
"/                    ^ VariableNode type:#ClassInstanceVariable
"/                                   name:varName
"/                                  index:varIndex
"/                              selfClass:aClass
"/                ].
            ] ifFalse:[
                "/ self halt:'oops - should not happen'.
            ]
        ].

        "is it a class-variable ?"

        varIndex := classVarIndex.
        varIndex ~~ 0 ifTrue:[
            aClass := self inWhichClassIsClassVar:varName.
            aClass notNil ifTrue:[
                parseForCode ifFalse:[self rememberClassVarUsed:varName].
                ^ VariableNode type:#ClassVariable class:aClass name:varName
            ].
            "/ self halt:'oops - should not happen'.
        ].

        "is it a private-class ?"

        aClass := self classToLookForClassVars.
        aClass := aClass theNonMetaclass.
        aClass isLoaded ifTrue:[
            (aClass privateClassesAt:varName) notNil ifTrue:[
                parseForCode ifFalse:[self rememberGlobalUsed:(aClass name , '::' , varName)].
                ^ VariableNode type:#PrivateClass class:aClass name:varName
            ].
        ].

        " is it a pool-variable ?"
        classToCompileFor theNonMetaclass realSharedPools do:checkSharedPoolAction.
    ].

    (self isDoIt) ifTrue:[
        moreSharedPools notNil ifTrue:[
            moreSharedPools do:checkSharedPoolAction.
        ].
    ].

    "is it in a namespace ?"
    space := self findNameSpaceWith:varName.
    space notNil ifTrue:[
        space ~~ Smalltalk ifTrue:[
            parseForCode ifFalse:[self rememberGlobalUsed:(space name , '::' , varName)].
            space isNameSpace ifTrue:[
                ^ VariableNode globalNamed:(space name , '::' , varName)
            ].
            ^ VariableNode type:#PrivateClass class:space name:varName
        ].
        parseForCode ifFalse:[self rememberGlobalUsed:varName].
        ^ VariableNode globalNamed:varName
    ].

    "is it a global-variable ?"
    tokenSymbol := varName asSymbolIfInterned.
    tokenSymbol notNil ifTrue:[
        (Smalltalk includesKey:tokenSymbol) ifTrue:[
            parseForCode ifFalse:[self rememberGlobalUsed:varName].
            ^ VariableNode globalNamed:tokenSymbol
        ]
    ].

    "is it a workspace variable ?"
    (requestor notNil and:[requestor isStream not]) ifTrue:[
        "/ when parsing doits, this is done twice;
        "/ first, for the parse, then as a block-code
        "/ for the code.
        "/ We only care for WorkspaceVars in doIts
        (self isDoIt) ifTrue:[
            (Workspace notNil 
            and:[(holder := Workspace workspaceVariableAt:varName) notNil])
            ifTrue:[
                ^ VariableNode type:#WorkspaceVariable holder:holder name:varName
            ]
        ]
    ].
    "is it a doIt variable ?"

"/    (requestor notNil and:[requestor isStream not]) ifTrue:[
        "/ when parsing doits, this is done twice;
        "/ first, for the parse, then as a block-code
        "/ for the code.
        "/ We only care for WorkspaceVars in doIts

        (self isDoIt) ifTrue:[
            (doItTemporaries notNil 
            and:[(holder := doItTemporaries at:varName asSymbol ifAbsent:nil) notNil]) 
            ifTrue:[
                ^ VariableNode type:#DoItTemporary holder:holder name:varName
            ]
        ].
"/    ].
    ^ #Error

    "Modified: / 07-06-2007 / 11:42:38 / cg"
! !

!Parser methodsFor:'parsing-primitives & pragmas'!

checkForClosingAngle
    ((tokenType == #BinaryOperator) and:[tokenName = '>']) ifTrue:[
        self nextToken.
    ] ifFalse:[
        self parseError:'bad primitive definition (''>'' expected)'.
        self skipForClosingAngle.
    ]
!

generateCallToExternalFunction:fn lineNr:lineNr
    |args sel node|

    fn argumentTypes size ~~ (methodArgNames size
                            "the following stuff was commented (2007-07-30), to make ole: work.
                             Ask felix or stefan"
                            " + (fn isCPPFunction ifTrue:1 ifFalse:0)") ifTrue:[
        self 
            ignorableParseError:('Number of method args (%1) does not match function arg list (ST/V api call)'
                                bindWith: methodArgNames size).
    ].

    args := (methodArgNames ? #()) collect:[:eachArgName | self nodeForMethodArg:eachArgName].
    fn isVirtualCPP ifTrue:[
        sel := #(       
              invokeCPPVirtualOn: 
              invokeCPPVirtualOn:with:
              invokeCPPVirtualOn:with:with:
              invokeCPPVirtualOn:with:with:with:
            ) at:args size+1 ifAbsent:nil.
        sel isNil ifTrue:[
            args := Array with:(self selfNode) with:(self genMakeArrayWith:args).
            sel := #invokeCPPVirtualOn:withArguments:.
        ] ifFalse:[
            args := (Array with:(self selfNode)) , args.
        ].
    ] ifFalse:[
        fn isNonVirtualCPP ifTrue:[ 
            args := (Array with:(self selfNode)) , args
        ].
        sel := #(       
              invoke 
              invokeWith:
              invokeWith:with:
              invokeWith:with:with:
            ) at:args size+1 ifAbsent:nil.
        sel isNil ifTrue:[
            args := Array with:(self genMakeArrayWith:args).
            sel := #invokeWithArguments:.
        ].
    ].

    node := MessageNode 
                receiver:(ConstantNode type:nil value:fn) 
                selector:sel 
                args:args 
                fold:false.
    node lineNumber:lineNr.
    tree := ReturnNode new expression:node.
    tree lineNumber:lineNr.

    "Created: / 01-08-2006 / 13:47:44 / cg"
    "Modified: / 25-10-2006 / 11:28:21 / cg"
!

generateReturnOfValue:aValue
    |node|

    node := ConstantNode type:nil value:aValue.
    node lineNumber:tokenLineNr.
    tree := ReturnNode new expression:node.
    tree lineNumber:tokenLineNr.

    "Modified: / 16-11-2006 / 14:36:35 / cg"
!

generateTrapCodeForUnavailableCParser
    |args node|

    self ignorableParseError:'CParser Missing'.

    args := Array with:(ConstantNode type:nil value:'External function call error - CParser missing.').
    node := MessageNode receiver:(self selfNode) selector:#error: args:args fold:false.
    node lineNumber:lineNr.
    tree := ReturnNode new expression:node.
    tree lineNumber:lineNr.
    ^ -1

    "Created: / 21-06-2006 / 09:58:43 / cg"
!

parseExceptionOrContextPragma
    |pragmaType|

    "/ notice: '<' has already been parsed.

    pragmaType := tokenName.

    self nextToken.
    (tokenType ~~ #Symbol) ifTrue:[
        self parseError:'symbol expected'.
        ^ #Error
    ].

    ((pragmaType = 'exception:'
        and:[tokenValue == #'handle'
             or:[tokenValue == #'raise'
             or:[tokenValue == #'unwind']]])
    or:[
        pragmaType = 'context:'
        and:[(tokenValue == #'return')]])

    ifTrue:[
        primitiveContextInfo isNil ifTrue:[
            primitiveContextInfo := Set new.
        ].
        primitiveContextInfo add:(pragmaType->tokenValue).
    ] ifFalse:[
        self parseError:'unrecognized exception pragma: ' , tokenValue.
    ].
    self nextToken.
!

parseExternalFunctionCallDeclaration
    |callType cString cStream returnType 
     functionName argTypes moduleName fn node args sel 
     type dictionaryOfKnownTypes function functionOrType lineNr|

    "callType is one of c: / cdecl: / api: / apicall: ..."
    callType := tokenName asLowercase.

    lineNr := tokenLineNr.
    cString := source upTo:$>.
    self nextToken.

    parseForCode ifFalse:[^ -1].

    CParser notNil ifTrue:[
        "/ collect existing types...
        dictionaryOfKnownTypes := Dictionary new.
        classToCompileFor methodsDo:[:m |
            m literalsDo:[:lit |
                (lit isKindOf:CType) ifTrue:[
                    self assert:lit name notNil.
                    dictionaryOfKnownTypes at:lit name put:lit.
                ].
            ].
        ].
    ].

    cStream := cString readStream.

    (#('apicall:' 'cdecl:' 'stdcall:' 'virtual') includes:callType ) ifTrue:[
        "/ squeak/dolphin/stx external function definition
        self
            parseSTXOrSqueakOrDolphinExternalFunctionDeclarationFrom:cStream 
            definitionType:callType
            knownDefinitions:dictionaryOfKnownTypes
            lineNr:lineNr.
        ^ -1
    ].

    callType = 'c:' ifTrue:[
        "/ VW external function definition
        self
            parseVWTypeOrExternalFunctionDeclarationFrom:cStream 
            definitionType:callType
            knownDefinitions:dictionaryOfKnownTypes
            lineNr:lineNr.
        ^ -1
    ].

    (callType = 'api:' or:[ callType = 'ole:' ]) ifTrue:[
        "/ ST/V external function definition
        self
            parseSTVExternalFunctionDeclarationFrom:cStream 
            definitionType:callType
            knownDefinitions:dictionaryOfKnownTypes
            lineNr:lineNr.
        ^ -1
    ].

    self ignorableParseError:'unsupported external function call type: ' , callType.
    ^ -1

    "
     (Parser for:'foo <cdecl: void ''glFlush'' (void) module: ''GL''>')
        nextToken;
        parseMethod
    "

    "Modified: / 25-10-2006 / 12:03:33 / cg"
!

parsePrimitive
    "parse an ST-80 type primitive as '< primitive: nr >';
        (return primitive number or #Error)
     or a Squeak-style primitive, as '< primitive: string >';
        (return primitive name or #Error)
     or a V'Age-style primitive, as '< primitive: identifier >';
        (return primitive name or #Error)

     Also, resource specs are parsed; the result is left (as side effect) in primitiveResource. 
     It is used to flag methods, for faster finding of used keyboard accelerators,
     and to mark resource methods (image, menu or canvas resources).

     prim ::= st80Primitive | st80Pragma | stxPragma
              squeakPrimitive | vAgePrimitive | newSTXPrimitive | resourceDecl

     st80Primitive ::= 'primitive:' INTEGER
     st80Pragma    ::= 'exception:' ( 'handle | 'raise' | 'unwind' )
     stxPragma     ::= 'context:' 'return'

     squeakPrimitive ::= 'primitive:' STRING

     newSTXPrimitive ::= 'primitive'

     vAgePrimitive ::= 'primitive:' IDENTIFIER
                       | 'sysprim:' IDENTIFIER

     resourceDecl ::= 'resource:' SYMBOL       - leave SYMBOL in primitiveResource
                    | 'resource:' SYMBOL (...) - leave (SYMBOL (...)) in primitiveResource
    "

    |lcTokenName|

    (tokenType == #Keyword or:[tokenType == #Identifier]) ifFalse:[
        self parseError:'bad primitive definition (keyword expected)'.
        ^ #Error
    ].

    (tokenName = 'primitive:') ifTrue:[
        ^ self parseTraditionalPrimitive.
    ].
    (tokenName = 'sysprim:') ifTrue:[
        parserFlags allowVisualAgePrimitives ifTrue:[
            ^ self parseTraditionalPrimitive.
        ].
    ].

    (tokenName = 'primitive') ifTrue:[
        self nextToken.
        self checkForClosingAngle.
        ^ 0.    "/ no primitive number
    ].
    (tokenName = 'resource:') ifTrue:[
        self parseResourcePragma.
        ^ nil.    "/ no primitive number
    ].
    (tokenName = 'exception:' 
    or:[tokenName = 'context:']) ifTrue:[
        self parseExceptionOrContextPragma.    
        self checkForClosingAngle.
        ^ nil   "/ no primitive number
    ].

    lcTokenName := tokenName asLowercase.
    ((lcTokenName = 'c:')                 "/ vw external function definition
    or:[ lcTokenName = 'api:'             "/ st/v external function definition
    or:[ lcTokenName = 'ole:'             "/ st/v external function definition
    or:[ lcTokenName = 'apicall:'         "/ squeak external function definition
    or:[ lcTokenName = 'cdecl:'           "/ squeak external function definition
    or:[ lcTokenName = 'stdcall:'         "/ dolphin external function definition
    ]]]]]) ifTrue:[
        self parseExternalFunctionCallDeclaration.
        ^ nil   "/ no primitive number
    ].

    self ignorableParseError:'unrecognized pragma: ' , tokenName.
    self skipForClosingAngle.
    ^ nil  "/ no primitive number
!

parsePrimitiveOrResourceSpecOrEmpty
    "parse a methods primitive or resource spec"

    |pos wmsg primNr primNrOrString|

    [(tokenType == #BinaryOperator) and:[tokenName = '<']] whileTrue:[
        pos := tokenPosition.
        self nextToken.
        primNrOrString := self parsePrimitive.

        (primNrOrString == #Error) ifTrue:[^ #Error].
        wmsg := nil.

        primNrOrString isString ifTrue:[
            primNr := self primitiveNumberFromName:primNrOrString
        ] ifFalse:[
            primNr := primNrOrString
        ].

        primNr notNil ifTrue:[
            primNr < 0 ifTrue:[
                parserFlags warnST80Directives == true ifTrue:[
                    wmsg := 'ST-80/Squeak directive ignored'.
                ].
            ] ifFalse:[
                primNr > 0 ifTrue:[
                    primitiveNr := primNr.
                    wmsg := 'ST-80 primitive may not work'
                ] ifFalse:[
                    primitiveNr := primNr.
                    wmsg := 'ST/X primitives only work in rel5 and newer'
                ]
            ].
            wmsg notNil ifTrue:[self warning:wmsg position:pos]
        ].
    ].

    "Created: 27.4.1996 / 16:55:55 / cg"
    "Modified: 29.5.1996 / 17:25:52 / cg"
!

parseResourcePragma
    " '< resource:' has already been parsed."

    |keys resource resourceValue|

    self nextToken.
    (tokenType ~~ #Symbol) ifTrue:[
        self parseError:'symbol expected'.
        ^ #Error
    ].

    resource := tokenValue.
    resourceValue := true.

    self nextToken.

    tokenType == $( ifTrue:[
        self nextToken.
        keys := OrderedCollection new.
        [(tokenType == $)) or:[tokenType == #EOF] ] whileFalse:[
            keys add:tokenValue.
            self nextToken.
        ].
        resourceValue := keys.
        (tokenType == $)) ifFalse:[
            self parseError:'unterminated primitive/spec (missing '')'')'.
        ].
        self nextToken.
    ].

    primitiveResource isNil ifTrue:[
        primitiveResource := IdentityDictionary new.
    ].
    primitiveResource at:(resource asSymbol) put:resourceValue.
    self checkForClosingAngle.
!

parseSTVExternalFunctionDeclarationFrom:aStream definitionType:definitionType knownDefinitions:dictionaryOfTypesOrNil lineNr:lineNr
    "parses ST/V function declarations of the forms 
        '<api: functionName argType1 .. argTypeN returnType>' 
        '<ole: vFunctionIndex argType1 .. argTypeN returnType>'
    "

    |primParser function|

    primParser := PrimitiveSpecParser new.
    function := primParser 
        parseSTVExternalFunctionDeclarationFrom:aStream 
        definitionType:definitionType 
        lineNr:lineNr
        for:self.

    function owningClass:classToCompileFor.
    self generateCallToExternalFunction:function lineNr:lineNr.

    "Modified: / 01-08-2006 / 16:16:53 / cg"
!

parseSTXOrSqueakOrDolphinExternalFunctionDeclarationFrom:aStream definitionType:definitionType 
    knownDefinitions:dictionaryOfTypesOrNil lineNr:lineNr

    "parses squeak/dolphin/stx function declarations of the forms 
        '<stdcall: [virtual|nonVirtual] returnType functionNameOrIndex argType1..argTypeN>'
        '<cdecl:   [virtual|nonVirtual] returnType functionNameOrIndex argType1..argTypeN>' 

        '<cdecl:   [async] [virtual|nonVirtual] returnType functionNameOrIndex ( argType1..argTypeN ) module: moduleName >' 
        '<apicall: [async] [virtual|nonVirtual] returnType functionNameOrIndex ( argType1..argTypeN ) module: moduleName >'
    "

    |primParser function|

    primParser := PrimitiveSpecParser new setClassToCompileFor:classToCompileFor.
    primParser notifying:requestor.
    function := primParser 
        parseSTXOrSqueakOrDolphinExternalFunctionDeclarationFrom:aStream 
        definitionType:definitionType 
        lineNr:lineNr
        for:self.

    function notNil ifTrue:[
        function owningClass:classToCompileFor.
        self generateCallToExternalFunction:function lineNr:lineNr.
    ].

    "Created: / 25-10-2006 / 12:03:24 / cg"
!

parseTraditionalPrimitive
    "parse everything after the initial '<primitive:'"

    |primNumber|

    self nextToken.
    (tokenType == #Integer) ifFalse:[
        (parserFlags allowSqueakExtensions
        or:[ parserFlags allowSqueakPrimitives ]) ifTrue:[
            (tokenType == #String) ifFalse:[
                self parseError:'primitive name as string expected'.
                ^ #Error
            ]
        ] ifFalse:[
            parserFlags allowVisualAgePrimitives ifTrue:[
                (tokenType == #Identifier) ifFalse:[
                    self parseError:'primitive name expected'.
                    ^ #Error
                ]
            ] ifFalse:[
                self parseError:'primitive number expected'.
                ^ #Error
            ].
        ]
    ].
    primitiveNr notNil ifTrue:[
        self parseError:'only one primitive spec allowed'.
        primNumber := -1.
    ] ifFalse:[
        primNumber := tokenValue.
    ].
    self nextToken.

    (tokenType == #Keyword) ifTrue:[
        (tokenName = 'errorCode:') ifTrue:[
            self nextToken.
            (tokenType == #Identifier) ifTrue:[
                self nextToken.
            ] ifFalse:[
                self error:'not yet implemented'.
            ]
        ].
        (tokenName = 'module:') ifTrue:[
            self nextToken.
            (tokenType == #String) ifTrue:[
                self nextToken.
            ] ifFalse:[
                self error:'not yet implemented'.
            ]
        ].
    ].

    self checkForClosingAngle.
    ^ primNumber
!

parseVWTypeOrExternalFunctionDeclarationFrom:aStream definitionType:definitionType knownDefinitions:dictionaryOfTypesOrNil lineNr:lineNr
    "parses visualWorks type/function declarations of the form: 
        '<c: ...>'"

    |primParser functionOrTypeOrValue|

    primParser := PrimitiveSpecParser new setClassToCompileFor:classToCompileFor.
    functionOrTypeOrValue := primParser
        parseVWTypeOrExternalFunctionDeclarationFrom:aStream 
        definitionType:definitionType 
        knownDefinitions:dictionaryOfTypesOrNil 
        lineNr:lineNr
        for: self.

    functionOrTypeOrValue isNil ifTrue:[^ self].

    (functionOrTypeOrValue isKindOf:ExternalLibraryFunction) ifFalse:[
        self generateReturnOfValue:functionOrTypeOrValue.
        ^ self
    ].

    functionOrTypeOrValue owningClass:classToCompileFor.
    self generateCallToExternalFunction:functionOrTypeOrValue lineNr:lineNr.

    "Modified: / 01-08-2006 / 16:21:36 / cg"
!

primitiveNumberFromName:aPrimitiveName
    "for future compatibility with Squeak ..."

    ^ nil
!

skipForClosingAngle
    "/ skip
    [tokenType ~~ #EOF] whileTrue:[
        ((tokenType == #BinaryOperator) and:[tokenName = '>']) ifTrue:[
            self nextToken.
            ^ nil "/ no primitive number
        ].
        self nextToken.
    ].
! !

!Parser methodsFor:'private'!

currentNameSpace
    |spc|

    spc := currentNamespace.
    spc isNil ifTrue:[
        (requestor respondsTo:#currentNameSpace) ifTrue:[
            spc := requestor currentNameSpace
        ] ifFalse:[
            spc := Class nameSpaceQuerySignal query.
        ].
        currentNamespace := spc.
    ].
    ^ spc

    "Created: / 19.12.1996 / 23:47:58 / cg"
    "Modified: / 14.10.1997 / 20:56:06 / cg"
    "Modified: / 18.3.1999 / 18:25:50 / stefan"
!

currentNameSpace:aNameSpace
    currentNamespace := aNameSpace.

    "Created: 8.2.1997 / 19:37:03 / cg"
!

currentPackage
    |pkg|

    pkg := currentPackage.
    pkg isNil ifTrue:[
        (requestor respondsTo:#currentPackage) ifTrue:[
            pkg := requestor currentPackage
        ] ifFalse:[
            pkg := Class packageQuerySignal query.
        ].
        currentPackage := pkg.
    ].
    ^ pkg
!

currentPackage:aPackageName
    currentPackage := aPackageName.
!

currentUsedNameSpaces
    |spaces|

    spaces := currentUsedNamespaces.
    spaces isNil ifTrue:[
        (requestor respondsTo:#usedNameSpaces) ifTrue:[
            spaces := requestor usedNameSpaces
        ] ifFalse:[
            spaces := Class usedNameSpaceQuerySignal query.
        ].
        spaces isNil ifTrue:[
            spaces := #()
        ].
        currentUsedNamespaces := spaces.
    ].
    ^ spaces

    "Created: / 19.12.1996 / 23:49:10 / cg"
    "Modified: / 7.4.1998 / 08:59:28 / cg"
    "Modified: / 18.3.1999 / 18:25:57 / stefan"
!

findNameSpaceWith:aVariableName
    |ns currentSpace usedSpaces|

    "/ private names have already been searched for.

    classToCompileFor notNil ifTrue:[
        "/ Q:
        "/ consider private classes of superclasses.
        "/ or search in the top owing classes namespace only ?

        "/ for now, ignore other private classes - they are only
        "/ known to the corresponding ownerClass.

        "is it in the classes namespace ?"

        ns := classToCompileFor topNameSpace.
        (ns notNil
        and:[ns ~~ Smalltalk]) ifTrue:[
            ns isNameSpace ifTrue:[
                (ns at:aVariableName) notNil ifTrue:[
                    ^ ns
                ]
            ]
        ].

"/        ns := classToCompileFor nameSpace.
"/        ns notNil ifTrue:[
"/            "is it in the current classes namespace ?"
"/            (ns at:aVariableName asSymbol) notNil ifTrue:[
"/                ^ ns
"/            ]
"/        ].
    ].

    "is it in the current namespace ?"
    currentSpace := self currentNameSpace.
    (currentSpace notNil
    and:[currentSpace ~~ Smalltalk]) ifTrue:[
        currentSpace isNameSpace ifTrue:[
            (currentSpace at:aVariableName) notNil ifTrue:[
                ^ currentSpace
            ]
        ] ifFalse:[
            (currentSpace privateClassesAt:aVariableName) notNil ifTrue:[
                ^ currentSpace
            ]
        ]
    ].

    "is it in one of the used namespaces ?"
    usedSpaces := self currentUsedNameSpaces.
    usedSpaces notNil ifTrue:[
        ^ usedSpaces detect:[:aNameSpace | (aNameSpace at:aVariableName) notNil] ifNone:nil.
    ].
    ^ nil

    "Created: 19.12.1996 / 23:51:02 / cg"
    "Modified: 14.10.1997 / 20:56:35 / cg"
!

genMakeArrayWith:elementExpressions
    "return a node to generate an array at runtime.
     Will generate:
        Array with:el1 ... with:elN                             (if N <= 5)
     or:
        (Array new at:1 put:el1; ... at:N put:elN; yourself)    (otherwise)
    "

    |numEl arrRec sel expr|

    arrRec := VariableNode globalNamed:#Array.

    numEl := elementExpressions size.

    (numEl between:1 and:8) ifTrue:[
        sel := #( 
                  #'with:'
                  #'with:with:'
                  #'with:with:with:'
                  #'with:with:with:with:'
                  #'with:with:with:with:with:'
                  #'with:with:with:with:with:with:'
                  #'with:with:with:with:with:with:with:'
                  #'with:with:with:with:with:with:with:with:'
                ) at:numEl.

        ^ MessageNode 
                    receiver:arrRec
                    selector:sel
                    args:elementExpressions.
    ].

    "/ array creation expression ...
    expr := MessageNode 
                receiver:arrRec
                selector:#new:
                arg:(ConstantNode type:#Integer value:numEl).

    numEl == 0 ifTrue:[
        ^ expr.
    ].
    "/ followed by a bunch of #at:put: messages...
    elementExpressions keysAndValuesDo:[:idx :e |
        expr := (idx == 1 ifTrue:[MessageNode] ifFalse:[CascadeNode])
                    receiver:expr
                    selector:#at:put:
                    arg1:(ConstantNode type:#Integer value:idx)
                    arg2:e
                    fold:false.
    ].
    "/ followed by a #yourself: message...
    expr := CascadeNode
                receiver:expr
                selector:#yourself.
    ^ expr
!

inWhichClassIsClassInstVar:aString
    "search class-chain for the class-instance variable named aString
     - return the class or nil if not found"

    |aClass|

    aClass := self classToLookForClassVars.

    [aClass notNil] whileTrue:[
        (aClass class instVarNames includes:aString) ifTrue:[ ^ aClass].
        aClass := aClass superclass
    ].
    ^ nil

    "Modified: / 18.6.1998 / 15:45:34 / cg"
!

inWhichClassIsClassVar:aString
    "search class-chain for the classvariable named aString
     - return the class or nil if not found"

    |aClass className baseClass|

    aClass := self classToLookForClassVars.

    aClass isMeta ifTrue:[
        className := aClass name copyWithoutLast:6.
        baseClass := Smalltalk at:(className asSymbol).
        baseClass notNil ifTrue:[
            aClass := baseClass
        ]
    ].
    ^ aClass whichClassDefinesClassVar:aString

"/    [aClass notNil] whileTrue:[
"/        (aClass classVarNames includes:aString) ifTrue:[ ^ aClass].
"/        aClass := aClass superclass
"/    ].
"/    ^ nil

    "Modified: / 17.6.1996 / 17:18:41 / stefan"
    "Modified: / 18.6.1998 / 15:45:29 / cg"
!

isStatementAnUnconditionalReturn:aStatementNode
    |expr selector block1 block2 stats1 stats2|

    aStatementNode isReturnNode ifTrue:[^ true ].
    ((expr := aStatementNode expression) notNil
    and:[expr isMessage]) ifTrue:[
        selector := expr selector.
        (selector == #'ifTrue:ifFalse:' or:[selector == #'ifFalse:ifTrue:']) ifTrue:[
            block1 := expr arg1.
            block2 := expr arguments at:2.
            (block1 isBlockNode and:[ block2 isBlockNode]) ifTrue:[
                stats1 := block1 statements.
                stats2 := block2 statements.
                    (stats1 notEmptyOrNil and:[ stats2 notEmptyOrNil]) ifTrue:[
                        ^ (self isStatementAnUnconditionalReturn:stats1 last)
                        and:[self isStatementAnUnconditionalReturn:stats2 last]
                ].
            ].
        ].
    ].
    ^ false.
!

isValidUnarySelector:tokenType
    tokenType == #Identifier ifTrue:[^true].
    tokenType == #Here ifTrue:[^true].

    parserFlags allowReservedWordsAsSelectors == true ifTrue:[
        tokenType == #Self ifTrue:[^true].
        tokenType == #Nil ifTrue:[^true].
        tokenType == #True ifTrue:[^true].
        tokenType == #False ifTrue:[^true].
        tokenType == #Super ifTrue:[^true].
        tokenType == #ThisContext ifTrue:[^true].
    ].
    ^ false

    "
     ParserFlags allowReservedWordsAsSelectors:true.
     1234 self.

     ParserFlags allowReservedWordsAsSelectors:false
     1234 self.
    "

    "
     1234 self
     1234 nil
     1234 true
     1234 false
     1234 here
     1234 super
     1234 thisContext
    "
!

makeImmutableArray:anArray
    ^ self class makeImmutableArray:anArray
!

makeImmutableString:aString
    ^ self class makeImmutableString:aString
!

makeReferenceFor:aNode
    |rec sel indexNode contextNode arg1 arg2|

    contextNode := VariableNode type:#ThisContext context:contextToEvaluateIn.
    indexNode := ConstantNode type:#Integer value:aNode index.

    aNode isArgument ifTrue:[
        sel := #forArgument:in:.
        arg1 := indexNode.
        arg2 := contextNode.
    ] ifFalse:[
        aNode isLocal ifTrue:[
            sel := #forLocal:in:.
            arg1 := indexNode.
            arg2 := contextNode.
        ] ifFalse:[
            self parseError:'unsupported variable reference (must be local or argument)'.
            ^ aNode
        ]
    ].

    parseForCode ifFalse:[self rememberGlobalUsed:'Reference'].
    rec := VariableNode globalNamed:'Reference'.

    ^ MessageNode receiver:rec selector:sel arg1:arg1 arg2:arg2.
!

noAssignmentAllowed:eMsg at:pos
    ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
        self parseError:eMsg position:pos to:tokenPosition + tokenType size - 1.
        self isSyntaxHighlighter ifFalse:[
            ^ false
        ].
        self nextToken. "/ eat the assign when doing highlighting only
    ].
    ^ true
!

nodeForMethodArg:varName
    |varIndex var|

    methodArgNames isNil ifTrue:[^ nil].
    varIndex := methodArgNames indexOf:varName.
    varIndex == 0 ifTrue:[^ nil].

    var := methodArgs at:varIndex.
"/    var used:true.
    ^ VariableNode type:#MethodArg
                   name:varName
                  token:var
                  index:varIndex
!

nodeForMethodVariable:varName
    |varIndex var|

    methodVarNames isNil ifTrue:[^ nil].
    varIndex := methodVarNames indexOf:varName.
    varIndex == 0 ifTrue:[^ nil].

    var := methodVars at:varIndex.
    var used:true.
    parseForCode ifFalse:[self rememberLocalUsed:varName].
    ^ VariableNode type:#MethodVariable
                   name:varName
                  token:var
                  index:varIndex
!

plausibilityCheck:aNode
    |note rcvr|

    note := aNode plausibilityCheckIn:self.
    note isNil ifTrue:[
        aNode isMessage ifTrue:[
            (contextToEvaluateIn isNil and:[selfValue isNil]) ifTrue:[    "/ do not check this for doits
                rcvr := aNode receiver.
                (rcvr isSuper and:[rcvr isHere not]) ifTrue:[
                    aNode selector ~= selector ifTrue:[
                        didWarnAboutBadSupersend ifFalse:[
                            didWarnAboutBadSupersend := true.
                            ^ 'possible bad super message ? (selector should be same as in current method)'.
                        ]
                    ].
                ].
            ].
        ].
    ].
    ^ note
!

selfNode
    selfNode isNil ifTrue:[ 
        selfNode := SelfNode value:selfValue
    ].
    ^ selfNode
! !

!Parser methodsFor:'queries'!

classToLookForClassVars
    "helper - return the class to look for classVars.
     If there is a context in which we evaluate, the
     methods implementing class is used instead of the
     class of the receiver."

    |m who|

    contextToEvaluateIn notNil ifTrue:[
        m := contextToEvaluateIn method.
        m notNil ifTrue:[
            who := contextToEvaluateIn method who.
            who notNil ifTrue:[
                ^ who methodClass.
            ]
        ].
        "/ mhmh - might be a doIt ...
    ].
    ^ classToCompileFor

    "Created: / 18.6.1998 / 15:43:42 / cg"
    "Modified: / 21.7.1998 / 18:19:52 / cg"
!

classesClassInstVarNames
    "caching allInstVarNames for next compilation saves time ..."

    |names|

    [
        |cls|

        cls := self classToLookForClassVars.

        (PrevClassInstVarNames isNil or:[PrevClass ~~ cls]) ifTrue:[
            PrevClass notNil ifTrue:[
                PrevClass removeDependent:Parser
            ].
            PrevClass := cls.

            PrevClassInstVarNames := cls class allInstVarNames.
            PrevClass addDependent:Parser.
        ].
        names := PrevClassInstVarNames.
    ] valueUninterruptably.
    ^ names

    "Created: / 14.10.1996 / 18:03:35 / cg"
    "Modified: / 18.6.1998 / 15:44:41 / cg"
!

classesClassVarNames
    "caching allClassVarNames for next compilation saves time ..."

    |names|

    [
        |cls aClass|

        cls := self classToLookForClassVars.

        (PrevClassVarNames isNil or:[PrevClass ~~ cls]) ifTrue:[
            PrevClass notNil ifTrue:[
                PrevClass removeDependent:Parser
            ].
            aClass := PrevClass := cls.
            aClass isMeta ifTrue:[
                aClass := aClass soleInstance.
                aClass isNil ifTrue:[
                    aClass := classToCompileFor
                ]
            ].
            PrevClassVarNames := aClass allClassVarNames.
            PrevClass addDependent:Parser.
        ].
        names := PrevClassVarNames.
    ] valueUninterruptably.
    ^ names

    "Modified: / 17.6.1996 / 17:15:53 / stefan"
    "Created: / 14.10.1996 / 18:02:41 / cg"
    "Modified: / 18.6.1998 / 15:44:30 / cg"
!

classesInstVarNames
    "caching allInstVarNames for next compilation saves time ..."

    |names|

    [
        (PrevInstVarNames isNil or:[PrevClass ~~ classToCompileFor]) ifTrue:[
            PrevClass notNil ifTrue:[
                PrevClass removeDependent:Parser
            ].
            PrevClass := classToCompileFor.
            PrevInstVarNames := classToCompileFor allInstVarNames.
            PrevClassInstVarNames := nil.
            PrevClassVarNames := nil.
            PrevClass addDependent:Parser
        ].
        names := PrevInstVarNames
    ] valueUninterruptably.

    ^ names

    "Created: 14.10.1996 / 18:00:26 / cg"
!

contextMustBeReturnable
    ^ primitiveContextInfo notNil 
      and:[ ^ primitiveContextInfo includes:('context:' -> #return) ]


!

hasNonOptionalPrimitiveCode
    "return true if there was any ST/X style primitive code (valid after parsing)"

    ^ hasNonOptionalPrimitiveCode
!

hasPrimitiveCode
    "return true if there was any ST/X style primitive code (valid after parsing)"

    ^ hasPrimitiveCode
!

isCompiling
    "return true if compiling code as opposed to evaluating"

    ^ false 
!

isDoIt
    ^ (selector isNil or:[selector == #'doIt' or:[selector == #'doIt:']])
!

isSyntaxHighlighter
    ^ false
!

lineNumberInfo
    ^ lineNumberInfo

    "Created: 21.10.1996 / 17:06:16 / cg"
!

lineNumberInfo:how
    lineNumberInfo := how

    "Created: 23.10.1996 / 15:39:43 / cg"
!

messagesSent
    "return a collection with sent message selectors (valid after parsing).
     Includes all sent messages (i.e. also sent super messages)"

    ^ (messagesSent ? #()) collect:[:each | each asSymbol]
!

messagesSentToSelf
    "return a collection with message selectors sent to self only (valid after parsing)"

    ^ (messagesSentToSelf ? #()) collect:[:each | each asSymbol]
!

messagesSentToSuper
    "return a collection with message selectors sent to super only (valid after parsing)"

    ^ (messagesSentToSuper ? #()) collect:[:each | each asSymbol]
!

methodArgs
    "return an array with methodarg names (valid after parsing spec)"

    ^ methodArgNames
!

methodVars
    "return a collection with method variablenames (valid after parsing)"

    ^ methodVarNames
!

modifiedClassVars
    "return a collection with classvariablenames modified by method (valid after parsing)"

    ^ modifiedClassVars ? #()

    "Modified: 19.6.1997 / 17:54:48 / cg"
!

modifiedGlobals
    "return a collection with globalnames modified by method (valid after parsing)"

    ^ modifiedGlobals ? #()

    "Modified: 19.6.1997 / 17:54:51 / cg"
!

modifiedInstVars
    "return a collection with instvariablenames modified by method (valid after parsing)"

    ^ modifiedInstVars ? #()

    "Modified: 19.6.1997 / 17:54:27 / cg"
!

numberOfMethodArgs
    "return the number of methodargs (valid after parsing spec)"

    ^ methodArgs size
!

numberOfMethodVars
    "return the number of method variables (valid after parsing)"

    ^ methodVars size
!

readClassVars
    "return a collection with classvariablenames read by method (valid after parsing)"

    ^ readClassVars ? #()

    "Modified: 19.6.1997 / 17:54:38 / cg"
!

readGlobals
    "return a collection with global varNames read by method (valid after parsing)"

    ^ readGlobals ? #()

    "Modified: 19.6.1997 / 17:54:38 / cg"
!

readInstVars
    "return a collection with instvariablenames read by method (valid after parsing)"

    ^ readInstVars ? #()

    "Modified: 19.6.1997 / 17:54:38 / cg"
!

selector
    "return the selector (valid after parsing spec)"

    ^ selector
!

shouldPerformCodingStyleChecks
    ^ ignoreWarnings not and:[ self isCompiling ]
!

usedClassVars
    "return a collection with classvariablenames refd by method (valid after parsing)"

    ^ usedClassVars ? #()

    "Modified: 19.6.1997 / 17:54:56 / cg"
!

usedGlobals
    "return a collection with globalnames refd by method (valid after parsing)"

    ^ usedGlobals ? #()

    "Modified: 19.6.1997 / 17:55:00 / cg"
!

usedInstVars
    "return a collection with instvariablenames refd by method (valid after parsing)"

    ^ usedInstVars ? #()

    "Modified: 19.6.1997 / 17:54:38 / cg"
!

usedSymbols
    "return a collection with used symbols (except for sent messages) (valid after parsing)"

    ^ (usedSymbols ? #()) 
!

usedVars
    "return a collection with variablenames refd by method (valid after parsing)"

    ^ usedVars ? #()

    "Modified: 19.6.1997 / 17:55:04 / cg"
!

usesSuper
    "return true if the parsed method uses super (valid after parsing)"

    ^ usesSuper
! !

!Parser methodsFor:'setup'!

arraysAreImmutable
    ^ parserFlags arraysAreImmutable
!

arraysAreImmutable:aBoolean
    parserFlags arraysAreImmutable:aBoolean.
!

classToCompileFor
    ^ classToCompileFor

    "Created: / 15.11.2001 / 17:21:10 / cg"
!

foldConstants:aSymbolOrNil
    "change the constant folding level. See the classMethod for a description."

    foldConstants := aSymbolOrNil

    "Created: 21.3.1996 / 16:03:22 / cg"
    "Modified: 21.3.1996 / 16:05:04 / cg"
!

initialize
    super initialize.

    hasPrimitiveCode := hasNonOptionalPrimitiveCode := false.
    usesSuper := false.
    parseForCode := false.
    foldConstants := FoldConstants.
    lineNumberInfo := LineNumberInfo.
    parenthesisLevel := 0.

    didWarnAboutSTXNameSpaceUse := false.
    didWarnAboutSTXHereExtensionUsed := false.
    didWarnAboutBadSupersend := false.

    "Modified: 7.9.1997 / 02:04:34 / cg"
!

parseForCode
    "turns off certain statistics (keeping referenced variables, modified vars etc.)
     Use this when parsing for compilation or evaluation"

    parseForCode := true
!

setClassToCompileFor:aClass
    "set the class to be used for parsing/evaluating"

    classToCompileFor := aClass.
    (classToCompileFor ~~ PrevClass) ifTrue:[
        PrevClass notNil ifTrue:[
            Parser update:PrevClass
        ]
    ]
!

setContext:aContext
    "set the context used while evaluating"

    contextToEvaluateIn := aContext
!

setSelf:anObject
    "set the value to be used for self while evaluating"

    selfValue := anObject.
    classToCompileFor := anObject class.
    (classToCompileFor ~~ PrevClass) ifTrue:[
        PrevClass notNil ifTrue:[
            Parser update:PrevClass
        ]
    ]
!

stringsAreImmutable
    ^ parserFlags stringsAreImmutable.
!

stringsAreImmutable:aBoolean
    parserFlags stringsAreImmutable:aBoolean.
!

warnUndeclared
    ^ parserFlags warnUndeclared

    "Created: 7.9.1997 / 02:05:00 / cg"
!

warnUndeclared:aBoolean
    parserFlags warnUndeclared:aBoolean.

    "Created: 7.9.1997 / 02:05:00 / cg"
!

warnUnusedVars
    ^ parserFlags warnUnusedVars
!

warnUnusedVars:aBoolean
    parserFlags warnUnusedVars:aBoolean.
! !

!Parser methodsFor:'statistic'!

rememberClassVarModified:name 
    modifiedClassVars isNil ifTrue:[
        modifiedClassVars := Set new
    ].
    modifiedClassVars add:name.
    self rememberClassVarUsed:name
!

rememberClassVarRead:name 
    readClassVars isNil ifTrue:[
        readClassVars := Set new
    ].
    readClassVars add:name.
    self rememberClassVarUsed:name
!

rememberClassVarUsed:name 
    usedClassVars isNil ifTrue:[
        usedClassVars := Set new
    ].
    usedClassVars add:name.
    self rememberVariableUsed:name
!

rememberGlobalModified:name 
    modifiedGlobals isNil ifTrue:[
        modifiedGlobals := Set new
    ].
    modifiedGlobals add:name.
    self rememberGlobalUsed:name.
!

rememberGlobalRead:name 
    readGlobals isNil ifTrue:[
        readGlobals := Set new
    ].
    readGlobals add:name.
    self rememberGlobalUsed:name
!

rememberGlobalUsed:name 
    usedGlobals isNil ifTrue:[
        usedGlobals := Set new
    ].
    usedGlobals add:name.
    self rememberVariableUsed:name
!

rememberInstVarModified:name 
    modifiedInstVars isNil ifTrue:[
        modifiedInstVars := Set new
    ].
    modifiedInstVars add:name.
    self rememberInstVarUsed:name.
!

rememberInstVarRead:name 
    readInstVars isNil ifTrue:[
        readInstVars := Set new
    ].
    readInstVars add:name.
    self rememberVariableUsed:name
!

rememberInstVarUsed:name 
    usedInstVars isNil ifTrue:[
        usedInstVars := Set new
    ].
    usedInstVars add:name.
    self rememberVariableUsed:name
!

rememberLocalUsed:name 
    usedLocalVars isNil ifTrue:[
        usedLocalVars := Set new
    ].
    usedLocalVars add:name.

!

rememberReturnedValue:anExpressionNode 
    |expr|

    returnedValues isNil ifTrue:[returnedValues := Set new].

    expr := anExpressionNode.
    expr isAssignment ifTrue:[
        expr := expr expression.
    ].
    (expr isConstant or:[expr isSelf]) ifTrue:[
        returnedValues add:expr
    ].
!

rememberSelectorUsed:sel
    messagesSent isNil ifTrue:[
        messagesSent := IdentitySet new.
    ].
    messagesSent add:sel 
!

rememberSelectorUsed:sel receiver:receiverNode
    self rememberSelectorUsed:sel.
    receiverNode isSuper ifTrue:[
        self rememberSelectorUsedInSuperSend:sel
    ] ifFalse:[
        receiverNode isSelf ifTrue:[
            self rememberSelectorUsedInSelfSend:sel
        ].
    ].
!

rememberSelectorUsedInSelfSend:sel
    messagesSentToSelf isNil ifTrue:[
        messagesSentToSelf := IdentitySet new.
    ].
    messagesSentToSelf add:sel
!

rememberSelectorUsedInSuperSend:sel
    messagesSentToSuper isNil ifTrue:[
        messagesSentToSuper := IdentitySet new.
    ].
    messagesSentToSuper add:sel
!

rememberSymbolUsed:aSymbol
    usedSymbols isNil ifTrue:[
        usedSymbols := IdentitySet new.
    ].
    usedSymbols add:aSymbol 
!

rememberVariableUsed:name 
    usedVars isNil ifTrue:[
        usedVars := Set new
    ].
    usedVars add:name
! !

!Parser::ParseError methodsFor:'accessing'!

description
    |s|

    s := super description.
    s last isSeparator ifFalse:[
        errorMessage size > 0 ifTrue:[
            s := s , ' '
        ]
    ].
    s := s , (errorMessage ? '').
    lineNumber notNil ifTrue:[
        s := s , ' [' , lineNumber asString , ']'
    ].
    ^ s
!

endPosition
    ^ endPosition
!

errorMessage
    ^ errorMessage
!

errorMessage:errorMessageArg startPosition:startPositionArg 
    errorMessage := errorMessageArg.
    startPosition := startPositionArg.
!

errorMessage:errorMessageArg startPosition:startPositionArg endPosition:endPositionArg 
    errorMessage := errorMessageArg.
    startPosition := startPositionArg.
    endPosition := endPositionArg.
!

lineNumber:something
    lineNumber := something.
!

parser
    ^ originator
!

startPosition
    ^ startPosition
! !

!Parser::PrimitiveSpecParser methodsFor:'initialization'!

initialize
    super initialize.

    actionArray := actionArray copy.
    actionArray at:$" codePoint put:(actionArray at:$' codePoint).

    "Created: / 01-08-2006 / 14:39:24 / cg"
! !

!Parser::PrimitiveSpecParser methodsFor:'parsing'!

parseSTVExternalFunctionDeclarationFrom:aStream definitionType:definitionType lineNr:lineNr for:aParserOrNil
    "parses ST/V function declarations of the forms 
        '<api: functionName argType1 .. argTypeN returnType>' 
        '<ccall: functionName argType1 .. argTypeN returnType>' 
        '<ole: vFunctionIndex argType1 .. argTypeN returnType>'
    "

    |returnType functionName argTypes type 
     function typeFromSTVTypeSpec virtualFunctionIndex|

    masterParser := aParserOrNil.

    self source:aStream.
    self nextToken.

    (definitionType = 'ole:') ifTrue:[
        (tokenType == #Integer) ifFalse:[
            self parseError:'virtual function number expected (got ' , token printString , ')'.
        ].
        virtualFunctionIndex := token.
        self nextToken.
    ] ifFalse:[ 
        (tokenType == #Identifier) ifFalse:[
            self parseError:'function identifier expected (got ' , token printString , ')'.
        ].
        functionName := token asSymbol.
        self nextToken.
    ].

    argTypes := OrderedCollection new.
    [ token notNil and:[ (token ~= '>') and:[ (tokenType ~~ #BinaryOperator) or:[tokenName ~= '>']]]] whileTrue:[
        argTypes add:(self typeMappingFor:token).
        self nextToken.
    ].
    returnType := argTypes last.
    argTypes := argTypes copyWithoutLast:1.

    function := ExternalLibraryFunction 
            name:(functionName ? virtualFunctionIndex)
            module:nil 
            returnType:returnType
            argumentTypes:argTypes asArray.

    (definitionType = 'api:') ifTrue:[
        function beCallTypeAPI
    ] ifFalse:[ 
        (definitionType = 'ole:') ifTrue:[
            function beCallTypeOLE
        ] ifFalse:[
            function beCallTypeC
        ].
    ].
    ^ function

    "Created: / 01-08-2006 / 16:11:24 / cg"
    "Modified: / 07-06-2007 / 13:13:20 / cg"
!

parseSTXOrSqueakOrDolphinExternalFunctionDeclarationFrom:aStream definitionType:definitionType lineNr:lineNrArg for: aParserOrNil
    "parses squeak/dolphin function declarations of the forms 
        '<stdcall: [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>'
        '<cdecl:   [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>' 

        '<cdecl:   [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >' 
        '<apicall: [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >'
    "

    |isVirtualCall isNonVirtualCall isAsyncCall isUnlimitedStack isConst scanningCallModifiers
    returnType functionName virtualFunctionIndex argTypes moduleName argType function 
    parentized thisType|

    masterParser := aParserOrNil.
    isVirtualCall := isNonVirtualCall := isAsyncCall := isUnlimitedStack := isConst := false.

    "/ self knownDefinitions:dictionaryOfTypesOrNil.
    self source:aStream.
    lineNr := lineNrArg.

    self nextToken.

    scanningCallModifiers := true.    
    [scanningCallModifiers] whileTrue:[    
        scanningCallModifiers := false.
        (tokenType == #Identifier) ifTrue:[
            (token = 'async') ifTrue:[
                self nextToken.
                isAsyncCall := true.
                scanningCallModifiers := true.
            ] ifFalse:[ (token = 'virtual') ifTrue:[
                self nextToken.
                isVirtualCall := true.
                scanningCallModifiers := true.
            ] ifFalse:[  (token = 'nonVirtual') ifTrue:[
                self nextToken.
                isNonVirtualCall := true.
                scanningCallModifiers := true.
            ] ifFalse:[  (token = 'unlimitedStack') ifTrue:[
                self nextToken.
                isUnlimitedStack := true.
                scanningCallModifiers := true.
            ] ifFalse:[  (token = 'const') ifTrue:[
                self nextToken.
                isConst := true.
                scanningCallModifiers := true.
            ]]]]]
        ]
    ].

    returnType := self parseTypeSpec.

    isVirtualCall ifTrue:[
        tokenType ~~ #Integer ifTrue:[
            (masterParser ? self) ignorableParseError:'invalid cdecl - virtual function index expected'. 
            ^ nil
        ].
        virtualFunctionIndex := token.
        self nextToken.
    ] ifFalse:[
        tokenType ~~ #String ifTrue:[
            (masterParser ? self) ignorableParseError:'invalid cdecl - functionName expected'. 
            ^ nil
        ].
        functionName := token asSymbol.
        self nextToken.
    ].

    tokenType = $( ifTrue:[
        parentized := true.
        self nextToken.
    ] ifFalse:[
        parentized := false.
    ].

    argTypes := OrderedCollection new.
    [ tokenType == #EOF
      or:[ parentized and:[tokenType = $) ]] ] whileFalse:[
        argType := self parseTypeSpec.
        argTypes add:argType.
        (tokenType = $, 
        or:[ tokenType == #BinaryOperator and:[token = ','] ]) ifTrue:[
            self nextToken
        ]
    ].
    tokenType = $) ifTrue:[
        self nextToken.
    ].

    ((tokenType == #Identifier and:[token = 'module'])
    or:[tokenType == #Keyword and:[ token = 'module:']]) ifTrue:[
        self nextToken.
        tokenType == $: ifTrue:[
            self nextToken.
        ].

        tokenType ~~ #String ifTrue:[
            (masterParser ? self) ignorableParseError:'Invalid declaration - moduleName expected'.
            ^ nil
        ].
        moduleName := token asSymbol.
    ].
    (argTypes size == 1 and:[argTypes first == #void "isCVoid"]) ifTrue:[
        argTypes := #()
    ].

    isNonVirtualCall ifTrue:[
        (classToCompileFor isSubclassOf:ExternalStructure) ifTrue:[
            thisType := classToCompileFor name.    
"/            (thisType := classToCompileFor cType) isNil ifTrue:[ 
"/                "/ self warning:'missing CType definition in ' , tok printString.
"/                thisType := CType newStructType.
"/                thisType name:(classToCompileFor nameWithoutPrefix).
"/                thisType := CType pointerTypeClass new baseType:thisType.
"/            ].
        ].
        thisType := thisType ? #pointer.
        argTypes := (Array with:thisType) , argTypes.
    ].

    function := ExternalLibraryFunction 
            name:(functionName ? virtualFunctionIndex)
            module:moduleName 
            returnType:returnType
            argumentTypes:argTypes asArray.

    (definitionType = 'apicall:') ifTrue:[
        function beCallTypeAPI
    ] ifFalse:[ 
        (definitionType = 'olecall:') ifTrue:[
            function beCallTypeOLE
        ] ifFalse:[
            function beCallTypeC
        ].
    ].
    isNonVirtualCall ifTrue:[
        function beNonVirtualCPP
    ].
    isAsyncCall ifTrue:[
        function beAsync
    ].
    isUnlimitedStack ifTrue:[
        function beUnlimitedStack
    ].
    isConst ifTrue:[
        function beConstReturnValue
    ].
    ^ function

    "Created: / 25-10-2006 / 12:03:59 / cg"
    "Modified: / 07-06-2007 / 13:13:35 / cg"
!

parseTypeSpec
    |type typeName ns cls|

    typeName := token.
    self nextToken.

    ((tokenType == #'::') or:[(tokenType == #'.')]) ifTrue:[
        "/ namespace...
        [(tokenType == #'::')  or:[(tokenType == #'.')]] whileTrue:[
            typeName := typeName , '::'.
            self nextToken.
            tokenType ~~ #Identifier ifTrue:[
                (masterParser ? self) parseError:'invalid type identifier'.
            ].
            typeName := typeName , token.
            self nextToken.
         ]
    ].

    type := self typeMappingFor:typeName.
    [(tokenType = $*) 
        or:[((tokenType == #BinaryOperator) and:[tokenName = '*'])
        or:[(tokenType == #BinaryOperator) and:[tokenName = '**']]]
    ] whileTrue:[
        type := self pointerTypeMappingFor:type.
        tokenName = '**' ifTrue:[
            type := self pointerTypeMappingFor:type.
        ].
        self nextToken.
    ].

    type first isUppercase ifTrue:[
        (ns := classToCompileFor nameSpace) notNil ifTrue:[
            cls := ns at:type.
        ].
        cls isNil ifTrue:[
            cls := Smalltalk at:type.
        ].
        cls isNil ifTrue:[
            (masterParser ? self) ignorableParseError:'possibly unknown type: ', type allBold.
        ] ifFalse:[
            cls autoload.    
            (cls isSubclassOf:ExternalBytes) ifFalse:[
                (masterParser ? self) ignorableParseError:'possibly wrong type: ', type allBold.
            ].
            type := cls name.
        ].
    ].

    ^ type

    "Modified: / 07-06-2007 / 13:14:59 / cg"
!

parseVWTypeOrExternalFunctionDeclarationFrom:aStream definitionType:definitionType knownDefinitions:dictionaryOfTypesOrNil lineNr:lineNr for:aParserOrNil
    "parses visualWorks type/function declarations of the form: 
        '<c: ...>'
        '<c: #define NAME value>'"

    |cParser moduleName type name
     nameAndFunctionOrType functionOrType function |

    masterParser := aParserOrNil.

    self source:aStream.
    self nextToken.
    ((tokenType == #Symbol) and:[token = #define]) ifTrue:[
        self nextToken.
        (tokenType == #Identifier) ifFalse:[
            (masterParser ? self) ignorableParseError:'invalid cdecl - identifier expected'.
            self generateTrapCodeForUnavailableCParser.
            ^ nil.
        ].
        name := token.
        self nextToken.
        "/ for now, only allow integer, string or floats.
        (#(Integer String Float) includes:tokenType) ifTrue:[
            ^ token
        ].
        (masterParser ? self) ignorableParseError:'invalid cdecl - integer, float or string expected'.
        self generateTrapCodeForUnavailableCParser.
        ^ nil.
    ].

    aStream reset.

    CParser isNil ifTrue:[
        self generateTrapCodeForUnavailableCParser.
        ^ nil.
    ].

    cParser := CParser new.
    cParser knownDefinitions:dictionaryOfTypesOrNil.
    cParser allowRedefinitions:true.
    cParser source:aStream scannerClass:CDeclScanner.
    cParser nextToken.

    cParser tokenType == #struct ifTrue:[
        type := cParser type.
    ] ifFalse:[
        cParser tokenType == #typedef ifTrue:[
            type := cParser typedef.
        ] ifFalse:[
            nameAndFunctionOrType := cParser typeOrFunctionDeclaration.
            functionOrType := nameAndFunctionOrType second.
            functionOrType isCFunction ifFalse:[
                type := functionOrType.
                function := nil.
            ] ifTrue:[
                function := functionOrType.
                type := nil.
            ].
        ]
    ].
    cParser token notNil ifTrue:[
        (masterParser ? self) ignorableParseError:'invalid cdecl - nothing more expected'.
        ^ nil.
    ].
    type notNil ifTrue:[
        ^ type.
    ].

    moduleName isNil ifTrue:[
        moduleName := classToCompileFor theNonMetaclass libraryName asSymbol.
    ].

    function := ExternalLibraryFunction 
            name:function name 
            module:moduleName 
            returnType:function returnType
            argumentTypes:function argumentTypes asArray.

    function beCallTypeC.    
    ^ function

    "Created: / 01-08-2006 / 16:18:05 / cg"
    "Modified: / 07-06-2007 / 13:14:06 / cg"
! !

!Parser::PrimitiveSpecParser methodsFor:'parsing-primitives & pragmas'!

pointerTypeMappingFor: aTypeSymbol
    "given a type, make it a 'pointer to that-type'"
    |e|

    e := #(
        (void            voidPointer    )
        (voidPointer         voidPointerPointer )
        (voidPointerPointer  voidPointerPointer )
        (char            charPointer    )
        (byte            bytePointer    )
        (uint8           uint8Pointer   )
        (uint16          uint16Pointer  )
        (uint32          uint32Pointer  )
        (int16           int16Pointer   )
        (int32           int32Pointer   )
        (int             intPointer     )
        (short           shortPointer   )
        (ushort          ushortPointer  )
        (long            longPointer    )
        (uint            uintPointer    )
        (ulong           ulongPointer   )
        (float           floatPointer   )
        (double          doublePointer  )
    ) detect:[:p | p first = aTypeSymbol] ifNone:nil.
    e notNil ifTrue:[
        ^ e second
    ].
    (masterParser ? self) ignorableParseError:'missing pointer type mapping for type: ', aTypeSymbol allBold.
    ^ #pointer "/ aTypeSymbol asSymbol

    "Created: / 01-08-2006 / 15:33:53 / cg"
    "Modified: / 11-06-2007 / 01:51:26 / cg"
!

typeMappingFor:aTypeSymbol
    |e|

    e := #(
        (short           int16          )
        (long            int32          )
        (int             int32          )
        (ushort          uint16         )
        (ulong           uint32         )
        (unsignedByte    uint8          )
        (unsignedChar    uint8          )
        (unsignedShort   uint16         )
        (unsignedLong    uint32         )
        (double          double         )
        (float           float          )
        (char            char           )
        (uchar           uint8          )
        (byte            uint8          )
        (void            void           )
        (bool            bool           )
        (boolean         bool           )
        (dword           uint32         )
        (sdword          int32          )
        (word            uint16         )
        (sword           int16          )
        (handle          voidPointer    )
        (lpstr           charPointer    )
        (hresult         uint32         )
        (ulongReturn     uint32         )
        (none            void           )
        (struct          voidPointer    )
        (structIn        voidPointer    )
        (structOut       voidPointer    )
    ) detect:[:p | p first = aTypeSymbol] ifNone:nil.

    e notNil ifTrue:[ ^ e second ].

"/ the following is now done in ExternalFunction (if at all), as the ctype is not required to
"/ be present right now, and also to allow for stc-compilation, where no
"/ ctypes are avaliable at all.

"/            e isNil ifTrue:[
"/                cls := classToCompileFor nameSpace classNamed:tok.
"/                cls isNil ifTrue:[
"/                    cls := Smalltalk classNamed:tok.
"/                ].
"/                cls notNil ifTrue:[
"/                    (cls isSubclassOf:ExternalStructure) ifTrue:[
"/                        (cType := cls cType) isNil ifTrue:[ 
"/                            "/ self warning:'missing CType definition in ' , tok printString.
"/                            cType := CType newStructType.
"/                            cType name:cls name.
"/                        ].
"/                        cType
"/                    ] ifFalse:[
"/                        cls
"/                    ].
"/                ] ifFalse:[
"/                    self parseError:'ulong, ushort, or another valid Squeak type identifier expected (got ' , tok printString , ')'.
"/                    nil
"/                ]
"/            ] ifFalse:[
"/                e second
"/            ].

    ^ aTypeSymbol asSymbol

    "Created: / 01-08-2006 / 15:35:52 / cg"
    "Modified: / 14-06-2007 / 17:18:54 / cg"
! !

!Parser::PrimitiveSpecParser methodsFor:'reading next token'!

isCommentCharacter:ch
    "no comments"

    ^ false

    "Created: / 01-08-2006 / 14:54:48 / cg"
! !

!Parser::UndefinedVariableNotification methodsFor:'accessing'!

description
    ^ 'undefined variable: ' , self variableName
!

parser
    "return the value of the instance variable 'parser' (automatically generated)"

    ^ parser
!

parser:something
    "set the value of the instance variable 'parser' (automatically generated)"

    parser := something.
!

variableName
    ^ parameter
! !

!Parser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.573 2008-05-28 09:42:30 cg Exp $'
! !

Parser initialize!