ParserFlags.st
author Claus Gittinger <cg@exept.de>
Sat, 08 Jun 2019 16:16:19 +0200
changeset 4438 bd363f7ca282
parent 4437 5155327c7c91
child 4449 25db115428a7
permissions -rw-r--r--
#FEATURE by cg class: Scanner changed: #nextToken

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1989 by Claus Gittinger
 COPYRIGHT (c) 2005 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libcomp' }"

"{ NameSpace: Smalltalk }"

Object subclass:#ParserFlags
	instanceVariableNames:'warnings warnUnusedVars warnUndeclared warnST80Directives
		warnSTXHereExtensionUsed warnSTXSpecialComment
		warnUnderscoreInIdentifier warnOldStyleAssignment
		warnCommonMistakes warnSTXNameSpaceUse
		warnPossibleIncompatibilities warnDollarInIdentifier
		warnParagraphInIdentifier warnHiddenVariables
		warnAboutVariableNameConventions warnAboutWrongVariableNames
		warnAboutBadComments warnInconsistentReturnValues
		warnAboutNonLowercaseLocalVariableNames
		warnAboutPossibleSTCCompilationProblems
		warnAboutReferenceToPrivateClass warnAboutShortLocalVariableNames
		warnAboutPossiblyUnimplementedSelectors
		warnAboutUnknownCharacterEscapesInJavaScriptStringConstant
		warnPlausibilityChecks allowLiteralNameSpaceSymbols
		allowUnderscoreInIdentifier allowDollarInIdentifier
		allowParagraphInIdentifier allowOldStyleAssignment
		allowSqueakExtensions allowDolphinExtensions
		allowExtendedBinarySelectors allowQualifiedNames
		allowFunctionCallSyntaxForBlockEvaluation
		allowLocalVariableDeclarationWithInitializerExpression
		allowDomainVariables allowArrayIndexSyntaxExtension
		allowReservedWordsAsSelectors allowVariableReferences
		allowLazyValueExtension allowFixedPointLiterals
		allowExtendedSTXSyntax allowVisualAgeESSymbolLiterals
		allowExtensionsToPrivateClasses allowSqueakPrimitives
		allowVisualAgePrimitives allowSTVPrimitives allowSTVExtensions
		allowNationalCharactersInIdentifier allowHashAsBinarySelector
		allowSTXEOLComments allowEmptyStatements
		allowVisualWorksMethodAnnotations
		allowPossibleSTCCompilationProblems arraysAreImmutable
		stringsAreImmutable implicitSelfSends stcKeepCIntermediate
		stcKeepOIntermediate stcKeepSTIntermediate stcModulePath
		stcCompilation stcCompilationIncludes stcCompilationDefines
		stcCompilationOptions stcPath ccCompilationOptions ccPath
		linkArgs linkSharedArgs linkCommand libPath searchedLibraries
		warnAboutPeriodInSymbol allowPeriodInSymbol allowCaretAsBinop
		allowUnicodeStrings allowUnicodeCharacters allowCharacterEscapes
		allowStringEscapes allowAssignmentToBlockArgument
		allowAssignmentToMethodArgument allowAssignmentToPoolVariable
		lineNumberInfo allowSTXDelimiterComments
		allowSTXExtendedArrayLiterals warnAssignmentToBlockArgument
		warnAssignmentToMethodArgument warnAssignmentToPoolVariable
		allowSignedByteArrayElements allowSymbolsStartingWithDigit
		allowJavaScriptConst allowPeriodAsNameSpaceSeparator
		allowCStrings warnAboutPossiblyUninitializedLocals allowEStrings
		singlePrecisionFloatF allowRStrings
		allowGreekCharactersInIdentifier'
	classVariableNames:'AllowArrayIndexSyntaxExtension AllowAssignmentToBlockArgument
		AllowAssignmentToMethodArgument AllowAssignmentToPoolVariable
		AllowCaretAsBinop AllowCharacterEscapes AllowDollarInIdentifier
		AllowDolphinExtensions AllowDomainVariables AllowEmptyStatements
		AllowExtendedBinarySelectors AllowExtendedSTXSyntax
		AllowExtensionsToPrivateClasses AllowFixedPointLiterals
		AllowFunctionCallSyntaxForBlockEvaluation
		AllowHashAsBinarySelector AllowLazyValueExtension
		AllowLiteralNameSpaceSymbols
		AllowLocalVariableDeclarationWithInitializerExpression
		AllowNationalCharactersInIdentifier AllowOldStyleAssignment
		AllowParagraphInIdentifier AllowPeriodInSymbol
		AllowPossibleSTCCompilationProblems AllowQualifiedNames
		AllowReservedWordsAsSelectors AllowSTVExtensions
		AllowSTVPrimitives AllowSTXDelimiterComments AllowSTXEOLComments
		AllowSTXExtendedArrayLiterals AllowSqueakExtensions
		AllowSqueakPrimitives AllowStringEscapes
		AllowUnderscoreInIdentifier AllowUnicodeCharacters
		AllowUnicodeStrings AllowVariableReferences
		AllowVisualAgeESSymbolLiterals AllowVisualAgePrimitives
		AllowVisualWorksMethodAnnotations ArraysAreImmutable BCCTop
		CCCompilationOptions CCPath DefineForBorlandC DefineForCLANG
		DefineForGNUC DefineForMINGW DefineForMINGW32 DefineForMINGW64
		DefineForMSC DefineForVisualC ForcedCompiler ImplicitSelfSends
		LibDirectory LibPath LineNumberInfo LinkArgs LinkCommand
		LinkSharedArgs MakeCommand MingwTop PerMethodFlags SDKTop
		STCCompilation STCCompilationDefines STCCompilationIncludes
		STCCompilationOptions STCKeepCIntermediate STCKeepOIntermediate
		STCKeepSTIntermediate STCModulePath STCPath SearchedLibraries
		StringsAreImmutable VCTop WarnAboutBadComments
		WarnAboutNonLowercaseLocalVariableNames WarnAboutPeriodInSymbol
		WarnAboutPossibleSTCCompilationProblems
		WarnAboutPossiblyUnimplementedSelectors
		WarnAboutReferenceToPrivateClass WarnAboutShortLocalVariableNames
		WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant
		WarnAboutVariableNameConventions WarnAboutWrongVariableNames
		WarnAssignmentToBlockArgument WarnAssignmentToMethodArgument
		WarnAssignmentToPoolVariable WarnCommonMistakes
		WarnDollarInIdentifier WarnHiddenVariables
		WarnInconsistentReturnValues WarnOldStyleAssignment
		WarnParagraphInIdentifier WarnPlausibilityChecks
		WarnPossibleIncompatibilities WarnST80Directives WarnSTXSpecials
		WarnUndeclared WarnUnderscoreInIdentifier WarnUnusedVars Warnings
		AutoDefineVariables AllowSignedByteArrayElements
		AllowSymbolsStartingWithDigit AllowJavaScriptConst
		AllowJavaScriptLet AllowPeriodAsNameSpaceSeparator AllowCStrings
		WarnAboutPossiblyUninitializedLocals AllowEStrings
		SinglePrecisionFloatF AllowRStrings
		AllowGreekCharactersInIdentifier'
	poolDictionaries:''
	category:'System-Compiler'
!

!ParserFlags class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
 COPYRIGHT (c) 2005 by eXept Software AG
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    compiler flags (used to be defined in Scanner and Parser) have been extracted for easier
    individual-method customization (using ST as scripting).

    The class side provides correspondingly-named variables, which hold the default values.

    howTo_fileInVSE:
        ParserFlags allowSTVExtensions:true.
        ParserFlags allowSTVPrimitives:true.
        ParserFlags allowSTXEOLComments:false.

    for stx debugging:
        STCKeepCIntermediate := true

    the flags control:
        Warnings                            -- enable/disable any warnings from the compiler
          WarnUndeclared                    -- warn about undeclared variables
          WarnUnusedVars                    -- warn about unused variables
          WarnST80Directives                -- warn when ST80 (visualworks) directives (primitives) are used
          WarnAboutWrongVariableNames       -- conventions / style
          WarnAboutVariableNameConventions 
          WarnAboutNonLowercaseLocalVariableNames
          WarnAboutShortLocalVariableNames
          WarnAboutBadComments 
          WarnCommonMistakes
          WarnAboutReferenceToPrivateClass
        WarnPossibleIncompatibilities
          WarnSTXSpecials                   -- warn when special ST/X syntax extensions are used
          WarnUnderscoreInIdentifier        -- underscores in identifier (not all Smalltalk dialects support this)
          WarnDollarInIdentifier            -- dollar in identifier (not all Smalltalk dialects support this)
          WarnParagraphInIdentifier         -- paragraph character in identifier
          WarnOldStyleAssignment            -- assignment with _ - character
          WarnHiddenVariables               -- locals shadowing outer/instvars
          WarnInconsistentReturnValues      -- boolean/non-boolean return values
          WarnAboutPeriodInSymbol
          WarnAboutPossibleSTCCompilationProblems
          WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant
          WarnAssignmentToBlockArgument 
          WarnAssignmentToMethodArgument
          WarnAssignmentToPoolVariable
        WarnPlausibilityChecks
          WarnAboutPossiblyUnimplementedSelectors

       AllowReservedWordsAsSelectors
       AllowUnderscoreInIdentifier 
       AllowParagraphInIdentifier 
       AllowDollarInIdentifier              -- st80-vms dollars in identifiers
       AllowOldStyleAssignment              -- st80 underscore as assignment
       AllowDolphinExtensions               -- dolphin computed literal
       AllowQualifiedNames                  -- vw3 qualified names
       AllowExtendedBinarySelectors         -- vw5.4 extended binary selectors (plus/minus, center-dot etc.)
       AllowCaretAsBinop                    -- too dangerous
       AllowLiteralNameSpaceSymbols         -- st/x literal nameSpace-symbols (#foo::bar)
       AllowArrayIndexSyntaxExtension 
       AllowFunctionCallSyntaxForBlockEvaluation 
       AllowLocalVariableDeclarationWithInitializerExpression 
       AllowDomainVariables 
       AllowArrayIndexSyntaxExtension 
       AllowReservedWordsAsSelectors 
       AllowVariableReferences 
       AllowLazyValueExtension 
       AllowFixedPointLiterals 
       AllowExtendedSTXSyntax 
       AllowVisualAgeESSymbolLiterals 
       AllowExtensionsToPrivateClasses 
       AllowVisualAgePrimitives 
       AllowSqueakExtensions                -- squeak computed array
       AllowSqueakPrimitives 
       AllowSTVPrimitives                   -- number-sign syntax
       AllowSTVExtensions 
       AllowNationalCharactersInIdentifier 
       AllowHashAsBinarySelector 
       AllowSTXEOLComments                  -- DQuote/ EOL comments
       AllowSTXDelimiterComments            -- DQuote<<END delimiter comments
       AllowVisualWorksMethodAnnotations 
       AllowPossibleSTCCompilationProblems  -- must be true, to allow fileIn
       AllowEmptyStatements 
       AllowPeriodInSymbol 
       AllowPeriodAsNameSpaceSeparator 

       AllowCStrings                        -- c'....' is a string with C-escapes
       AllowUnicodeStrings 
       AllowUnicodeCharacters 
       AllowCharacterEscapes 
       AllowStringEscapes 
       AllowAssignmentToBlockArgument 
       AllowAssignmentToMethodArgument 
       AllowAssignmentToPoolVariable 
       AllowSignedByteArrayElements 
       AllowSymbolsStartingWithDigit 

       AllowJavaScriptConst               

       ArraysAreImmutable                 -- still care for ST-80 compatibility
       StringsAreImmutable                -- still care for ST-80 compatibility
       ImplicitSelfSends 
    
"
! !

!ParserFlags class methodsFor:'instance creation'!

new
    ^ self basicNew initialize
! !

!ParserFlags class methodsFor:'accessing-compilation control'!

allowExtensionsToPrivateClasses
    ^ AllowExtensionsToPrivateClasses
!

allowExtensionsToPrivateClasses:aBoolean
    AllowExtensionsToPrivateClasses := aBoolean
!

allowPossibleSTCCompilationProblems
    ^ AllowPossibleSTCCompilationProblems

    "
     self allowPossibleSTCCompilationProblems:true
     self allowPossibleSTCCompilationProblems:false

     self warnAboutPossibleSTCCompilationProblems
    "

    "Created: / 16-11-2006 / 14:31:36 / cg"
!

allowPossibleSTCCompilationProblems:aBoolean
    AllowPossibleSTCCompilationProblems := aBoolean

    "Created: / 16-11-2006 / 14:31:40 / cg"
!

arraysAreImmutable
    "return true if arrays and byteArrays are compiled as immutable literals"

    ^ ArraysAreImmutable
!

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

    ArraysAreImmutable := aBoolean.

    "
     can be added to your private.rc file:

     ParserFlags arraysAreImmutable:true
     ParserFlags arraysAreImmutable:false
    "
!

fullLineNumberInfo
    ^ (self lineNumberInfo == #full)

    "Created: / 26-09-2012 / 14:16:09 / cg"
!

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

    ^ ImplicitSelfSends
!

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

    ImplicitSelfSends := aBoolean

    "
     Compiler implicitSelfSends:true
     Compiler implicitSelfSends:false
    "
!

lineNumberInfo
    ^ LineNumberInfo

    "Created: / 26-09-2012 / 13:27:34 / cg"
!

lineNumberInfo:aSymbol
    LineNumberInfo := aSymbol.

    "Created: / 26-09-2012 / 13:27:54 / cg"
!

stringsAreImmutable
    "return true if strings are immutable literals"

    ^ StringsAreImmutable

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

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

    StringsAreImmutable := aBoolean.

    "
     can be added to your private.rc file:

     ParserFlags stringsAreImmutable:true
     ParserFlags stringsAreImmutable:false
    "

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

!ParserFlags class methodsFor:'accessing-per method flags'!

disableFlag:flagName forClass:class selector:selector
    "remember that warnings named flagName (such as #warnUnusedVars)
     are disabled for a particular method.
     Sent if user wants to disable warnings in the future
     (try defining a method with an unused var, to see)"

    |key|

    PerMethodFlags isNil ifTrue:[
	PerMethodFlags := Dictionary new.
    ].
    key := class name, '>>',selector.
    PerMethodFlags at:key put:(Timestamp now + self perMethodDisableWarningTimeDuration).

    "Created: / 28-02-2012 / 12:57:45 / cg"
!

isFlag:flagName enabledForClass:class selector:selector
    "return true, if warnings named <flagName> (such as #warnUnusedVars)
     are to be suppressed for a particular method."

    |key endTime|

    PerMethodFlags isNil ifTrue:[^ true].
    class isNil ifTrue:[^ true].
    selector isNil ifTrue:[^ true].

    key := class name, '>>',selector.
    endTime := PerMethodFlags at:key ifAbsent:nil.
    endTime isNil ifTrue:[^ true].
    endTime > Timestamp now ifTrue:[^ false].
    PerMethodFlags removeKey:key.
    ^ true

    "Created: / 28-02-2012 / 12:57:30 / cg"
!

perMethodDisableWarningTimeDuration
    "when the user wants to suppress a particular warning for a particular
     method, it will be only suppressed for some time duration.
     After that, the suppress will automatically be removed, and normal warnings
     are issued again."

    ^ 30 minutes

    "Created: / 08-03-2012 / 10:22:57 / cg"
!

reenableAllSuppressedFlags
    "turn off any suppressed warnings"

    PerMethodFlags := nil

    "Created: / 28-02-2012 / 12:59:08 / cg"
! !

!ParserFlags class methodsFor:'accessing-stc compilation control'!

bccTop:aPath
    "windows only: define the borland-C installation directory.
     must contain bin\bcc32.exe and include.
     Typically, something like 'C:\borland\bcc55'"

    BCCTop := aPath

    "Created: / 08-08-2011 / 22:41:48 / cg"
!

ccCompilationOptions
    ^ CCCompilationOptions ? ''
!

ccCompilationOptions:aString
    CCCompilationOptions := aString
!

ccPath
    ^ CCPath
!

ccPath:aSymbol
    CCPath := aSymbol
!

libDirectory
    ^ LibDirectory

    "Created: / 07-08-2011 / 14:01:21 / cg"
!

libDirectory:aString
    LibDirectory := aString

    "Created: / 07-08-2011 / 14:01:28 / cg"
!

libPath
    ^ LibPath
!

libPath:aString
    LibPath := aString
!

linkArgs
    ^ LinkArgs
!

linkArgs:aString
    LinkArgs := aString
!

linkCommand
    ^ LinkCommand
!

linkCommand:aString
    LinkCommand := aString
!

linkSharedArgs
    ^ LinkSharedArgs
!

linkSharedArgs:aString
    LinkSharedArgs := aString

    "Modified (format): / 28-02-2012 / 13:34:58 / cg"
!

makeCommand
    ^ MakeCommand

    "Created: / 09-08-2006 / 18:45:04 / fm"
!

makeCommand:aString
    MakeCommand := aString

    "Created: / 09-08-2006 / 18:45:12 / fm"
!

sdkTop:aPath
    "windows only: define the SDK top directory.
     must include folder with windows header files.
     Typically something like 'C:\Program Files\Microsoft SDKs\Windows\v6.0A'"

    SDKTop := aPath

    "Created: / 08-08-2011 / 22:39:24 / cg"
!

searchedLibraries
    ^ SearchedLibraries
!

searchedLibraries:aString
    SearchedLibraries := aString
!

stcCompilation
    ^ STCCompilation
!

stcCompilation:aSymbol
    STCCompilation := aSymbol
!

stcCompilationDefines
    ^ STCCompilationDefines
!

stcCompilationDefines:aString
    STCCompilationDefines := aString
!

stcCompilationIncludes
    ^ STCCompilationIncludes
!

stcCompilationIncludes:aString
    STCCompilationIncludes := aString
!

stcCompilationOptions
    ^ STCCompilationOptions
!

stcCompilationOptions:aString
    STCCompilationOptions := aString
!

stcKeepCIntermediate
    ^ STCKeepCIntermediate ? false

    "Modified: / 16-09-2011 / 19:56:18 / cg"
!

stcKeepCIntermediate:aBoolean
    STCKeepCIntermediate := aBoolean.

    "
     STCKeepCIntermediate := true.
     STCKeepCIntermediate := false.
    "

    "Modified: / 07-11-2006 / 10:58:42 / cg"
!

stcKeepOIntermediate
    ^ STCKeepOIntermediate ? false

    "Modified: / 16-09-2011 / 19:56:49 / cg"
!

stcKeepOIntermediate:aBoolean
    STCKeepOIntermediate := aBoolean.

    "
     STCKeepOIntermediate := true.
     STCKeepOIntermediate := false.
    "
!

stcKeepSTIntermediate
    ^ STCKeepSTIntermediate ? false

    "
     STCKeepSTIntermediate := true.
     STCKeepSTIntermediate := false.
    "

    "Modified: / 16-09-2011 / 19:57:17 / cg"
!

stcKeepSTIntermediate:aBoolean
    STCKeepSTIntermediate := aBoolean.

    "
     STCKeepSTIntermediate := true.
     STCKeepSTIntermediate := false.
    "

    "Modified: / 07-11-2006 / 10:58:54 / cg"
!

stcModulePath
    "the folder, where temporarily compiled modules are created by stc.
     Used to be inside the bin-directory, but that did not work for readonly/shared
     st/x installations (i.e. running stx from a mounted dbg).
     Therefore, this is now in the workspace (where the snapshot image resudes as well)
     
     Notice: 
        this ought to be a persistent folder (at least as along as any
        snapshot image is present, which refers to any module there.
        As we cannot (currently) scan snapshots, this is somewhat tricky."
        
    STCModulePath notNil ifTrue:[^ STCModulePath].    
    ^ UserPreferences current workspaceDirectory  / 'modules'     
!

stcModulePath:aPath
    "set the path to the directory, where temporary modules are created.
     Obsolete now, as this should not be set from the outside,
     but instead rely totally on the userPreferences."

    STCModulePath := aPath.
!

stcPath
    ^ STCPath
!

stcPath:aPath
    STCPath := aPath
!

useBorlandC
    "true if borland compiler should be used"

    ^ self usedCompilerDefine = DefineForBorlandC

    "Created: / 15-03-2007 / 13:33:32 / cg"
!

useClang
    "true if clang compiler should be used"

    ^ self usedCompilerDefine = DefineForCLANG
!

useCompilerDefine: aCompilerDefine
    "enforce a particular compiler to be used (independent from
     what the system was compiled with)"

    ForcedCompiler := aCompilerDefine.

    "
     self useCompiler: DefineForBorlandC
     self useCompiler: DefineForVisualC
     self useCompiler: DefineForMINGW32
    "

    "Created: / 20-07-2012 / 13:10:30 / cg"
!

useGnuC
    "true if gnu-c compiler should be used"

    ^ self usedCompilerDefine = DefineForGNUC

    "Created: / 15-03-2007 / 13:34:49 / cg"
!

useMingw32
    "true if mingw compiler should be used"

    ^ self usedCompilerDefine = DefineForMINGW32
!

useMingw64
    "true if mingw compiler should be used"

    ^ self usedCompilerDefine = DefineForMINGW64
!

useVisualC
    "true if visual-c compiler should be used"

    |def|

    ^ (def := self usedCompilerDefine) = DefineForVisualC
    or:[ def = DefineForMSC ]

    "Created: / 08-08-2011 / 22:50:25 / cg"
!

usedCompiler
    |dfn|

    dfn := self usedCompilerDefine.

    dfn = DefineForGNUC ifTrue:[ ^'gcc'].
    dfn = DefineForBorlandC ifTrue:[ ^'bcc'].
    dfn = DefineForMSC ifTrue:[ ^'vc'].
    dfn = DefineForVisualC ifTrue:[ ^'vc'].
    dfn = DefineForMINGW64 ifTrue:[ ^'mingw'].
    dfn = DefineForMINGW32 ifTrue:[ ^'mingw'].
    dfn = DefineForMINGW ifTrue:[ ^'mingw'].
"/    dfn = DefineForLCC ifTrue:[ ^'lcc'].

    OperatingSystem isMSWINDOWSlike ifTrue:[
	^ 'bcc'
    ].
    ^ 'gcc'

    "
     self usedCompiler
    "

    "Created: / 31-01-2012 / 12:05:30 / cg"
!

usedCompilerDefine
    "return the define to be used for the compiler toolchain.
     By default, the toolchain with which stx itself was compiled is used (getCCDefine);
     can be overwritten by setting ForcedCompiler"

    ^ ForcedCompiler ? STCCompilerInterface getCCDefine.

    "
     ForcedCompiler := DefineForCLANG.
     self usedCompilerDefine.
     
     ForcedCompiler := nil.
     self usedCompilerDefine.
    "

    "Created: / 20-07-2012 / 13:11:22 / cg"
    "Modified: / 11-05-2018 / 09:44:34 / stefan"
!

vcTop:aPath
    "windows only: define the visual-C top directory.
     must contain bin\cl.exe and include.
     Typically, something like 'C:\Program Files\Microsoft Visual Studio 10.0\VC'"

    VCTop := aPath

    "Created: / 08-08-2011 / 22:39:15 / cg"
!

withSTCCompilation:howSymbol do:aBlock
    |prev|

    prev := self stcCompilation.
    self stcCompilation:howSymbol.
    aBlock ensure:[ self stcCompilation:prev ]
! !

!ParserFlags class methodsFor:'accessing-syntax-control'!

allowArrayIndexSyntaxExtension
    "experimental syntax: var[idx-expr]"

    ^ AllowArrayIndexSyntaxExtension ? false

    "
     self allowArrayIndexSyntaxExtension:true
     self allowArrayIndexSyntaxExtension:false
     self allowArrayIndexSyntaxExtension
    "

    "Modified (comment): / 23-09-2018 / 00:42:11 / Claus Gittinger"
!

allowArrayIndexSyntaxExtension:aBoolean
    "experimental syntax: var[idx-expr]"

    AllowArrayIndexSyntaxExtension := aBoolean.

    "
     self allowArrayIndexSyntaxExtension:true
     self allowArrayIndexSyntaxExtension:false
    "

    "Modified (comment): / 23-09-2018 / 00:42:15 / Claus Gittinger"
!

allowAssignmentToBlockArgument
    ^ AllowAssignmentToBlockArgument

    "Created: / 08-09-2011 / 14:49:46 / cg"
!

allowAssignmentToBlockArgument:aBoolean
    AllowAssignmentToBlockArgument := aBoolean

    "Created: / 08-09-2011 / 14:50:23 / cg"
!

allowAssignmentToMethodArgument
    ^ AllowAssignmentToMethodArgument

    "Created: / 08-09-2011 / 14:49:57 / cg"
!

allowAssignmentToMethodArgument:aBoolean
    AllowAssignmentToMethodArgument := aBoolean

    "Created: / 08-09-2011 / 14:50:34 / cg"
!

allowAssignmentToPoolVariable
    ^ AllowAssignmentToPoolVariable

    "Created: / 08-09-2011 / 14:50:06 / cg"
!

allowAssignmentToPoolVariable:aBoolean
    AllowAssignmentToPoolVariable := aBoolean

    "Created: / 08-09-2011 / 14:50:48 / cg"
!

allowCStrings
    "allow c-style strings of the form:
        c'...' containing c-language character escapes"
        
    ^ AllowCStrings

    "Created: / 08-02-2019 / 18:42:15 / Claus Gittinger"
    "Modified (comment): / 23-05-2019 / 08:57:46 / Claus Gittinger"
!

allowCStrings:aBoolean
    "allow c-style strings of the form:
        c'...' containing c-language character escapes"

    AllowCStrings := aBoolean.

    "
     ParserFlags allowCStrings:true
     ParserFlags allowCStrings
    "

    "Created: / 08-02-2019 / 18:42:30 / Claus Gittinger"
    "Modified (comment): / 23-05-2019 / 08:57:50 / Claus Gittinger"
!

allowCaretAsBinop
    "allow '^' to be used as a binary operator"

    ^ AllowCaretAsBinop

    "Created: / 08-02-2019 / 18:49:12 / Claus Gittinger"
    "Modified (comment): / 23-05-2019 / 08:58:11 / Claus Gittinger"
!

allowCaretAsBinop:aBoolean
    "allow '^' to be used as a binary operator"

    AllowCaretAsBinop := aBoolean

    "Created: / 08-02-2019 / 18:49:21 / Claus Gittinger"
    "Modified (comment): / 23-05-2019 / 08:58:14 / Claus Gittinger"
!

allowDollarInIdentifier
    "return true, if $-characters are allowed in identifiers.
     Notice, that dollars are NEVER allowed as the first character in an identifier
     (because they are interpreted as character-constant then).
     Dollars in identifiers were used in VMS versions of VW-Smalltalk"

    ^ AllowDollarInIdentifier

    "Created: / 07-09-1997 / 01:32:18 / cg"
    "Modified (comment): / 16-11-2016 / 22:25:59 / cg"
    "Modified (comment): / 23-05-2019 / 08:59:03 / Claus Gittinger"
!

allowDollarInIdentifier:aBoolean
    "this allows turning on/off $-characters in identifiers.
     Notice, that dollars are NEVER allowed as the first character in an identifier.
     If turned off (the default), dollars are not allowed in identifiers,
     but instead are scanned as character-constant prefix.
     If turned on, dollars in identifiers are allowed, while extra
     dollars are still scanned as constant character prefix.
     If you have to fileIn old VW-Vsn2.x classes, turn this off
     before filing them in; i.e.:
        Compiler allowDollarInIdentifiers:false
     Dollars in identifiers were used in VMS versions of VW-Smalltalk.
    "

    AllowDollarInIdentifier := aBoolean.

    "Created: / 07-09-1997 / 01:34:49 / cg"
    "Modified (comment): / 16-11-2016 / 22:26:38 / cg"
    "Modified (comment): / 23-05-2019 / 09:00:00 / Claus Gittinger"
!

allowDolphinExtensions
    "return true, if ##(..) computed literals are allowed"

    ^ AllowDolphinExtensions
!

allowDolphinExtensions:aBoolean
    "this allows turning on/off support for computed arrays ##(..) as in dolphin.
     If you want to fileIn Dolphin classes, enable this with:
	Compiler allowDolphinComputedArrays:true"

    AllowDolphinExtensions := aBoolean.

    "
     self allowDolphinExtensions:true
     self allowDolphinExtensions:false
    "
!

allowEStrings
    "allow extended strings with embedded expressions of the form:
        e'...' containing c-language character escapes
               and embedded expressions {expr} which are sliced in"
        
    ^ AllowEStrings

    "Created: / 23-05-2019 / 10:28:17 / Claus Gittinger"
!

allowEStrings:aBoolean
    "allow extended strings with embedded expressions of the form:
        e'...' containing c-language character escapes
               and embedded expressions {expr} which are sliced in"
        
    AllowEStrings := aBoolean

    "Created: / 23-05-2019 / 10:28:29 / Claus Gittinger"
!

allowEmptyStatements
    "return true, if empty statements are allowed (two .'s in a row).
     Notice, that stc cannot (yet) handle those."

    ^ AllowEmptyStatements

    "Created: / 20-11-2006 / 14:29:02 / cg"
!

allowEmptyStatements:aBoolean
    "turn on/off, if empty statements are allowed (two .'s in a row).
     Notice, that stc cannot (yet) handle those."

    AllowEmptyStatements := aBoolean

    "Created: / 20-11-2006 / 14:29:15 / cg"
!

allowExtendedBinarySelectors
    "experimental extended selectors extensions"

    ^ AllowExtendedBinarySelectors

    "
     ParserFlags allowExtendedBinarySelectors
     ParserFlags allowExtendedBinarySelectors:false
     ParserFlags allowExtendedBinarySelectors:true
    "
!

allowExtendedBinarySelectors:aBoolean
    "experimental syntax extensions"

    AllowExtendedBinarySelectors := aBoolean

    "Modified (comment): / 23-05-2019 / 10:40:47 / Claus Gittinger"
!

allowExtendedSTXSyntax
    "Enables ALL of the ST/X extensions.
     Do not use for now, as stc does not support all of them"

    ^ AllowExtendedSTXSyntax

    "Modified (comment): / 23-05-2019 / 10:41:53 / Claus Gittinger"
!

allowExtendedSTXSyntax:aBoolean
    "Enables ALL of the ST/X extensions.
     Do not use for now, as stc does not support all of them"

    AllowExtendedSTXSyntax := aBoolean

    "
     self allowExtendedSTXSyntax:true
     'a\tb' inspect.
     'a\u1616b' inspect.
     self allowExtendedSTXSyntax:false
    "

    "Modified (comment): / 23-05-2019 / 10:41:57 / Claus Gittinger"
!

allowFixedPointLiterals
    "return true, if nnnsn (FixedPoint) literals are allowed.
     The default is true."

    ^ AllowFixedPointLiterals

    "Modified (comment): / 23-05-2019 / 09:00:40 / Claus Gittinger"
!

allowFixedPointLiterals:aBoolean
    "enable/disable, if nnnsn (FixedPoint) literals are allowed.
     The default is true."

    AllowFixedPointLiterals := aBoolean

    "Modified (comment): / 23-05-2019 / 09:00:44 / Claus Gittinger"
!

allowFunctionCallSyntaxForBlockEvaluation
    "experimental"

    ^ AllowFunctionCallSyntaxForBlockEvaluation

    "
     AllowFunctionCallSyntaxForBlockEvaluation := true
    "
!

allowFunctionCallSyntaxForBlockEvaluation:aBoolean
    "experimental"

    AllowFunctionCallSyntaxForBlockEvaluation := aBoolean.
!

allowGreekCharactersInIdentifier
    "return true, if greek characters (alpha, beta etc.) are allowed in identifiers"

    ^ AllowGreekCharactersInIdentifier

    "Created: / 08-06-2019 / 14:52:29 / Claus Gittinger"
!

allowGreekCharactersInIdentifier:aBoolean
    "are greek characters (alpha, beta etc.) are allowed in identifiers.
     Use this ONLY to file in some non-ANSI ST code"

    AllowGreekCharactersInIdentifier := aBoolean

    "Created: / 08-06-2019 / 14:54:04 / Claus Gittinger"
!

allowHashAsBinarySelector
    "if true, a free-standing single '#' is allowed as a binary selector.
     The default is true."
    
    ^ AllowHashAsBinarySelector

    "Modified (comment): / 23-05-2019 / 09:01:57 / Claus Gittinger"
!

allowHashAsBinarySelector:aBoolean
    "if true, a free-standing single '#' is allowed as a binary selector.
     The default is true."

    AllowHashAsBinarySelector := aBoolean

    "
     self allowHashAsBinarySelector:true
     self allowHashAsBinarySelector:false
     123 # 234
    "

    "Modified (comment): / 23-05-2019 / 09:01:54 / Claus Gittinger"
!

allowJavaScriptConst
    "return true, if const is allowed and treated as a keyword (in JavaScript)"

    ^ AllowJavaScriptConst

    "Created: / 08-08-2017 / 23:48:48 / cg"
!

allowJavaScriptConst:aBoolean
    "true, if const is allowed and treated as a keyword (in JavaScript)"

    AllowJavaScriptConst := aBoolean

    "Created: / 08-08-2017 / 23:49:07 / cg"
!

allowLazyValueExtension
    "allow !![...] to generate a lazy value"

    ^ AllowLazyValueExtension

    "Created: / 03-06-2019 / 10:57:42 / Claus Gittinger"
!

allowLazyValueExtension:aBoolean
    "allow !![...] to generate a lazy value"

    AllowLazyValueExtension := aBoolean

    "Created: / 03-06-2019 / 10:57:50 / Claus Gittinger"
!

allowLiteralNameSpaceSymbols
    "return true, if literal nameSpace symbols are allowed (#foo::bar) are allowed"

    ^ AllowLiteralNameSpaceSymbols

    "
     #foo - ok 
     #foo::bar - ok 
     #foo.bar - not allowed
    "

    "Modified (comment): / 23-05-2019 / 09:03:47 / Claus Gittinger"
!

allowLiteralNameSpaceSymbols:aBoolean
    "controls, if literal nameSpace symbols are allowed (#foo::bar) are allowed"

    AllowLiteralNameSpaceSymbols := aBoolean

    "
     #foo - ok
     #foo::bar - ok 
     #foo.bar - not allowed
    "

    "Modified (comment): / 23-05-2019 / 09:03:43 / Claus Gittinger"
!

allowLocalVariableDeclarationWithInitializerExpression
    "experimental: | var := expr |"

    ^ AllowLocalVariableDeclarationWithInitializerExpression

    "
     self allowLocalVariableDeclarationWithInitializerExpression:true
     self allowLocalVariableDeclarationWithInitializerExpression:false

     |a := 0 . b := 1 |
     Transcript showCR:'a is',a,' b is ',b
    "

    "Modified (comment): / 23-05-2019 / 09:07:42 / Claus Gittinger"
!

allowLocalVariableDeclarationWithInitializerExpression:aBoolean
    "experimental: | var := expr |"

    AllowLocalVariableDeclarationWithInitializerExpression := aBoolean.

    "Modified (comment): / 23-09-2018 / 00:44:04 / Claus Gittinger"
!

allowNationalCharactersInIdentifier
    "return true, if national characters (diaresis etc.) are allowed in identifiers"

    ^ AllowNationalCharactersInIdentifier
!

allowNationalCharactersInIdentifier:aBoolean
    "this allows turning on/off recognition of national characters (diaresis etc.) in identifiers.
     Use this ONLY to file in some non-ANSI ST/V code"

    AllowNationalCharactersInIdentifier := aBoolean

    "
     ParserFlags allowNationalCharactersInIdentifier:true
    "
!

allowOldStyleAssignment
    "return true, if underscore-assignment (pre ST-80v4 syntax) are to be allowed"

    ^ AllowOldStyleAssignment
!

allowOldStyleAssignment:aBoolean
    "this allows turning on/off recognition of underscore-assignment (pre ST-80v4 syntax).
     You must turn this off, if code with variables named '_' is to be filedIn"

    AllowOldStyleAssignment := aBoolean
!

allowParagraphInIdentifier
    "return true, if ยง-characters are allowed in identifiers (treated as letter)"

    ^ AllowParagraphInIdentifier

    "Created: / 16-11-2016 / 22:24:32 / cg"
!

allowParagraphInIdentifier:aBoolean
    "this allows turning on/off ยง-characters in identifiers."

    AllowParagraphInIdentifier := aBoolean.

    "Created: / 16-11-2016 / 22:28:49 / cg"
!

allowPeriodInSymbol
    "return true, if periods are allowed in a symbol literal #foo.bar.
     Needed to parse some old ST80/Squeak code"

    ^ AllowPeriodInSymbol
!

allowPeriodInSymbol:aBoolean
    "control, if periods are allowed in a symbol literal #foo.bar.
     Needed to parse some old ST80/Squeak code"

    AllowPeriodInSymbol := aBoolean

    "
     self allowPeriodInSymbol:true.
     self assert:( Parser parseExpression:' #foo.bar.baz. ' ) value == #'foo.bar.baz'.

     self allowPeriodInSymbol:false.
     self assert:( Parser parseExpression:' #foo.bar.baz. ' ) value == #'foo'.
   "
!

allowQualifiedNames
    "return true, if '#{..}' and 'namespace.varName' qualified names are allowed"

    ^ AllowQualifiedNames

    "Modified (comment): / 23-09-2018 / 01:08:29 / Claus Gittinger"
!

allowQualifiedNames:aBoolean
    "this allows turning on/off support for qualifiedNames #{ .., } as in vw3.
     If you want to fileIn vw3 or later classes, enable this with:
	Compiler allowQualifiedNames:true
     Notice, that qualified names are not really supported semantically
     (they are parsed, but treated like regular globals)
    "

    AllowQualifiedNames := aBoolean.

    "
     self allowQualifiedNames:true
     self allowQualifiedNames:false
    "
!

allowRStrings
    "rstrings have the syntax:
        r'...'
     which generates a regex"
        
    ^ AllowRStrings

    "Created: / 03-06-2019 / 11:12:11 / Claus Gittinger"
!

allowRStrings:aBoolean
    "rstrings have the syntax:
        r'...'
     which generates a regex"
        
    AllowRStrings := aBoolean

    "Created: / 03-06-2019 / 11:12:37 / Claus Gittinger"
!

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

    ^ AllowReservedWordsAsSelectors ? false
!

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

    AllowReservedWordsAsSelectors := aBoolean.

    "
     self allowReservedWordsAsSelectors:true
     self allowReservedWordsAsSelectors:false
    "
!

allowSTVExtensions
    "return true, if support for ST/V syntax extensions is enabled."

    ^ AllowSTVExtensions
!

allowSTVExtensions:aBoolean
    "this allows turning on/off support for ST/V extensions:
     If you want to fileIn ST/V classes, enable this with:
	Compiler allowSTVComputedArrays:true"

    AllowSTVExtensions := aBoolean.

    "
     ParserFlags allowSTVExtensions:true
     ParserFlags allowSTVExtensions:false
    "
!

allowSTVPrimitives
    "return true, if support for ST/V primitives is enabled."

    ^ AllowSTVPrimitives
!

allowSTVPrimitives:aBoolean
    "this allows turning on/off support for ST/V primitives"

    AllowSTVPrimitives := aBoolean

    "
     ParserFlags allowSTVPrimitives:true
    "
!

allowSTXDelimiterComments
    "token delimited comments;
     these are multiline comments of the form:
        ''>>TOKEN
           ... anything, including double quotes
        TOKEN>>''
     (the '' being a double quote in the above)
     Such comments are especially useful to comment pieces of sample code, which may
     contain another comment in it, but you don't want to make them all EOL comments
     (which are an ST/X speciality also, by the way).
     Be aware, that no other smalltalk supports this, so your code becomes harder to port, if you use it.
    "

    ^ AllowSTXDelimiterComments

    "Modified (comment): / 28-07-2017 / 10:32:54 / cg"
!

allowSTXDelimiterComments:aBoolean
    "enable token delimited comments;
     these are multiline comments of the form:
	''>>TOKEN
	   ... anything, including double quotes
	TOKEN>>''
     (the '' being a double quote in the above)
     Such comments are especially useful to comment pieces of sample code, which may
     contain another comment in it, but you don't want to make them all EOL comments
     (which are an ST/X speciality also, by the way).
     Be aware, that no other smalltalk supports this, so your code becomes harder to port, if you use it.
    "

    AllowSTXDelimiterComments := aBoolean.

    "
     self allowSTXDelimiterComments:true
     self allowSTXDelimiterComments:false
    "
!

allowSTXEOLComments
    "are ST/X end-of-line comments allowed?"

    ^ AllowSTXEOLComments
!

allowSTXEOLComments:aBoolean
    "are ST/X end-of-line comments allowed?"

    AllowSTXEOLComments := aBoolean.

    "
     self allowSTXEOLComments:true
     self allowSTXEOLComments:false
    "
!

allowSTXExtendedArrayLiterals
    "are scheme-style typed literal arrays allowed?"

    ^ AllowSTXExtendedArrayLiterals ? false
!

allowSTXExtendedArrayLiterals:aBoolean
    "are scheme-style typed literal arrays allowed?"

    AllowSTXExtendedArrayLiterals := aBoolean.

    "
     self allowSTXExtendedArrayLiterals:true
     self allowSTXExtendedArrayLiterals:false
    "
!

allowSignedByteArrayElements
    "return true, if byteArray elements are allowed to be negative."

    ^ AllowSignedByteArrayElements
!

allowSignedByteArrayElements:aBoolean
    "controls, if byteArray elements are allowed to be negative."

    AllowSignedByteArrayElements := aBoolean
!

allowSqueakExtensions
    "return true, if support for squeak extensions
	computed arrays { .., }
	c/java style arguments in message sends rec foo(arg1, ... argN)
     is enabled."

    ^ AllowSqueakExtensions
!

allowSqueakExtensions:aBoolean
    "this allows turning on/off support for squeak extensions:
	computed arrays { .., }
	c/java style arguments in message sends rec foo(arg1, ... argN)

     If you want to fileIn Squeak classes, enable this with:
	Compiler allowSqueakComputedArrays:true"

    AllowSqueakExtensions := aBoolean.

    "
     self allowSqueakExtensions:true
     self allowSqueakExtensions:false
    "
!

allowSqueakPrimitives
    "return true, if support for squeak primitives is enabled."

    ^ AllowSqueakPrimitives
!

allowSqueakPrimitives:aBoolean
    "this allows turning on/off support for squeak primitives"

    AllowSqueakPrimitives := aBoolean
!

allowSymbolsStartingWithDigit
    "return true, if a symbol is allowed to start with a digit
     i.e. as in #2D.
     This seems to be ok in new Squeak/Pharo versions"

    ^ AllowSymbolsStartingWithDigit

    "Created: / 18-06-2017 / 16:23:20 / cg"
!

allowSymbolsStartingWithDigit:aBoolean
    "controls if a symbol is allowed to start with a digit
     i.e. as in #2D.
     This seems to be ok in new Squeak/Pharo versions"

    AllowSymbolsStartingWithDigit := aBoolean

    "Created: / 18-06-2017 / 16:24:47 / cg"
!

allowUnderscoreInIdentifier
    "return true, if underscores are allowed in identifiers"

    ^ AllowUnderscoreInIdentifier
!

allowUnderscoreInIdentifier:aBoolean
    "this allows turning on/off underscores in identifiers.
     If turned off (the default), underscores are not allowed in identifiers,
     but instead scanned as assignment character (old ST/80 syntax).
     If turned on, underscores are in identifiers are allowed, while extra
     underscores are still scanned as assignment.
     If you have to fileIn old VW-Vsn2.x classes,
     turn them off with:
	Compiler allowUnderscoreInIdentifiers:false"

    AllowUnderscoreInIdentifier := aBoolean.

    "Modified: 7.9.1997 / 01:35:19 / cg"
!

allowUnicodeCharacters
    ^ AllowUnicodeCharacters
!

allowUnicodeCharacters:aBoolean
    AllowUnicodeCharacters := aBoolean.
!

allowUnicodeStrings
    ^ AllowUnicodeStrings
!

allowUnicodeStrings:aBoolean
    AllowUnicodeStrings := aBoolean.
!

allowVisualAgeESSymbolLiterals
    "return true, if ##symbols are allowed (treated like symbols)"

    ^ AllowVisualAgeESSymbolLiterals
!

allowVisualAgeESSymbolLiterals:aBoolean
    "if on, visualAge's ##symbols are allowed (treated like symbols)"

    AllowVisualAgeESSymbolLiterals := aBoolean.
!

allowVisualAgePrimitives
    "return true, if support for V'Age primitives is enabled."

    ^ AllowVisualAgePrimitives

    "
     AllowVisualAgePrimitives := true
     AllowVisualAgePrimitives := false
    "

    "Modified (comment): / 18-10-2011 / 16:49:12 / cg"
!

allowVisualAgePrimitives:aBoolean
    "this allows turning on/off support for V'Age primitives"

    AllowVisualAgePrimitives := aBoolean
!

allowVisualWorksMethodAnnotations
    "return true, if support for V'Works extended primitive syntax for method annotations."

    ^ AllowVisualWorksMethodAnnotations

    "Created: / 07-07-2006 / 15:49:32 / cg"
!

allowVisualWorksMethodAnnotations:aBoolean
    "turn on/off support for V'Works extended primitive syntax for method annotations."

    AllowVisualWorksMethodAnnotations := aBoolean

    "Created: / 07-07-2006 / 15:49:27 / cg"
!

singlePrecisionFloatF
    "by default, the 'f'-character in a float literal will generate
     double-precision Float instances.
     With allowSinglePrecisionFloats, it will generate single precision ShortFloat instances.
     Notice, that there is some confusion among Smalltalk systems, whether a float has
     single or double precision (VW vs. V'age).
     In ST/X, floats have double-precision by default."

    ^ SinglePrecisionFloatF

    "Created: / 26-05-2019 / 11:32:38 / Claus Gittinger"
!

singlePrecisionFloatF:aBoolean
    "by default, the 'f'-character in a float literal will generate
     double-precision Float instances.
     With allowSinglePrecisionFloats, it will generate single precision ShortFloat instances.
     Notice, that there is some confusion among Smalltalk systems, whether a float has
     single or double precision (VW vs. V'age).
     In ST/X, floats have double-precision by default."

    SinglePrecisionFloatF := aBoolean

    "Created: / 26-05-2019 / 11:32:29 / Claus Gittinger"
!

warnAssignmentToBlockArgument
    ^ WarnAssignmentToBlockArgument
!

warnAssignmentToBlockArgument:aBoolean
    WarnAssignmentToBlockArgument := aBoolean
!

warnAssignmentToMethodArgument
    ^ WarnAssignmentToMethodArgument
!

warnAssignmentToMethodArgument:aBoolean
    WarnAssignmentToMethodArgument := aBoolean
!

warnAssignmentToPoolVariable
    ^ WarnAssignmentToPoolVariable
!

warnAssignmentToPoolVariable:aBoolean
    WarnAssignmentToPoolVariable := aBoolean
! !

!ParserFlags class methodsFor:'accessing-warning-control'!

warnAboutBadComments
    "controls generation of warning messages about empty comments"

    ^ WarnAboutBadComments
!

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

    WarnAboutBadComments := aBoolean
!

warnAboutNonLowercaseLocalVariableNames
    "controls generation of warning messages about wrong variable names"

    ^ WarnAboutNonLowercaseLocalVariableNames
!

warnAboutNonLowercaseLocalVariableNames:aBoolean
    "controls generation of warning messages about wrong variable names"

    WarnAboutNonLowercaseLocalVariableNames := aBoolean
!

warnAboutPeriodInSymbol
    ^ WarnAboutPeriodInSymbol
!

warnAboutPeriodInSymbol:aBoolean
    WarnAboutPeriodInSymbol := aBoolean
!

warnAboutPossibleSTCCompilationProblems
    ^ WarnAboutPossibleSTCCompilationProblems

    "Created: / 16-11-2006 / 14:31:52 / cg"
!

warnAboutPossibleSTCCompilationProblems:aBoolean
    WarnAboutPossibleSTCCompilationProblems := aBoolean

    "Created: / 16-11-2006 / 14:31:57 / cg"
!

warnAboutPossiblyUnimplementedSelectors
    ^ WarnAboutPossiblyUnimplementedSelectors
!

warnAboutPossiblyUnimplementedSelectors:aBoolean
    WarnAboutPossiblyUnimplementedSelectors := aBoolean
!

warnAboutPossiblyUninitializedLocals
    ^ WarnAboutPossiblyUninitializedLocals

    "Created: / 23-04-2019 / 23:09:08 / Claus Gittinger"
!

warnAboutPossiblyUninitializedLocals:aBoolean
    WarnAboutPossiblyUninitializedLocals := aBoolean

    "Created: / 23-04-2019 / 23:09:20 / Claus Gittinger"
!

warnAboutReferenceToPrivateClass
    "controls generation of warning messages when a private class is referenced"

    ^ WarnAboutReferenceToPrivateClass
!

warnAboutReferenceToPrivateClass:aBoolean
    "controls generation of warning messages when a private class is referenced"

    WarnAboutReferenceToPrivateClass := aBoolean
!

warnAboutShortLocalVariableNames
    "controls generation of warning messages about short variable names"

    ^ WarnAboutShortLocalVariableNames
!

warnAboutShortLocalVariableNames:aBoolean
    "controls generation of warning messages about short variable names"

    WarnAboutShortLocalVariableNames := aBoolean
!

warnAboutUnknownCharacterEscapesInJavaScriptStringConstant
    "things like '\c:foo' instead of '\\c:foo' "

    ^ WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant

    "Created: / 04-10-2011 / 19:54:57 / cg"
!

warnAboutUnknownCharacterEscapesInJavaScriptStringConstant:aBoolean
    "things like '\c:foo' instead of '\\c:foo' "

    WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant := aBoolean

    "Created: / 04-10-2011 / 19:54:42 / cg"
!

warnAboutVariableNameConventions
    "controls generation of warning messages about wrong variable names"

    ^ WarnAboutVariableNameConventions
!

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

    WarnAboutVariableNameConventions := aBoolean
!

warnAboutWrongVariableNames
    "controls generation of warning messages about wrong variable names"

    ^ WarnAboutWrongVariableNames
!

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

    WarnAboutWrongVariableNames := aBoolean
!

warnCommonMistakes
    "return true, if common beginners mistakes are to be warned about"

    ^ WarnCommonMistakes
!

warnCommonMistakes:aBoolean
    "this allows turning on/off warnings about common beginners mistakes.
     Those are not really errors in the strict sense, but often lead to
     run time errors later.
     Examples are: expr or:expr2, where expr2 is not a block.
     If you get bored by those warnings, turn them off by adding
     a line as:
	ParserFlags warnCommonMistakes:false
     in your 'private.rc' file"

    WarnCommonMistakes := aBoolean

    "Modified: / 05-09-2006 / 11:46:26 / cg"
!

warnDollarInIdentifier
    "return true, if $-characters in identifiers are to be warned about"

    ^ Warnings and:[WarnDollarInIdentifier]

    "Created: 7.9.1997 / 01:36:17 / cg"
!

warnDollarInIdentifier:aBoolean
    "this allows turning on/off warnings about $-characters in identifiers.
     You may find those warnings useful, to make certain that your code
     is portable to other Smalltalk versions, which do not allow this
     (i.e. VW releases 2.x and maybe others).
     Notice, that dollars are NEVER allowed as the first character in an identifier.
     If you get bored by those warnings, turn them off by adding
     a line as:
        ParserFlags warnDollarInIdentifier:false
     in your 'private.rc' file"

    WarnDollarInIdentifier := aBoolean

    "Created: / 07-09-1997 / 01:37:42 / cg"
    "Modified: / 05-09-2006 / 11:46:23 / cg"
    "Modified (comment): / 16-11-2016 / 22:31:06 / cg"
!

warnHiddenVariables
    "controls generation of warning messages about hiding variables by locals"

    ^ WarnHiddenVariables
!

warnHiddenVariables:aBoolean
    "controls generation of warning messages about hiding variables by locals"

    WarnHiddenVariables := aBoolean
!

warnInconsistentReturnValues
    "return true, if compiler should warn about inconsitent (boolean / non-boolean)
     return values"

    ^ WarnInconsistentReturnValues
!

warnInconsistentReturnValues:aBoolean
    "constrols if the compiler should warn about inconsitent (boolean / non-boolean)
     return values"

    WarnInconsistentReturnValues := aBoolean
!

warnOldStyleAssignment
    "return true, if underscore-assignment (pre ST-80v4 syntax) are to be warned about"

    ^ Warnings and:[WarnOldStyleAssignment]
!

warnOldStyleAssignment:aBoolean
    "this allows turning on/off warnings about underscore-assignment (pre ST-80v4 syntax).
     If you get bored by those warnings, turn them off by adding
     a line as:
	ParserFlags warnOldStyleAssignment:false
     in your 'private.rc' file"

    WarnOldStyleAssignment := aBoolean

    "Modified: / 05-09-2006 / 11:46:17 / cg"
!

warnParagraphInIdentifier
    "return true, if ยง-characters in identifiers are to be warned about"

    ^ Warnings and:[WarnParagraphInIdentifier]

    "Created: / 16-11-2016 / 22:30:01 / cg"
!

warnParagraphInIdentifier:aBoolean
    "this allows turning on/off warnings about ยง-characters in identifiers.
     You may find those warnings useful, to make certain that your code
     is portable to other Smalltalk versions, which do not allow this"

    WarnParagraphInIdentifier := aBoolean

    "Created: / 16-11-2016 / 22:30:45 / cg"
!

warnPlausibilityChecks
    "controls generation of warning messages about plausibility checks (possible precedence, etc.)"

    ^ WarnPlausibilityChecks

    "Created: / 19-01-2012 / 10:38:20 / cg"
!

warnPlausibilityChecks:aBoolean
    "controls generation of warning messages about plausibility checks (possible precedence, etc.)"

    WarnPlausibilityChecks := aBoolean

    "Created: / 19-01-2012 / 10:38:39 / cg"
!

warnPossibleIncompatibilities
    "return true, if possible incompatibilities (with other ST systems)
     are to be warned about"

    ^ Warnings and:[WarnPossibleIncompatibilities]

    "Modified: 23.5.1997 / 12:02:02 / cg"
!

warnPossibleIncompatibilities:aBoolean
    "this turns warnings about possible incompatibilities (with other ST systems)
     on or off.
     If you get bored by those warnings, turn them off by adding
     a line as:
	ParserFlags warnPossibleIncompatibilities:false
     in your 'private.rc' file."

    WarnPossibleIncompatibilities := aBoolean

    "Created: / 23-05-1997 / 12:02:45 / cg"
    "Modified: / 05-09-2006 / 11:46:14 / cg"
!

warnSTXSpecials
    "return true, if ST/X specials are to be warned about"

    ^ Warnings and:[WarnSTXSpecials]
!

warnSTXSpecials:aBoolean
    "this allows turning on/off warnings about stx specials.
     If you get bored by those warnings, turn them off by adding
     a line as:
	ParserFlags warnSTXSpecials:false
     in your 'private.rc' file"

    WarnSTXSpecials := aBoolean

    "Modified: / 05-09-2006 / 11:46:11 / cg"
!

warnUnderscoreInIdentifier
    "return true, if underscores in identifiers are to be warned about"

    ^ Warnings and:[WarnUnderscoreInIdentifier]
!

warnUnderscoreInIdentifier:aBoolean
    "this allows turning on/off warnings about underscores in identifiers.
     You may find those warnings useful, to make certain that your code
     is portable to other smalltalk versions, which do not allow this
     (i.e. VW releases 2.x).
     If you get bored by those warnings, turn them off by adding
     a line as:
	ParserFlags warnUnderscoreInIdentifier:false
     in your 'private.rc' file"

    WarnUnderscoreInIdentifier := aBoolean

    "Modified: / 05-09-2006 / 11:46:08 / cg"
!

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

    ^ WarnUnusedVars
!

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

    WarnUnusedVars := aBoolean
!

warnings
    "return true, if any warnings are to be shown"

    ^ Warnings
!

warnings:aBoolean
    "this allows turning on/off all warnings; the default is on.
     You can turn off warnings in your 'private.rc' file with
	 ParserFlags warnings:false
    "

    Warnings := aBoolean

    "
     ParserFlags warnings
     ParserFlags warnings:true
     ParserFlags warnings:false
    "

    "Modified: / 05-09-2006 / 11:46:47 / cg"
! !

!ParserFlags class methodsFor:'class initialization'!

initialize
    |executablePath topDir|

    SinglePrecisionFloatF := false.
    
    Warnings := true.
    WarnUndeclared := true.
    WarnUnusedVars := true.
    WarnSTXSpecials := false.
    WarnST80Directives := false.
    WarnAboutWrongVariableNames := true.
    WarnAboutVariableNameConventions := true.
    WarnAboutBadComments := true.
    WarnAboutPossiblyUninitializedLocals := true.
    WarnUnderscoreInIdentifier := false.
    WarnDollarInIdentifier := true.
    WarnParagraphInIdentifier := true.
    WarnOldStyleAssignment := true.
    WarnCommonMistakes := true.
    WarnPossibleIncompatibilities := false.
    WarnHiddenVariables := true.
    WarnInconsistentReturnValues := true.
    WarnAboutNonLowercaseLocalVariableNames := true.
    WarnAboutShortLocalVariableNames := false.
    WarnAboutPossibleSTCCompilationProblems := true.
    WarnAboutReferenceToPrivateClass := true.
    WarnAboutPossiblyUnimplementedSelectors := true.
    WarnAboutPeriodInSymbol := true.
    WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant := false.
    WarnPlausibilityChecks := true.
    WarnAssignmentToBlockArgument := true.
    WarnAssignmentToMethodArgument := true.
    WarnAssignmentToPoolVariable := true.

    AllowReservedWordsAsSelectors := false.
    AllowUnderscoreInIdentifier := true.
    AllowParagraphInIdentifier := false.
    AllowDollarInIdentifier := false.           "/ st80-vms dollars in identifiers
    AllowOldStyleAssignment := true.            "/ st80 underscore as assignment
    AllowDolphinExtensions := false.            "/ dolphin computed literal
    AllowQualifiedNames := false.               "/ vw3 qualified names
    AllowExtendedBinarySelectors := false.      "/ vw5.4 extended binary selectors (plus/minus, center-dot etc.)
    AllowCaretAsBinop := false.                 "/ too dangerous
    AllowLiteralNameSpaceSymbols := true.       "/ st/x literal nameSpace-symbols (#foo::bar)
    AllowArrayIndexSyntaxExtension := false.
    AllowFunctionCallSyntaxForBlockEvaluation := false.
    AllowLocalVariableDeclarationWithInitializerExpression := false.
    AllowDomainVariables := false.
    AllowArrayIndexSyntaxExtension := false.
    AllowReservedWordsAsSelectors := true.
    AllowVariableReferences := false.
    AllowLazyValueExtension := false.
    AllowFixedPointLiterals := true "false".
    AllowExtendedSTXSyntax := false.
    AllowVisualAgeESSymbolLiterals := false.
    AllowExtensionsToPrivateClasses := true.
    AllowVisualAgePrimitives := false.
    AllowSqueakExtensions := true.              "/ squeak computed array
    AllowSqueakPrimitives := false.
    AllowSTVPrimitives := false.                "/ number-sign syntax
    AllowSTVExtensions := false.
    AllowNationalCharactersInIdentifier := false.
    AllowGreekCharactersInIdentifier := false.
    AllowHashAsBinarySelector := true.
    AllowSTXEOLComments := true.
    AllowSTXDelimiterComments := true.         "/ until stc and RBScanner support it also
    AllowVisualWorksMethodAnnotations := false.
    AllowPossibleSTCCompilationProblems := true. "/ must be true, to allow fileIn!!
    AllowEmptyStatements := false.
    AllowPeriodInSymbol := false.
    AllowPeriodAsNameSpaceSeparator := false.
    "/ these are only used by the new compiler
    AllowCStrings := true.                     "/ c'...' syntax
    AllowEStrings := false.                    "/ e'...' syntax
    AllowRStrings := false.                    "/ r'...' syntax
    AllowUnicodeStrings := false.
    AllowUnicodeCharacters := false.
    AllowCharacterEscapes := false.
    AllowStringEscapes := false.
    AllowAssignmentToBlockArgument := false.
    AllowAssignmentToMethodArgument := false.
    AllowAssignmentToPoolVariable := false.
    "/ AllowAssignmentToPoolVariable := true.
    AllowSignedByteArrayElements := false.
    AllowSymbolsStartingWithDigit := false.

    AllowJavaScriptConst := true.              
    
    ArraysAreImmutable := false.                "/ still care for ST-80 compatibility
    StringsAreImmutable := false.               "/ still care for ST-80 compatibility
    "/ ArraysAreImmutable := true.                 "/ do not care for ST-80 compatibility
    "/ StringsAreImmutable := true.                "/ do not care for ST-80 compatibility
    ImplicitSelfSends := false.
    
    STCKeepCIntermediate := false.
    STCKeepOIntermediate := false.
    STCKeepSTIntermediate := false.
    STCCompilation := #default.

    DefineForBorlandC := '__BORLANDC__'.
    DefineForVisualC := '__VISUALC__'.
    DefineForMSC := '__MSC__'.
    "/ https://expeccoalm.exept.de/D252306
    "/ must not redefine __GNUC__, because gcc defines this anyway with the gcc version 
    "/ contained in this macro (which is used by glibc includes).
    "/ also defined in STCCompilerInterface class >> #getCCDefine
    DefineForGNUC := 'STX__GNUC__'.
    DefineForMINGW := '__MINGW__'.
    DefineForMINGW32 := '__MINGW32__'.
    DefineForMINGW64 := '__MINGW64__'.
    DefineForCLANG := '__CLANG__'.

    "/ try along the executable's path itself
    (executablePath := OperatingSystem pathOfSTXExecutable) notNil ifTrue:[
        |parentDir|
        
        parentDir := executablePath asFilename directory.
        ((parentDir / 'include') exists and:[(parentDir / 'stc') exists]) ifTrue:[
            topDir := parentDir.
        ] ifFalse:[    
            parentDir := parentDir directory.
            ((parentDir / 'include') exists and:[(parentDir / 'stc') exists]) ifTrue:[  
                topDir := parentDir.
            ] ifFalse:[    
                parentDir := parentDir directory.
                ((parentDir / 'include') exists and:[(parentDir / 'stc') exists]) ifTrue:[  
                    topDir := parentDir.
                ]
            ]
        ].
    ].
    
    topDir isNil ifTrue:[
        "/ try standard installation paths...
        OperatingSystem isOSXlike ifTrue:[
            |appDir parentDir|

            (appDir := '/Applications/SmalltalkX.app' asFilename) exists ifTrue:[
                (parentDir := appDir / 'Packages/stx') exists ifTrue:[
                    ((parentDir / 'include') exists and:[(parentDir / 'stc') exists]) ifTrue:[  
                        topDir := parentDir.
                    ].
                ].
            ].    
            (appDir := Filename homeDirectory / 'Applications/SmalltalkX.app') exists ifTrue:[
                (parentDir := appDir / 'Packages/stx') exists ifTrue:[
                    ((parentDir / 'include') exists and:[(parentDir / 'stc') exists]) ifTrue:[  
                        topDir := parentDir.
                    ].
                ].
            ].    
        ].
    ].
    
    topDir notNil ifTrue:[
        self initializeSTCFlagsForTopDirectory:topDir.
    ].

    "
     ParserFlags initialize
    "

    "Modified: / 09-08-2006 / 18:47:18 / fm"
    "Modified: / 08-08-2017 / 23:49:41 / cg"
    "Modified (comment): / 11-05-2018 / 10:12:29 / stefan"
    "Modified: / 08-06-2019 / 14:53:27 / Claus Gittinger"
!

initializeSTCFlagsForTopDirectory:topDirArg
    "topDirArg must be the stx directory (where stc directory with stc-executable is found)
     notice: for now, can only initialize for borland+windows or linux;
     visualC setup still fails."

    |topDir topDirName vcTop sdkTop bccTop mingwTop
     borlandDir useBorlandC useVisualC useMingw32 useMingw64
     programFiles archArg picArg optArg|

    topDir := topDirArg.
    OperatingSystem isMSWINDOWSlike ifTrue:[
        topDirArg isString ifTrue:[
            topDir := topDirArg copyReplaceAll:$/ with:$\ ifNone:topDirArg.
        ]
    ].
    topDir := topDir asFilename.
    topDirName := topDir name.

    "/ if in the development directory, use ./modules
    Smalltalk isSmalltalkDevelopmentSystem ifTrue:[
        STCModulePath := UserPreferences current workspaceDirectory / 'modules'.
    ] ifFalse:[
        STCModulePath := Filename tempDirectory / 'modules'.
    ].

    (topDir construct:'stc') exists ifFalse:[
        ('ParserFlags [warning]: stc not found in "',topDirName,'"') infoPrintCR.
        'ParserFlags [warning]: stc-compiling (primitive code) will not work in the browser' infoPrintCR.
        STCCompilation := #never.
    ].

    OperatingSystem isMSWINDOWSlike ifTrue:[
        useBorlandC := useVisualC := useMingw32 := useMingw64 := false.
        programFiles := OperatingSystem getEnvironment:'ProgramFiles'.
        programFiles isEmptyOrNil ifTrue:[ programFiles := 'C:\Program Files' ].

        STCCompilationIncludes := '-I',topDirName,'\include -I',topDirName,'\libopengl'.

        ExternalBytes sizeofPointer == 4 ifFalse:[
            bccTop := nil
        ] ifTrue:[
            (bccTop := BCCTop) isNil ifTrue:[
                borlandDir := OperatingSystem getEnvironment:'BCCDIR'.
                borlandDir isEmptyOrNil ifTrue:[ borlandDir := 'C:\Borland\bcc55' ].
                bccTop := {
                            (borlandDir) .
                            (programFiles , '\Borland\bcc55') .
                            (programFiles , '\bcc55') .
                          } detect:[:path | path asFilename exists and:[(path asFilename construct:'include') exists]]
                             ifNone:nil.
            ].
        ].

        STCCompilationDefines := '-DWIN32'.

        (bccTop notNil and:[bccTop asFilename exists]) ifTrue:[
            STCCompilationIncludes := STCCompilationIncludes,' -I',bccTop,'\Include'.
            LibDirectory := topDirName,'\lib\bc'.
            LinkArgs := '-L',topDirName,'\lib\bc'.
            LinkArgs := LinkArgs,' -L',bccTop,'\Lib -r -c -ap -Tpd -Gi -w-dup'.
            CCPath := 'bcc32'.
            MakeCommand := 'bmake'.
            LinkCommand := 'ilink32'.
            CCCompilationOptions := '-w-'.
            useBorlandC := true.
        ] ifFalse:[
            ExternalBytes sizeofPointer == 4 ifFalse:[
                vcTop := nil.
            ] ifTrue:[
                (vcTop := VCTop) isNil ifTrue:[
                    vcTop := {
                                (programFiles,'\Microsoft Visual Studio 13.0\VC') .
                                (programFiles,'\Microsoft Visual Studio 12.0\VC') .
                                (programFiles,'\Microsoft Visual Studio 11.0\VC') .
                                (programFiles,'\Microsoft Visual Studio 10.0\VC') .
                                (programFiles,'\Microsoft Visual Studio 9.0\VC' ) .
                             } detect:[:path | path asFilename exists and:[(path asFilename construct:'bin/cl.exe') exists]]
                               ifNone:nil.
                ].
            ].
            (vcTop notNil and:[vcTop asFilename exists]) ifTrue:[
                useVisualC := true.
                STCCompilationIncludes := STCCompilationIncludes,' -I',vcTop,'include'.

                (sdkTop := SDKTop) isNil ifTrue:[
                    sdkTop := {
                                (programFiles,'\Microsoft SDKs\Windows\v9.0A') .
                                (programFiles,'\Microsoft SDKs\Windows\v8.0A') .
                                (programFiles,'\Microsoft SDKs\Windows\v8.0A') .
                                (programFiles,'\Microsoft SDKs\Windows\v7.0A') .
                                (programFiles,'\Microsoft SDKs\Windows\v6.0A') .
                             }  detect:[:path | path asFilename exists and:[(path asFilename construct:'include') exists]] ifNone:nil.
                ].
                (sdkTop notNil and:[sdkTop asFilename exists]) ifTrue:[
                    STCCompilationIncludes := STCCompilationIncludes,' -I',sdkTop,'\include'.
                ].
                LibDirectory := topDirName,'\lib\vc'.
                LinkArgs := '-L',topDirName,'\lib\vc'.
                LinkArgs := LinkArgs,' -r -c -ap -Tpd -Gi -w-dup'.
                CCPath := vcTop,'\bin\cl.exe'.
                LinkCommand := 'ilink32'.
                MakeCommand := 'vcmake'.
                CCCompilationOptions := '/nologo /ZI  /w /GF /EHsc /FR.\objvc\'.
            ] ifFalse:[
                "/ add definitions for lcc, mingc etc.
                "/ STCCompilationIncludes := STCCompilationIncludes,' -IC:\xxxxx\Include'.
                ExternalBytes sizeofPointer == 4 ifTrue:[
                    (mingwTop := MingwTop) isNil ifTrue:[
                        mingwTop := {
                                    (programFiles,'\mingw') .
                                    (programFiles,'\mingw') .
                                    ('c:\mingw32') .
                                    ('c:\mingw') .
                                 } detect:[:path | path asFilename exists and:[(path asFilename construct:'bin/gcc.exe') exists]]
                                   ifNone:nil.
                    ].
                    (mingwTop notNil and:[mingwTop asFilename exists]) ifTrue:[
                        useMingw32 := true.
                        STCCompilationDefines := STCCompilationDefines,' -D__MINGW32__'.
                        CCCompilationOptions := '-w32'.
                    ].
                ] ifFalse:[
                    (mingwTop := MingwTop) isNil ifTrue:[
                        mingwTop := {
                                    (programFiles,'\mingw64') .
                                    (programFiles,'\mingw') .
                                    ('c:\mingw64') .
                                    ('c:\mingw') .
                                 } detect:[:path | path asFilename exists and:[(path asFilename construct:'bin/gcc.exe') exists]]
                                   ifNone:nil.
                    ].
                    (mingwTop notNil and:[mingwTop asFilename exists]) ifTrue:[
                        STCCompilationDefines := STCCompilationDefines,' -D__MINGW64__'.
                        "/ CCCompilationOptions := '-w64'.
                    ].
                ].
                (mingwTop notNil and:[mingwTop asFilename exists]) ifTrue:[
                    STCCompilationDefines := STCCompilationDefines,' -D__MINGW__'.
                    CCPath := mingwTop,'\bin\gcc.exe'.
                    LinkCommand := 'gcc'.
                    MakeCommand := 'mingwmake'.
                    LibDirectory := topDirName,'\lib\mingw'.
                    LinkArgs := '-L',topDirName,'\lib\mingw'.
                    "/ LinkArgs := LinkArgs,' -r -c -ap -Tpd -Gi -w-dup'.
                ].
            ].
        ].
        STCCompilationOptions := '+optinline +inlineNew'.
        (topDirName,'\stc\stc.exe') asFilename exists ifTrue:[
            STCPath := (topDirName,'\stc\stc.exe').
        ] ifFalse:[
            STCPath := 'stc.exe'.
        ].
        LibPath := ''.
        SearchedLibraries := #('import32.lib').
        "/ SearchedLibraries := #('import32.lib' 'glu32.lib' 'opengl32.lib').
    ] ifFalse:[
        STCCompilationIncludes := '-I',topDirName,'/include'.
        STCCompilationDefines := ''.
        STCCompilationOptions := '+optinline +inlineNew'.
        STCPath := topDirName,'/stc/stc'.

        archArg := picArg := ''.
        optArg := '-O'.
        (ExternalBytes sizeofPointer == 4) ifTrue:[
            archArg := ' -m32'
        ] ifFalse:[
            archArg := ' -m64'.            "gcc -m64 needs -fPIC to make a shared library"
            picArg := ' -fPIC'.
        ].
        self useClang ifTrue:[
            CCPath := 'clang'
        ] ifFalse:[
            self useGnuC ifTrue:[
                CCPath := 'gcc'.
                optArg := '-O2 -fno-toplevel-reorder -fno-stack-protector -fno-strict-overflow'.
            ] ifFalse:[
                CCPath := 'cc'
            ].
        ].
        CCCompilationOptions := STCCompilerInterface getCPUDefine,
                                ' -D', self usedCompilerDefine,
                                ' ', STCCompilerInterface getOSDefine,
                                ' ', optArg, archArg, picArg.
        LinkArgs := archArg.
        LinkCommand := CCPath.
        LinkSharedArgs := '-shared'.

        OperatingSystem isOSXlike ifTrue:[
            LinkSharedArgs := '-shared -mmacosx-version-min=10.5 -arch x86_64 librun.so'.
            CCCompilationOptions := CCCompilationOptions ,' -mmacosx-version-min=10.5' 
        ].    
        LibPath := ''.
        SearchedLibraries := #().
        MakeCommand := 'make'.
    ].

    (Smalltalk verbose and:[ Smalltalk infoPrinting ]) ifTrue:[
        'ParserFlags [info]: STC Setup:' infoPrintCR.
        ('ParserFlags [info]:  STCCompilationDefines: ',(STCCompilationDefines?'')) infoPrintCR.
        ('ParserFlags [info]:  CCPath: ',CCPath asString) infoPrintCR.
        ('ParserFlags [info]:  CCCompilationOptions: ',(CCCompilationOptions?'')) infoPrintCR.
        ('ParserFlags [info]:  LinkCommand: ',LinkCommand asString) infoPrintCR.
        ('ParserFlags [info]:  MakeCommand: ',MakeCommand asString) infoPrintCR.
        ('ParserFlags [info]:  LinkArgs: ',(LinkArgs?''),' ',(LinkSharedArgs ?'')) infoPrintCR.
        ('ParserFlags [info]:  STCModulePath: ',STCModulePath asString) infoPrintCR.
    ].

    "
     ParserFlags initializeSTCFlagsForTopDirectory:'../..'
     ParserFlags initialize
    "

    "Modified: / 09-08-2006 / 18:47:18 / fm"
    "Created: / 06-08-2011 / 19:47:47 / cg"
    "Modified: / 11-05-2018 / 14:18:42 / stefan"
    "Modified: / 19-06-2018 / 10:47:21 / Stefan Vogel"
! !

!ParserFlags methodsFor:'accessing'!

fullLineNumberInfo
    ^ (self lineNumberInfo == #full)

    "Created: / 26-09-2012 / 14:13:42 / cg"
!

lineNumberInfo
    ^ lineNumberInfo

    "Created: / 26-09-2012 / 13:27:08 / cg"
!

lineNumberInfo:something
    lineNumberInfo := something.

    "Created: / 26-09-2012 / 13:27:17 / cg"
! !

!ParserFlags methodsFor:'accessing-compilation control'!

allowExtensionsToPrivateClasses
    ^ allowExtensionsToPrivateClasses
!

allowExtensionsToPrivateClasses:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowExtensionsToPrivateClasses := aBoolean

    "Modified (comment): / 09-02-2019 / 15:52:10 / Claus Gittinger"
!

allowPossibleSTCCompilationProblems
    ^ allowPossibleSTCCompilationProblems

    "Created: / 16-11-2006 / 14:24:54 / cg"
!

allowPossibleSTCCompilationProblems:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowPossibleSTCCompilationProblems := aBoolean

    "Created: / 16-11-2006 / 14:24:56 / cg"
    "Modified (comment): / 09-02-2019 / 15:53:08 / Claus Gittinger"
!

arraysAreImmutable
    ^ arraysAreImmutable
!

arraysAreImmutable:aBoolean
    arraysAreImmutable := aBoolean.
!

flattenVisualWorksNamespaces
    ^ true
!

stringsAreImmutable
    ^ stringsAreImmutable
!

stringsAreImmutable:aBoolean
    stringsAreImmutable := aBoolean.
! !

!ParserFlags methodsFor:'accessing-stc compilation control'!

ccCompilationOptions
    ^ ccCompilationOptions ? ''

    "
     self ccCompilationOptions
    "

    "Modified (comment): / 17-11-2016 / 15:40:29 / cg"
!

ccCompilationOptions:something
    ccCompilationOptions := something.
!

ccPath
    ^ ccPath

    "
     self ccPath
    "

    "Modified (comment): / 17-11-2016 / 15:40:40 / cg"
!

ccPath:something
    ccPath := something.
!

implicitSelfSends
    ^ implicitSelfSends
!

implicitSelfSends:aBoolean
    implicitSelfSends := aBoolean.
!

libPath
    ^ libPath

    "
     self libPath
    "

    "Modified (comment): / 17-11-2016 / 15:40:52 / cg"
!

libPath:aString
    libPath := aString
!

linkArgs
    ^ linkArgs

    "
     self linkArgs
    "

    "Modified (comment): / 17-11-2016 / 15:41:03 / cg"
!

linkArgs:aString
    linkArgs := aString
!

linkCommand
    ^ linkCommand

    "
     self linkCommand
    "

    "Modified (comment): / 17-11-2016 / 15:41:16 / cg"
!

linkCommand:aString
    linkCommand := aString
!

linkSharedArgs
    ^ linkSharedArgs
!

linkSharedArgs:aString
    linkSharedArgs := aString
!

searchedLibraries
    ^ searchedLibraries
!

searchedLibraries:aString
    searchedLibraries := aString
!

stcCompilation
    ^ stcCompilation
!

stcCompilation:something
    stcCompilation := something.
!

stcCompilationDefines
    ^ stcCompilationDefines
!

stcCompilationDefines:something
    stcCompilationDefines := something.
!

stcCompilationIncludes
    ^ stcCompilationIncludes

    "
     self stcCompilationIncludes
    "

    "Modified (comment): / 17-11-2016 / 15:41:43 / cg"
!

stcCompilationIncludes:something
    stcCompilationIncludes := something.
!

stcCompilationOptions
    ^ stcCompilationOptions
!

stcCompilationOptions:something
    stcCompilationOptions := something.
!

stcKeepCIntermediate
    ^ stcKeepCIntermediate ? false

    "Modified: / 16-09-2011 / 19:56:22 / cg"
!

stcKeepCIntermediate:something
    stcKeepCIntermediate := something.
!

stcKeepOIntermediate
    ^ stcKeepOIntermediate ? false

    "Modified: / 16-09-2011 / 19:56:52 / cg"
!

stcKeepOIntermediate:something
    stcKeepOIntermediate := something.
!

stcKeepSIntermediate
    ^ false
    "/ ^ true
!

stcKeepSTIntermediate
    ^ stcKeepSTIntermediate ? false

    "Modified: / 16-09-2011 / 19:57:11 / cg"
!

stcKeepSTIntermediate:something
    stcKeepSTIntermediate := something.
!

stcModulePath
    stcModulePath isNil ifTrue:[^ self class stcModulePath].
    ^ stcModulePath
!

stcModulePath:aPath
    "set the path to the directory (for an individual compilation context).
     Obsolete now, as this should not be set from the outside,
     but instead rely totally on the userPreferences."

    stcModulePath := aPath.
!

stcPath
    ^ stcPath
!

stcPath:aPath
    stcPath := aPath.
! !

!ParserFlags methodsFor:'accessing-syntax-control'!

allowArrayIndexSyntaxExtension
    "experimental syntax: var[idx-expr]"

    ^ allowArrayIndexSyntaxExtension ? false

    "Modified: / 08-08-2017 / 16:57:03 / cg"
    "Modified (comment): / 08-06-2019 / 15:00:13 / Claus Gittinger"
!

allowArrayIndexSyntaxExtension:aBoolean
    "experimental syntax: var[idx-expr]"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowArrayIndexSyntaxExtension := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:18 / Claus Gittinger"
!

allowAssignmentToBlockArgument
    ^ allowAssignmentToBlockArgument
!

allowAssignmentToBlockArgument:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowAssignmentToBlockArgument := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:22 / Claus Gittinger"
!

allowAssignmentToMethodArgument
    ^ allowAssignmentToMethodArgument
!

allowAssignmentToMethodArgument:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowAssignmentToMethodArgument := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:27 / Claus Gittinger"
!

allowAssignmentToPoolVariable
    ^ allowAssignmentToPoolVariable
!

allowAssignmentToPoolVariable:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowAssignmentToPoolVariable := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:29 / Claus Gittinger"
!

allowCStrings
    "cstrings have the syntax:
        c'...'
     where inside the string, c-language escapes are recognized"
     
    ^ allowCStrings ? false.

    "Created: / 08-02-2019 / 18:28:33 / Claus Gittinger"
    "Modified (comment): / 23-05-2019 / 10:26:31 / Claus Gittinger"
!

allowCStrings:aBoolean
    "cstrings have the syntax:
        c'...'
     where inside the string, c-language escapes are recognized"

    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowCStrings := aBoolean

    "Created: / 08-02-2019 / 18:28:47 / Claus Gittinger"
    "Modified (comment): / 23-05-2019 / 10:26:36 / Claus Gittinger"
!

allowCaretAsBinop
    ^ allowCaretAsBinop
!

allowCaretAsBinop:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowCaretAsBinop := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:38 / Claus Gittinger"
!

allowCharacterEscapes
    ^ allowCharacterEscapes
!

allowCharacterEscapes:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowCharacterEscapes := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:41 / Claus Gittinger"
!

allowDollarInIdentifier
    ^ allowDollarInIdentifier
!

allowDollarInIdentifier:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowDollarInIdentifier := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:47 / Claus Gittinger"
!

allowDolphinExtensions
    ^ allowDolphinExtensions
!

allowDolphinExtensions:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowDolphinExtensions := aBoolean

    "Modified (comment): / 09-02-2019 / 15:51:50 / Claus Gittinger"
!

allowDomainVariables
    ^ allowDomainVariables
!

allowDomainVariables:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowDomainVariables := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:51:55 / Claus Gittinger"
!

allowEStrings
    "estrings have the syntax:
        e'...'
     where inside the string, c-language escapes are recognized
     AND embedded expressions {expr} are sliced into the string."

    ^ allowEStrings ? false.

    "Created: / 23-05-2019 / 10:25:50 / Claus Gittinger"
!

allowEStrings:aBoolean
    "estrings have the syntax:
        e'...'
     where inside the string, c-language escapes are recognized
     AND embedded expressions {expr} are sliced into the string."

    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowEStrings := aBoolean

    "Created: / 23-05-2019 / 10:26:02 / Claus Gittinger"
!

allowEmptyStatements
    ^ allowEmptyStatements ? false

    "Created: / 20-11-2006 / 13:56:14 / cg"
!

allowEmptyStatements:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowEmptyStatements := aBoolean.

    "Created: / 20-11-2006 / 14:26:48 / cg"
    "Modified (comment): / 09-02-2019 / 15:51:58 / Claus Gittinger"
!

allowExtendedBinarySelectors
    ^ allowExtendedBinarySelectors
!

allowExtendedBinarySelectors:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowExtendedBinarySelectors := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:52:01 / Claus Gittinger"
!

allowExtendedSTXSyntax
    "enables ALL of the ST/X extensions.
     Do not use for now, as stc does not support all of them"
     
    ^ allowExtendedSTXSyntax

    "Modified (comment): / 23-05-2019 / 10:36:04 / Claus Gittinger"
!

allowExtendedSTXSyntax:aBoolean
    "enables ALL of the ST/X extensions.
     Do not use for now, as stc does not support all of them"

    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowExtendedSTXSyntax := aBoolean.

    "Modified (comment): / 23-05-2019 / 10:41:41 / Claus Gittinger"
!

allowFixedPointLiterals
    ^ allowFixedPointLiterals
!

allowFixedPointLiterals:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowFixedPointLiterals := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:52:13 / Claus Gittinger"
!

allowFunctionCallSyntaxForBlockEvaluation
    ^ allowFunctionCallSyntaxForBlockEvaluation ? false

    "Modified: / 08-08-2017 / 16:57:17 / cg"
!

allowFunctionCallSyntaxForBlockEvaluation:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowFunctionCallSyntaxForBlockEvaluation := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:52:19 / Claus Gittinger"
!

allowGreekCharactersInIdentifier
    ^ allowGreekCharactersInIdentifier

    "Created: / 08-06-2019 / 14:52:42 / Claus Gittinger"
!

allowGreekCharactersInIdentifier:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowGreekCharactersInIdentifier := aBoolean

    "Created: / 08-06-2019 / 14:54:55 / Claus Gittinger"
!

allowHashAsBinarySelector
    ^ allowHashAsBinarySelector
!

allowJavaScriptConst
    "attn: possibly sent via perform (Parser >> parsePragma)"

    ^ allowJavaScriptConst

    "Created: / 08-08-2017 / 23:50:12 / cg"
    "Modified (comment): / 08-06-2019 / 15:00:52 / Claus Gittinger"
!

allowJavaScriptConst:aBoolean
    allowJavaScriptConst := aBoolean

    "Created: / 08-08-2017 / 23:50:23 / cg"
!

allowLazyValueExtension
    "allow !![...] to generate a lazy value"
    
    ^ allowLazyValueExtension

    "Modified (comment): / 03-06-2019 / 10:57:32 / Claus Gittinger"
!

allowLazyValueExtension:aBoolean
    "allow !![...] to generate a lazy value"
    "attn: possibly sent via perform (Parser >> parsePragma)"
    
    allowLazyValueExtension := aBoolean.

    "Modified (comment): / 03-06-2019 / 10:57:58 / Claus Gittinger"
!

allowLiteralNameSpaceSymbols
    ^ allowLiteralNameSpaceSymbols
!

allowLiteralNameSpaceSymbols:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowLiteralNameSpaceSymbols := aBoolean

    "Modified (comment): / 09-02-2019 / 15:52:36 / Claus Gittinger"
!

allowLocalVariableDeclarationWithInitializerExpression
    ^ allowLocalVariableDeclarationWithInitializerExpression
!

allowLocalVariableDeclarationWithInitializerExpression:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowLocalVariableDeclarationWithInitializerExpression := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:52:43 / Claus Gittinger"
!

allowNationalCharactersInIdentifier
    ^ allowNationalCharactersInIdentifier
!

allowNationalCharactersInIdentifier:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowNationalCharactersInIdentifier := aBoolean

    "Modified (comment): / 09-02-2019 / 15:52:46 / Claus Gittinger"
!

allowOldStyleAssignment
    "return true, if underscore-assignment (pre ST-80v4 syntax) are to be allowed"

    ^ allowOldStyleAssignment
!

allowOldStyleAssignment:aBoolean
    "return true, if underscore-assignment (pre ST-80v4 syntax) are to be allowed"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowOldStyleAssignment := aBoolean

    "Modified (format): / 09-02-2019 / 15:52:52 / Claus Gittinger"
!

allowParagraphInIdentifier
    "return true, if ยง-characters are allowed in identifiers (treated as letter)"

    ^ allowParagraphInIdentifier

    "Created: / 16-11-2016 / 22:29:06 / cg"
    "Modified (comment): / 08-06-2019 / 14:59:39 / Claus Gittinger"
!

allowParagraphInIdentifier:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowParagraphInIdentifier := aBoolean.

    "Created: / 16-11-2016 / 22:29:14 / cg"
    "Modified (comment): / 09-02-2019 / 15:52:54 / Claus Gittinger"
!

allowPeriodAsNameSpaceSeparator
    "experimental syntax: foo.bar"

    ^ allowPeriodAsNameSpaceSeparator ? false

    "Created: / 23-09-2018 / 00:48:59 / Claus Gittinger"
!

allowPeriodAsNameSpaceSeparator:aBoolean
    "experimental syntax: foo.bar"
    "attn: possibly sent via perform (Parser >> parsePragma)"


    allowPeriodAsNameSpaceSeparator := aBoolean

    "Created: / 23-09-2018 / 00:49:09 / Claus Gittinger"
    "Modified (comment): / 09-02-2019 / 15:53:00 / Claus Gittinger"
!

allowPeriodInSymbol
    ^ allowPeriodInSymbol
!

allowPeriodInSymbol:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowPeriodInSymbol := aBoolean

    "Modified (comment): / 09-02-2019 / 15:53:02 / Claus Gittinger"
!

allowQualifiedNames
    "return true, if '#{..}' and 'namespace.varName' qualified names are allowed"

    ^ allowQualifiedNames

    "Modified (comment): / 23-09-2018 / 01:08:34 / Claus Gittinger"
!

allowQualifiedNames:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowQualifiedNames := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:53:11 / Claus Gittinger"
!

allowRStrings
    "rstrings have the syntax:
        r'...'
     which generates a regex"

    ^ allowRStrings ? false.

    "Created: / 03-06-2019 / 11:11:25 / Claus Gittinger"
!

allowRStrings:aBoolean
    "rstrings have the syntax:
        r'...'
     which generates a regex"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowRStrings := aBoolean

    "Created: / 03-06-2019 / 11:11:51 / Claus Gittinger"
    "Modified (comment): / 08-06-2019 / 15:01:17 / Claus Gittinger"
!

allowReservedWordsAsSelectors
    ^ allowReservedWordsAsSelectors
!

allowReservedWordsAsSelectors:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowReservedWordsAsSelectors := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:53:13 / Claus Gittinger"
!

allowSTVExtensions
    "return true, if support for ST/V extensions is enabled."

    ^ allowSTVExtensions
!

allowSTVExtensions:aBoolean
    "if support for ST/V extensions is enabled."
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSTVExtensions := aBoolean

    "Created: / 09-02-2019 / 15:53:32 / Claus Gittinger"
!

allowSTVPrimitives
    "return true, if support for ST/V primitives is enabled."

    ^ allowSTVPrimitives
!

allowSTVPrimitives:aBoolean
    "if support for ST/V primitives is enabled."
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSTVPrimitives := aBoolean

    "Created: / 09-02-2019 / 15:53:53 / Claus Gittinger"
!

allowSTXDelimiterComments
    "are ST/X token-delimited comments allowed?
     (see comment on class side)"

    ^ allowSTXDelimiterComments
!

allowSTXDelimiterComments:aBoolean
    "are ST/X token-delimited comments allowed? (default is true)
     (see comment on class side)"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSTXDelimiterComments := aBoolean.

    "
     ParserFlags allowSTXDelimiterComments:false
     ParserFlags allowSTXDelimiterComments:true
    "

    "Modified (comment): / 09-02-2019 / 15:54:26 / Claus Gittinger"
!

allowSTXEOLComments
    "are ST/X end-of-line comments allowed?"

    ^ allowSTXEOLComments
!

allowSTXEOLComments:aBoolean
    "are ST/X end-of-line comments allowed? (default is true)"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSTXEOLComments := aBoolean.

    "
     ParserFlags allowSTXEOLComments:false
     ParserFlags allowSTXEOLComments:true
    "

    "Modified (comment): / 09-02-2019 / 15:54:21 / Claus Gittinger"
!

allowSTXExtendedArrayLiterals
    "are scheme-style typed literal arrays allowed?"

    ^ allowSTXExtendedArrayLiterals ? false
!

allowSTXExtendedArrayLiterals:aBoolean
    "are scheme-style typed literal arrays allowed?"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSTXExtendedArrayLiterals := aBoolean

    "Modified (comment): / 09-02-2019 / 15:54:33 / Claus Gittinger"
!

allowSTXFunctions
    ^ false

    "Created: / 23-05-2011 / 17:43:45 / cg"
!

allowSignedByteArrayElements
    ^ allowSignedByteArrayElements
!

allowSignedByteArrayElements:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSignedByteArrayElements := aBoolean

    "Modified (comment): / 09-02-2019 / 15:54:39 / Claus Gittinger"
!

allowSqueakExtensions
    "return true, if support for squeak extensions
	computed arrays { .., }
	c/java style arguments in message sends rec foo(arg1, ... argN)
     is enabled."

    ^ allowSqueakExtensions
!

allowSqueakExtensions:aBoolean
    "this allows turning on/off support for squeak extensions:
        computed arrays { .., }
        c/java style arguments in message sends rec foo(arg1, ... argN)
     attn: possibly sent via perform (Parser >> parsePragma)
    "

    allowSqueakExtensions := aBoolean

    "Modified (comment): / 09-02-2019 / 15:54:53 / Claus Gittinger"
!

allowSqueakPrimitives
    "return true, if support for squeak primitives is enabled."

    ^ allowSqueakPrimitives
!

allowSqueakPrimitives:aBoolean
    "this allows turning on/off support for squeak primitives"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowSqueakPrimitives := aBoolean

    "Modified (comment): / 09-02-2019 / 15:55:01 / Claus Gittinger"
!

allowStringEscapes
    ^ allowStringEscapes
!

allowStringEscapes:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowStringEscapes := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:55:04 / Claus Gittinger"
!

allowSymbolsStartingWithDigit
    "return true, if a symbol is allowed to start with a digit
     i.e. as in #2D.
     This seems to be ok in new Squeak/Pharo versions"

    ^ allowSymbolsStartingWithDigit

    "Created: / 18-06-2017 / 16:26:08 / cg"
!

allowSymbolsStartingWithDigit:aBoolean
    "control if a symbol is allowed to start with a digit
     i.e. as in #2D.
     This seems to be ok in new Squeak/Pharo versions.
     attn: possibly sent via perform (Parser >> parsePragma)"

    allowSymbolsStartingWithDigit := aBoolean

    "Created: / 18-06-2017 / 16:26:23 / cg"
    "Modified (comment): / 09-02-2019 / 15:55:14 / Claus Gittinger"
!

allowUnderscoreInIdentifier
    ^ allowUnderscoreInIdentifier
!

allowUnderscoreInIdentifier:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowUnderscoreInIdentifier := aBoolean

    "Modified (comment): / 09-02-2019 / 15:55:21 / Claus Gittinger"
!

allowUnicodeCharacters
    ^ allowUnicodeCharacters
!

allowUnicodeCharacters:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowUnicodeCharacters := aBoolean

    "Modified (comment): / 09-02-2019 / 15:55:25 / Claus Gittinger"
!

allowUnicodeStrings
    ^ allowUnicodeStrings
!

allowUnicodeStrings:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowUnicodeStrings := aBoolean

    "Modified (comment): / 09-02-2019 / 15:55:28 / Claus Gittinger"
!

allowVariableReferences
    ^ allowVariableReferences
!

allowVariableReferences:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowVariableReferences := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:55:32 / Claus Gittinger"
!

allowVisualAgeESSymbolLiterals
    ^ allowVisualAgeESSymbolLiterals
!

allowVisualAgeESSymbolLiterals:aBoolean
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowVisualAgeESSymbolLiterals := aBoolean.

    "Modified (comment): / 09-02-2019 / 15:55:35 / Claus Gittinger"
!

allowVisualAgePrimitives
    "return true, if support for V'Age primitives is enabled."

    ^ allowVisualAgePrimitives
!

allowVisualAgePrimitives:aBoolean
    "this allows turning on/off support for V'Age primitives"
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowVisualAgePrimitives := aBoolean

    "Modified (comment): / 09-02-2019 / 15:55:39 / Claus Gittinger"
!

allowVisualWorksMethodAnnotations
    "return true, if support for V'Works extended primitive syntax for method annotations."

    ^ allowVisualWorksMethodAnnotations

    "Created: / 07-07-2006 / 15:48:30 / cg"
!

allowVisualWorksMethodAnnotations:aBoolean
    "turn on/off support for V'Works extended primitive syntax for method annotations."
    "attn: possibly sent via perform (Parser >> parsePragma)"

    allowVisualWorksMethodAnnotations := aBoolean

    "Created: / 07-07-2006 / 15:49:03 / cg"
    "Modified (comment): / 09-02-2019 / 15:55:42 / Claus Gittinger"
!

singlePrecisionFloatF
    "by default, the 'f'-character in a float literal will generate
     double-precision Float instances.
     With singlePrecisionFloats, it will generate single precision ShortFloat instances.
     Notice, that there is some confusion among Smalltalk systems, whether a float has
     single or double precision (VW vs. V'age).
     In ST/X, floats have double-precision by default."
     
    ^ singlePrecisionFloatF

    "Created: / 26-05-2019 / 11:31:37 / Claus Gittinger"
    "Modified (comment): / 08-06-2019 / 15:02:20 / Claus Gittinger"
!

singlePrecisionFloatF:aBoolean
    "by default, the 'f'-character in a float literal will generate
     double-precision Float instances.
     With singlePrecisionFloats, it will generate single precision ShortFloat instances.
     Notice, that there is some confusion among Smalltalk systems, whether a float has
     single or double precision (VW vs. V'age).
     In ST/X, floats have double-precision by default."
     
    singlePrecisionFloatF := aBoolean

    "Created: / 26-05-2019 / 11:32:11 / Claus Gittinger"
    "Modified (comment): / 08-06-2019 / 15:02:14 / Claus Gittinger"
! !

!ParserFlags methodsFor:'accessing-warning-control'!

warnAboutBadComments
    ^ warnAboutBadComments
!

warnAboutBadComments:aBoolean
    warnAboutBadComments := aBoolean.
!

warnAboutNonLowercaseLocalVariableNames
    ^ warnAboutNonLowercaseLocalVariableNames
!

warnAboutNonLowercaseLocalVariableNames:aBoolean
    warnAboutNonLowercaseLocalVariableNames := aBoolean.
!

warnAboutPeriodInSymbol
    ^ warnAboutPeriodInSymbol
!

warnAboutPeriodInSymbol:aBoolean
    warnAboutPeriodInSymbol := aBoolean.
!

warnAboutPossibleSTCCompilationProblems
    ^ warnAboutPossibleSTCCompilationProblems

    "Created: / 16-11-2006 / 14:24:38 / cg"
!

warnAboutPossibleSTCCompilationProblems:aBoolean
    warnAboutPossibleSTCCompilationProblems := aBoolean.

    "Created: / 16-11-2006 / 14:24:40 / cg"
!

warnAboutPossiblyUnimplementedSelectors
    ^ warnAboutPossiblyUnimplementedSelectors
!

warnAboutPossiblyUnimplementedSelectors:aBoolean
    warnAboutPossiblyUnimplementedSelectors := aBoolean.
!

warnAboutPossiblyUninitializedLocals
    ^ warnAboutPossiblyUninitializedLocals

    "Created: / 23-04-2019 / 23:09:55 / Claus Gittinger"
!

warnAboutPossiblyUninitializedLocals:aBoolean
    warnAboutPossiblyUninitializedLocals := aBoolean.

    "Created: / 23-04-2019 / 23:10:01 / Claus Gittinger"
!

warnAboutReferenceToPrivateClass
    "controls generation of warning messages when a private class is referenced"

    ^ warnAboutReferenceToPrivateClass
!

warnAboutReferenceToPrivateClass:aBoolean
    "controls generation of warning messages when a private class is referenced"

    warnAboutReferenceToPrivateClass := aBoolean
!

warnAboutShortLocalVariableNames
    ^ warnAboutShortLocalVariableNames
!

warnAboutShortLocalVariableNames:aBoolean
    warnAboutShortLocalVariableNames := aBoolean.
!

warnAboutUnknownCharacterEscapesInJavaScriptStringConstant
    ^ warnAboutUnknownCharacterEscapesInJavaScriptStringConstant ? false

    "Created: / 04-10-2011 / 19:51:19 / cg"
!

warnAboutUnknownCharacterEscapesInJavaScriptStringConstant:aBoolean
    warnAboutUnknownCharacterEscapesInJavaScriptStringConstant := aBoolean.

    "Created: / 04-10-2011 / 19:51:27 / cg"
!

warnAboutVariableNameConventions
    ^ warnAboutVariableNameConventions
!

warnAboutVariableNameConventions:aBoolean
    warnAboutVariableNameConventions := aBoolean.
!

warnAboutWrongVariableNames
    ^ warnAboutWrongVariableNames
!

warnAboutWrongVariableNames:aBoolean
    warnAboutWrongVariableNames := aBoolean.
!

warnAssignmentToBlockArgument
    ^ warnAssignmentToBlockArgument
!

warnAssignmentToBlockArgument:aBoolean
    warnAssignmentToBlockArgument := aBoolean.
!

warnAssignmentToMethodArgument
    ^ warnAssignmentToMethodArgument
!

warnAssignmentToMethodArgument:aBoolean
    warnAssignmentToMethodArgument := aBoolean.
!

warnAssignmentToPoolVariable
    ^ warnAssignmentToPoolVariable
!

warnAssignmentToPoolVariable:aBoolean
    warnAssignmentToPoolVariable := aBoolean.
!

warnCommonMistakes
    ^ warnCommonMistakes
!

warnCommonMistakes:aBoolean
    warnCommonMistakes := aBoolean.
!

warnDollarInIdentifier
    ^ warnDollarInIdentifier
!

warnDollarInIdentifier:aBoolean
    warnDollarInIdentifier := aBoolean.
!

warnHiddenVariables
    ^ warnHiddenVariables
!

warnHiddenVariables:aBoolean
    "controls generation of warning messages about hiding variables by locals"

    warnHiddenVariables := aBoolean.

    "Modified: / 30-11-2010 / 15:00:55 / cg"
!

warnInconsistentReturnValues
    ^ warnInconsistentReturnValues
!

warnInconsistentReturnValues:aBoolean
    warnInconsistentReturnValues := aBoolean.
!

warnOldStyleAssignment
    ^ warnOldStyleAssignment
!

warnOldStyleAssignment:aBoolean
    warnOldStyleAssignment := aBoolean.
!

warnParagraphInIdentifier
    ^ warnParagraphInIdentifier

    "Created: / 16-11-2016 / 22:29:33 / cg"
!

warnParagraphInIdentifier:aBoolean
    warnParagraphInIdentifier := aBoolean.

    "Created: / 16-11-2016 / 22:29:45 / cg"
!

warnPlausibilityChecks
    "controls generation of warning messages about plausibility checks (possible precedence, etc.)"

    ^ warnPlausibilityChecks ? true

    "Created: / 19-01-2012 / 10:38:54 / cg"
!

warnPlausibilityChecks:aBoolean
    "controls generation of warning messages about plausibility checks (possible precedence, etc.)"

    warnPlausibilityChecks := aBoolean

    "Created: / 19-01-2012 / 10:39:02 / cg"
!

warnPossibleIncompatibilities
    "holds true, if possible incompatibilities (with other ST systems)
     are to be warned about"

    ^ warnPossibleIncompatibilities
!

warnPossibleIncompatibilities:aBoolean
    "holds true, if possible incompatibilities (with other ST systems)
     are to be warned about"

    warnPossibleIncompatibilities := aBoolean.
!

warnST80Directives
    ^ warnST80Directives
!

warnST80Directives:aBoolean
    warnST80Directives := aBoolean.

    "Modified: / 30-01-2011 / 13:01:06 / cg"
!

warnSTXHereExtensionUsed
    ^ warnSTXHereExtensionUsed
!

warnSTXHereExtensionUsed:aBoolean
    warnSTXHereExtensionUsed := aBoolean.
!

warnSTXNameSpaceUse
    ^ warnSTXNameSpaceUse
!

warnSTXNameSpaceUse:aBoolean
    warnSTXNameSpaceUse := aBoolean.
!

warnSTXSpecialComment
    ^ warnSTXSpecialComment
!

warnSTXSpecialComment:aBoolean
    warnSTXSpecialComment := aBoolean.
!

warnUndeclared
    ^ warnUndeclared
!

warnUndeclared:aBoolean
    warnUndeclared := aBoolean.
!

warnUnderscoreInIdentifier
    ^ warnUnderscoreInIdentifier
!

warnUnderscoreInIdentifier:aBoolean
    warnUnderscoreInIdentifier := aBoolean.
!

warnUnusedVars
    ^ warnUnusedVars
!

warnUnusedVars:aBoolean
    warnUnusedVars := aBoolean.
!

warnings
    ^ warnings ? true

    "Modified: / 30-01-2011 / 13:05:48 / cg"
!

warnings:aBoolean
    warnings := aBoolean.

    "Modified: / 30-01-2011 / 13:00:51 / cg"
! !

!ParserFlags methodsFor:'initialization'!

initialize
    "each instance is initially setup from the classes global defaults.
     (but can be changed as required for an individual compilation run"

    singlePrecisionFloatF := SinglePrecisionFloatF.
    
    warnings := Warnings.
    warnUndeclared := WarnUndeclared.
    warnUnusedVars := WarnUnusedVars.
    warnST80Directives := WarnST80Directives.
    warnSTXSpecialComment := WarnSTXSpecials.
    warnSTXNameSpaceUse := WarnSTXSpecials.
    warnSTXHereExtensionUsed := WarnSTXSpecials.
    warnUnderscoreInIdentifier := WarnUnderscoreInIdentifier.
    warnDollarInIdentifier := WarnDollarInIdentifier.
    warnParagraphInIdentifier := WarnParagraphInIdentifier.
    warnOldStyleAssignment := WarnOldStyleAssignment.
    warnCommonMistakes := WarnCommonMistakes.
    warnPossibleIncompatibilities := WarnPossibleIncompatibilities.
    warnAboutVariableNameConventions := WarnAboutVariableNameConventions.
    warnAboutWrongVariableNames := WarnAboutWrongVariableNames.
    warnAboutBadComments := WarnAboutBadComments.
    warnAboutReferenceToPrivateClass := WarnAboutReferenceToPrivateClass.
    warnAboutPossiblyUninitializedLocals := WarnAboutPossiblyUninitializedLocals.
    warnHiddenVariables := WarnHiddenVariables.
    warnInconsistentReturnValues := WarnInconsistentReturnValues.
    warnAboutNonLowercaseLocalVariableNames := WarnAboutNonLowercaseLocalVariableNames.
    warnAboutShortLocalVariableNames := WarnAboutShortLocalVariableNames.
    warnAboutPossibleSTCCompilationProblems := WarnAboutPossibleSTCCompilationProblems.
    warnAboutPossiblyUnimplementedSelectors := WarnAboutPossiblyUnimplementedSelectors.
    warnAboutPeriodInSymbol := WarnAboutPeriodInSymbol.
    warnAboutUnknownCharacterEscapesInJavaScriptStringConstant := WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant.
    warnPlausibilityChecks := WarnPlausibilityChecks.
    warnAssignmentToBlockArgument := WarnAssignmentToBlockArgument.
    warnAssignmentToMethodArgument := WarnAssignmentToMethodArgument.
    warnAssignmentToPoolVariable := WarnAssignmentToPoolVariable.

    allowUnderscoreInIdentifier := AllowUnderscoreInIdentifier.
    allowDollarInIdentifier := AllowDollarInIdentifier.
    allowParagraphInIdentifier := AllowParagraphInIdentifier.
    allowOldStyleAssignment := AllowOldStyleAssignment.
    allowSqueakExtensions := AllowSqueakExtensions.
    allowDolphinExtensions := AllowDolphinExtensions.
    allowLiteralNameSpaceSymbols := AllowLiteralNameSpaceSymbols.
    allowExtendedBinarySelectors := AllowExtendedBinarySelectors.
    allowCaretAsBinop := AllowCaretAsBinop.
    allowFunctionCallSyntaxForBlockEvaluation := AllowFunctionCallSyntaxForBlockEvaluation.
    allowLocalVariableDeclarationWithInitializerExpression := AllowLocalVariableDeclarationWithInitializerExpression.
    allowDomainVariables := AllowDomainVariables.
    allowArrayIndexSyntaxExtension := AllowArrayIndexSyntaxExtension.
    allowReservedWordsAsSelectors := AllowReservedWordsAsSelectors.
    allowVariableReferences := AllowVariableReferences.
    allowLazyValueExtension := AllowLazyValueExtension.
    allowFixedPointLiterals := AllowFixedPointLiterals.
    allowExtendedSTXSyntax := AllowExtendedSTXSyntax.
    allowQualifiedNames := AllowQualifiedNames.
    allowVisualAgeESSymbolLiterals := AllowVisualAgeESSymbolLiterals.
    allowExtensionsToPrivateClasses := AllowExtensionsToPrivateClasses.
    allowVisualAgePrimitives := AllowVisualAgePrimitives.
    allowSqueakPrimitives := AllowSqueakPrimitives.
    allowSTVPrimitives := AllowSTVPrimitives.
    allowSTVExtensions := AllowSTVExtensions.
    allowNationalCharactersInIdentifier := AllowNationalCharactersInIdentifier.
    allowGreekCharactersInIdentifier := AllowGreekCharactersInIdentifier.
    allowHashAsBinarySelector := AllowHashAsBinarySelector.
    allowSTXEOLComments := AllowSTXEOLComments.
    allowSTXDelimiterComments := AllowSTXDelimiterComments.
    allowSTXExtendedArrayLiterals := AllowSTXExtendedArrayLiterals.
    allowVisualWorksMethodAnnotations := AllowVisualWorksMethodAnnotations.
    allowPossibleSTCCompilationProblems := AllowPossibleSTCCompilationProblems.
    allowEmptyStatements := AllowEmptyStatements.
    allowPeriodInSymbol := AllowPeriodInSymbol.
    allowPeriodAsNameSpaceSeparator := AllowPeriodAsNameSpaceSeparator.
    
    "/ these are only supported in the new compiler
    allowCStrings := AllowCStrings.
    allowEStrings := AllowEStrings.
    allowRStrings := AllowRStrings.
    allowUnicodeStrings := AllowUnicodeStrings.
    allowUnicodeCharacters := AllowUnicodeCharacters.
    allowCharacterEscapes := AllowCharacterEscapes.
    allowStringEscapes := AllowStringEscapes.
    allowAssignmentToBlockArgument := AllowAssignmentToBlockArgument.
    allowAssignmentToMethodArgument := AllowAssignmentToMethodArgument.
    allowAssignmentToPoolVariable := AllowAssignmentToPoolVariable.
    allowSignedByteArrayElements := AllowSignedByteArrayElements.
    allowSymbolsStartingWithDigit := AllowSymbolsStartingWithDigit.

    allowJavaScriptConst := AllowJavaScriptConst.              
    
    arraysAreImmutable := ArraysAreImmutable ? true.
    stringsAreImmutable := StringsAreImmutable ? true.
    implicitSelfSends := ImplicitSelfSends ? false.
    lineNumberInfo := LineNumberInfo ? false.

    stcKeepCIntermediate := STCKeepCIntermediate.
    stcKeepOIntermediate := STCKeepOIntermediate.
    stcKeepSTIntermediate := STCKeepSTIntermediate.
    stcModulePath := STCModulePath.
    stcCompilation := STCCompilation.
    stcCompilationIncludes := STCCompilationIncludes.
    stcCompilationDefines := STCCompilationDefines.
    stcCompilationOptions := STCCompilationOptions.
    stcPath := STCPath.
    ccCompilationOptions := CCCompilationOptions.
    ccPath := CCPath.
    linkArgs := LinkArgs.
    linkCommand := LinkCommand.
    libPath := LibPath.
    searchedLibraries := SearchedLibraries.

    "
     ParserFlags initialize.
     self new inspect.
    "

    "Modified: / 08-08-2017 / 23:50:01 / cg"
    "Modified: / 08-06-2019 / 14:53:04 / Claus Gittinger"
! !

!ParserFlags class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


ParserFlags initialize!