ParserFlags.st
author Claus Gittinger <cg@exept.de>
Tue, 31 Jan 2012 12:12:30 +0100
changeset 2803 de9ca0b32bd4
parent 2801 5046659b4c15
child 2804 f76727ee9e2d
permissions -rw-r--r--
class definition added: #defineFor_borlandC #useCompiler: #usedCompiler changed: #initialize #useBorlandC #useGnuC #useVisualC

"
 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' }"

Object subclass:#ParserFlags
	instanceVariableNames:'warnings warnUnusedVars warnUndeclared warnST80Directives
		warnSTXHereExtensionUsed warnSTXSpecialComment
		warnUnderscoreInIdentifier warnOldStyleAssignment
		warnCommonMistakes warnSTXNameSpaceUse
		warnPossibleIncompatibilities warnDollarInIdentifier
		warnHiddenVariables warnAboutVariableNameConventions
		warnAboutWrongVariableNames warnAboutBadComments
		warnInconsistentReturnValues
		warnAboutNonLowercaseLocalVariableNames
		warnAboutPossibleSTCCompilationProblems
		warnAboutReferenceToPrivateClass warnAboutShortLocalVariableNames
		warnAboutPossiblyUnimplementedSelectors
		warnAboutUnknownCharacterEscapesInJavaScriptStringConstant
		warnPlausibilityChecks allowLiteralNameSpaceSymbols
		allowUnderscoreInIdentifier allowDollarInIdentifier
		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'
	classVariableNames:'WarnST80Directives WarnUnusedVars WarnUndeclared
		WarnAboutWrongVariableNames WarnAboutBadComments
		WarnAboutVariableNameConventions WarnSTXSpecials
		WarnOldStyleAssignment WarnUnderscoreInIdentifier
		WarnCommonMistakes WarnPossibleIncompatibilities
		WarnDollarInIdentifier WarnHiddenVariables
		WarnAboutNonLowercaseLocalVariableNames
		WarnInconsistentReturnValues Warnings
		WarnAboutPossibleSTCCompilationProblems
		WarnAboutReferenceToPrivateClass WarnAboutShortLocalVariableNames
		WarnAboutPossiblyUnimplementedSelectors WarnAboutPeriodInSymbol
		WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant
		WarnPlausibilityChecks AllowUnderscoreInIdentifier
		AllowFunctionCallSyntaxForBlockEvaluation AllowLazyValueExtension
		AllowVariableReferences AllowReservedWordsAsSelectors
		AllowLocalVariableDeclarationWithInitializerExpression
		AllowArrayIndexSyntaxExtension AllowDomainVariables
		AllowDollarInIdentifier AllowSqueakExtensions AllowQualifiedNames
		AllowDolphinExtensions AllowOldStyleAssignment
		AllowExtendedBinarySelectors AllowExtendedSTXSyntax
		AllowFixedPointLiterals AllowLiteralNameSpaceSymbols
		AllowVisualAgeESSymbolLiterals AllowExtensionsToPrivateClasses
		AllowSqueakPrimitives AllowVisualAgePrimitives AllowSTVPrimitives
		AllowSTVExtensions AllowNationalCharactersInIdentifier
		AllowHashAsBinarySelector AllowSTXEOLComments
		AllowPossibleSTCCompilationProblems AllowEmptyStatements
		AllowVisualWorksMethodAnnotations ArraysAreImmutable
		AllowPeriodInSymbol StringsAreImmutable ImplicitSelfSends
		STCModulePath STCKeepCIntermediate STCKeepOIntermediate
		STCKeepSTIntermediate STCCompilation STCCompilationIncludes
		STCCompilationDefines STCCompilationOptions STCPath
		CCCompilationOptions CCPath LinkArgs LinkSharedArgs LinkCommand
		LibPath SearchedLibraries MakeCommand AllowCaretAsBinop
		AllowUnicodeStrings AllowUnicodeCharacters AllowCharacterEscapes
		AllowStringEscapes AllowAssignmentToBlockArgument
		AllowAssignmentToMethodArgument AllowAssignmentToPoolVariable
		LibDirectory VCTop SDKTop BCCTop ForcedCompiler DefineForBorlandC
		DefineForVisualC DefineForMSVER DefineForMSC DefineForGNUC'
	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).

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

    for stx debugging:
        STCKeepCIntermediate := true

"
! !

!ParserFlags class methodsFor:'instance creation'!

new
    ^ self basicNew initialize
! !

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

allowExtensionsToPrivateClasses
    ^ AllowExtensionsToPrivateClasses
!

allowExtensionsToPrivateClasses:aBoolean
    AllowExtensionsToPrivateClasses := aBoolean
!

allowPossibleSTCCompilationProblems
    ^ AllowPossibleSTCCompilationProblems

    "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 are immutable literals"

    ^ ArraysAreImmutable
!

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

    ArraysAreImmutable := aBoolean.

    "
     can be added to your private.rc file:

     ParserFlags arraysAreImmutable:true     
     ParserFlags arraysAreImmutable:false      
    "
!

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

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-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
!

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:something 
    STCKeepCIntermediate := something.

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

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

stcKeepOIntermediate
    ^ STCKeepOIntermediate ? false

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

stcKeepOIntermediate:something 
    STCKeepOIntermediate := something.
!

stcKeepSTIntermediate
    ^ STCKeepSTIntermediate ? false

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

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

stcKeepSTIntermediate:something 
    STCKeepSTIntermediate := something.

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

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

stcModulePath
    ^ STCModulePath
!

stcModulePath:something 
    STCModulePath := something.
!

stcPath
    ^ STCPath
!

stcPath:aSymbol
    STCPath := aSymbol
!

useBorlandC
    "true if borland compiler should be used"

    ^ self usedCompiler = DefineForBorlandC

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

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

    ForcedCompiler := aCompilerDefine.

    "Created: / 31-01-2012 / 12:01:08 / cg"
!

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

    ^ self usedCompiler = DefineForGNUC

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

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

    |compiler|

    ^ (compiler := self usedCompiler) = DefineForVisualC
    or:[ compiler = DefineForMSC ]

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

usedCompiler
    ForcedCompiler notNil ifTrue:[^ ForcedCompiler].
    ^ OperatingSystem getCCDefine

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

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"

    ^ AllowArrayIndexSyntaxExtension ? false
!

allowArrayIndexSyntaxExtension:aBoolean
    "experimental"

    AllowArrayIndexSyntaxExtension := aBoolean.

    "
     self allowArrayIndexSyntaxExtension:true
     self allowArrayIndexSyntaxExtension:false
    "
!

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

allowDollarInIdentifier
    "return true, if $-characters are allowed in identifiers.
     Notice, that dollars are NEVER allowed as the first character in an identifier."

    ^ AllowDollarInIdentifier

    "Created: 7.9.1997 / 01:32:18 / cg"
    "Modified: 7.9.1997 / 01:39:44 / cg"
!

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

    AllowDollarInIdentifier := aBoolean.

    "Created: 7.9.1997 / 01:34:49 / cg"
    "Modified: 7.9.1997 / 01:39:30 / cg"
!

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

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 syntay extensions"

    AllowExtendedBinarySelectors := aBoolean
!

allowExtendedSTXSyntax
    "experimental syntay extensions"

    ^ AllowExtendedSTXSyntax
!

allowExtendedSTXSyntax:aBoolean
    "experimental syntay extensions"

    AllowExtendedSTXSyntax := aBoolean

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

allowFixedPointLiterals
    "return true, if nnnsn (FixedPoint) literals are allowed"

    ^ AllowFixedPointLiterals
!

allowFixedPointLiterals:aBoolean
    "enable/disable, if nnnsn (FixedPoint) literals are allowed"

    AllowFixedPointLiterals := aBoolean
!

allowFunctionCallSyntaxForBlockEvaluation
    "experimental"

    ^ AllowFunctionCallSyntaxForBlockEvaluation

    "
     AllowFunctionCallSyntaxForBlockEvaluation := true
    "
!

allowFunctionCallSyntaxForBlockEvaluation:aBoolean
    "experimental"

    AllowFunctionCallSyntaxForBlockEvaluation := aBoolean.
!

allowHashAsBinarySelector
    ^ AllowHashAsBinarySelector
!

allowHashAsBinarySelector:aBoolean
    AllowHashAsBinarySelector := aBoolean

    "
     self allowHashAsBinarySelector:true
     self allowHashAsBinarySelector:false   
    "
!

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

    ^ AllowLiteralNameSpaceSymbols
!

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

    AllowLiteralNameSpaceSymbols := aBoolean
!

allowLocalVariableDeclarationWithInitializerExpression
    "experimental"

    ^ AllowLocalVariableDeclarationWithInitializerExpression
!

allowLocalVariableDeclarationWithInitializerExpression:aBoolean
    "experimental"

    AllowLocalVariableDeclarationWithInitializerExpression := aBoolean.
!

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
!

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 #{..} qualified names are allowed"

    ^ AllowQualifiedNames
!

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

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

allowSTXEOLComments
    ^ AllowSTXEOLComments
!

allowSTXEOLComments:aBoolean
    AllowSTXEOLComments := aBoolean.

    "
     self allowSTXEOLComments:true
     self allowSTXEOLComments:false
    "
!

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
!

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

!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
!

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

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

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
    Warnings := true.
    WarnUndeclared := true.
    WarnUnusedVars := true.
    WarnSTXSpecials := false.
    WarnST80Directives := false.
    WarnAboutWrongVariableNames := true.
    WarnAboutVariableNameConventions := true.
    WarnAboutBadComments := true.
    WarnUnderscoreInIdentifier := false.
    WarnDollarInIdentifier := 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.

    AllowReservedWordsAsSelectors := false.
    AllowUnderscoreInIdentifier := true.        "/ underscores in identifiers
    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 := false.             "/ squeak computed array
    AllowSqueakPrimitives := false.
    AllowSTVPrimitives := false.                "/ number-sign syntax
    AllowSTVExtensions := false.
    AllowNationalCharactersInIdentifier := false.
    AllowHashAsBinarySelector := true.
    AllowSTXEOLComments := true.
    AllowVisualWorksMethodAnnotations := false.
    AllowPossibleSTCCompilationProblems := true.
    AllowEmptyStatements := false.
    AllowPeriodInSymbol := false.
    "/ these are only used by the new compiler
    AllowUnicodeStrings := false.               
    AllowUnicodeCharacters := false.
    AllowCharacterEscapes := false.
    AllowStringEscapes := false.
    AllowAssignmentToBlockArgument := false.
    AllowAssignmentToMethodArgument := false.
    AllowAssignmentToPoolVariable := false.
    "/ AllowAssignmentToPoolVariable := true.

    ArraysAreImmutable := false.                "/ no longer care for ST-80 compatibility
    StringsAreImmutable := false.               "/ no longer care for ST-80 compatibility
    ImplicitSelfSends := false.

    STCKeepCIntermediate := false.
    STCKeepOIntermediate := false.
    STCKeepSTIntermediate := false.
    STCCompilation := #default.

    DefineForBorlandC := '__BORLANDC__'.
    DefineForVisualC := '__VISUALC__'.
    DefineForMSC := '__MSC__'.
    DefineForGNUC := '__GNUC__'.

    self initializeSTCFlagsForTopDirectory:'../..'.

    "
     ParserFlags initialize
    "

    "Modified: / 09-08-2006 / 18:47:18 / fm"
    "Modified: / 31-01-2012 / 12:06:32 / cg"
!

initializeSTCFlagsForTopDirectory:topDirArg
    "notice: for now, can only initialize for borland+windows or linux;
     visualC setup still fails"

    |topDir vcTop sdkTop bccTop useBorlandC useVisualC|

    topDir := topDirArg.
    OperatingSystem isMSWINDOWSlike ifTrue:[
        topDir := topDirArg copyReplaceAll:$/ with:$\.
    ].

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

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

    OperatingSystem isMSWINDOWSlike ifTrue:[
        useBorlandC := useVisualC := false.

        STCCompilationIncludes := '-I',topDir,'\include -I',topDir,'\libopengl'.
        (bccTop := BCCTop) isNil ifTrue:[
            bccTop := #(
                        'C:\Borland\bcc55'
                       ) detect:[:path | path asFilename exists and:[(path asFilename construct:'include') exists]] ifNone:nil.
        ].

        (bccTop notNil and:[bccTop asFilename exists]) ifTrue:[
            STCCompilationIncludes := STCCompilationIncludes,' -I',bccTop,'\Include'.
            LibDirectory := topDir,'\libbc'.
            LinkArgs := '-L',topDir,'\libbc'.
            LinkArgs := LinkArgs,' -L',bccTop,'\Lib -r -c -ap -Tpd -Gi -w-dup'.
            CCPath := 'bcc32'.
            MakeCommand := 'bmake'.
            LinkCommand := 'ilink32'.
            CCCompilationOptions := '-w-'.
            useBorlandC := true.
        ] ifFalse:[
            (vcTop := VCTop) isNil ifTrue:[
                vcTop := #(
                            'C:\Program Files\Microsoft Visual Studio 10.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 := #(
                                'C:\Program Files\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 := topDir,'\libvc'.
                LinkArgs := '-L',topDir,'\libvc'.
                LinkArgs := LinkArgs,' -LC:\Borland\bcc55\Lib -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:\Borland\xxxxx\Include'.
                LibDirectory := topDir,'\libbc'.
                LinkArgs := '-L',topDir,'\libbc'.
                LinkArgs := LinkArgs,' -LC:\Borland\xxxxx\Lib -r -c -ap -Tpd -Gi -w-dup'.
            ].
        ].
        STCCompilationDefines := '-DWIN32'.
        STCCompilationOptions := '+optinline +inlineNew'.
        (topDir,'\stc\stc.exe') asFilename exists ifTrue:[
            STCPath := (topDir,'\stc\stc.exe').
        ] ifFalse:[
            STCPath := 'stc.exe'.
        ].
        LibPath := ''.
        SearchedLibraries := #('import32.lib').
        "/ SearchedLibraries := #('import32.lib' 'glu32.lib' 'opengl32.lib').
    ] ifFalse:[
        STCCompilationIncludes := '-I',topDir,'/include'.
        STCCompilationDefines := ''.
        STCCompilationOptions := '+optinline +inlineNew'.
        STCPath := topDir,'/stc/stc'.
        CCCompilationOptions := '-O -m32'.
        ParserFlags useGnuC ifTrue:[
            CCPath := 'gcc'
        ] ifFalse:[
            CCPath := 'cc'
        ].
        LinkArgs := '-m32'.
        LinkSharedArgs := '-shared -m32'.
        LinkCommand := CCPath.
        LibPath := ''.
        SearchedLibraries := #().
        MakeCommand := 'make'.
    ].

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

    "Modified: / 09-08-2006 / 18:47:18 / fm"
    "Created: / 06-08-2011 / 19:47:47 / cg"
! !

!ParserFlags methodsFor:'accessing'!

allowAssignmentToBlockArgument
    ^ allowAssignmentToBlockArgument
!

allowAssignmentToBlockArgument:something
    allowAssignmentToBlockArgument := something.
!

allowAssignmentToMethodArgument
    ^ allowAssignmentToMethodArgument
!

allowAssignmentToMethodArgument:something
    allowAssignmentToMethodArgument := something.
!

allowAssignmentToPoolVariable
    ^ allowAssignmentToPoolVariable
!

allowAssignmentToPoolVariable:something
    allowAssignmentToPoolVariable := something.
! !

!ParserFlags methodsFor:'accessing-compilation control'!

allowExtensionsToPrivateClasses
    ^ allowExtensionsToPrivateClasses
!

allowExtensionsToPrivateClasses:aBoolean
    allowExtensionsToPrivateClasses := aBoolean
!

allowPossibleSTCCompilationProblems
    ^ allowPossibleSTCCompilationProblems

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

allowPossibleSTCCompilationProblems:aBoolean
    allowPossibleSTCCompilationProblems := aBoolean

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

arraysAreImmutable
    ^ arraysAreImmutable
!

arraysAreImmutable:aBoolean
    arraysAreImmutable := aBoolean.
!

flattenVisualWorksNamespaces
    ^ true
!

stringsAreImmutable
    ^ stringsAreImmutable
!

stringsAreImmutable:aBoolean
    stringsAreImmutable := aBoolean.
! !

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

ccCompilationOptions
    ^ ccCompilationOptions ? ''
!

ccCompilationOptions:something
    ccCompilationOptions := something.
!

ccPath
    ^ ccPath
!

ccPath:something
    ccPath := something.
!

implicitSelfSends
    ^ implicitSelfSends
!

implicitSelfSends:aBoolean
    implicitSelfSends := aBoolean.
!

libPath
    ^ libPath
!

libPath:aString
    libPath := aString
!

linkArgs
    ^ linkArgs
!

linkArgs:aString
    linkArgs := aString
!

linkCommand
    ^ linkCommand
!

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
!

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
!

stcModulePath:something
    stcModulePath := something.
!

stcPath
    ^ stcPath
!

stcPath:something
    stcPath := something.
! !

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

allowArrayIndexSyntaxExtension
    ^ allowArrayIndexSyntaxExtension
!

allowArrayIndexSyntaxExtension:aBoolean
    allowArrayIndexSyntaxExtension := aBoolean.
!

allowCaretAsBinop
    ^ allowCaretAsBinop
!

allowCaretAsBinop:aBoolean
    allowCaretAsBinop := aBoolean.
!

allowCharacterEscapes
    ^ allowCharacterEscapes
!

allowCharacterEscapes:aBoolean
    allowCharacterEscapes := aBoolean.
!

allowDollarInIdentifier
    ^ allowDollarInIdentifier
!

allowDollarInIdentifier:aBoolean
    allowDollarInIdentifier := aBoolean.
!

allowDolphinExtensions
    ^ allowDolphinExtensions
!

allowDolphinExtensions:aBoolean
    allowDolphinExtensions := aBoolean
!

allowDomainVariables
    ^ allowDomainVariables
!

allowDomainVariables:aBoolean
    allowDomainVariables := aBoolean.
!

allowEmptyStatements
    ^ allowEmptyStatements ? false

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

allowEmptyStatements:aBoolean
    allowEmptyStatements := aBoolean.

    "Created: / 20-11-2006 / 14:26:48 / cg"
!

allowExtendedBinarySelectors
    ^ allowExtendedBinarySelectors
!

allowExtendedBinarySelectors:aBoolean
    allowExtendedBinarySelectors := aBoolean.
!

allowExtendedSTXSyntax
    ^ allowExtendedSTXSyntax
!

allowExtendedSTXSyntax:something
    allowExtendedSTXSyntax := something.
!

allowFixedPointLiterals
    ^ allowFixedPointLiterals
!

allowFixedPointLiterals:something
    allowFixedPointLiterals := something.
!

allowFunctionCallSyntaxForBlockEvaluation
    ^ allowFunctionCallSyntaxForBlockEvaluation
!

allowFunctionCallSyntaxForBlockEvaluation:aBoolean
    allowFunctionCallSyntaxForBlockEvaluation := aBoolean.
!

allowHashAsBinarySelector
    ^ allowHashAsBinarySelector
!

allowLazyValueExtension
    ^ allowLazyValueExtension
!

allowLazyValueExtension:something
    allowLazyValueExtension := something.
!

allowLiteralNameSpaceSymbols
    ^ allowLiteralNameSpaceSymbols
!

allowLiteralNameSpaceSymbols:aBoolean
    allowLiteralNameSpaceSymbols := aBoolean
!

allowLocalVariableDeclarationWithInitializerExpression
    ^ allowLocalVariableDeclarationWithInitializerExpression
!

allowLocalVariableDeclarationWithInitializerExpression:aBoolean
    allowLocalVariableDeclarationWithInitializerExpression := aBoolean.
!

allowNationalCharactersInIdentifier
    ^ allowNationalCharactersInIdentifier
!

allowNationalCharactersInIdentifier:aBoolean
    allowNationalCharactersInIdentifier := aBoolean
!

allowOldStyleAssignment
    ^ allowOldStyleAssignment
!

allowOldStyleAssignment:aBoolean
    allowOldStyleAssignment := aBoolean
!

allowPeriodInSymbol
    ^ allowPeriodInSymbol
!

allowPeriodInSymbol:aBoolean
    allowPeriodInSymbol := aBoolean
!

allowQualifiedNames
    ^ allowQualifiedNames
!

allowQualifiedNames:aBoolean
    allowQualifiedNames := aBoolean.
!

allowReservedWordsAsSelectors
    ^ allowReservedWordsAsSelectors
!

allowReservedWordsAsSelectors:aBoolean
    allowReservedWordsAsSelectors := aBoolean.
!

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

    ^ allowSTVExtensions
!

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

    ^ allowSTVPrimitives
!

allowSTXEOLComments
    ^ allowSTXEOLComments
!

allowSTXEOLComments:aBoolean
    allowSTXEOLComments := aBoolean.

    "
     ParserFlags allowSTXEOLComments:false
     ParserFlags allowSTXEOLComments:true
    "
!

allowSTXFunctions
    ^ false

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

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

    allowSqueakExtensions := aBoolean
!

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

    ^ allowSqueakPrimitives
!

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

    allowSqueakPrimitives := aBoolean
!

allowStringEscapes
    ^ allowStringEscapes
!

allowStringEscapes:aBoolean
    allowStringEscapes := aBoolean.
!

allowUnderscoreInIdentifier
    ^ allowUnderscoreInIdentifier
!

allowUnderscoreInIdentifier:aBoolean
    allowUnderscoreInIdentifier := aBoolean
!

allowUnicodeCharacters
    ^ allowUnicodeCharacters
!

allowUnicodeCharacters:aBoolean
    allowUnicodeCharacters := aBoolean
!

allowUnicodeStrings
    ^ allowUnicodeStrings
!

allowUnicodeStrings:aBoolean
    allowUnicodeStrings := aBoolean
!

allowVariableReferences
    ^ allowVariableReferences
!

allowVariableReferences:aBoolean
    allowVariableReferences := aBoolean.
!

allowVisualAgeESSymbolLiterals
    ^ allowVisualAgeESSymbolLiterals
!

allowVisualAgeESSymbolLiterals:aBoolean
    allowVisualAgeESSymbolLiterals := aBoolean.
!

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

    ^ allowVisualAgePrimitives
!

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:48:30 / cg"
!

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

    ^ allowVisualWorksMethodAnnotations := aBoolean

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

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

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

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

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
    warnings := Warnings.
    warnUndeclared := WarnUndeclared.
    warnUnusedVars := WarnUnusedVars.
    warnST80Directives := WarnST80Directives.
    warnSTXSpecialComment := WarnSTXSpecials.
    warnSTXNameSpaceUse := WarnSTXSpecials.
    warnSTXHereExtensionUsed := WarnSTXSpecials.
    warnUnderscoreInIdentifier := WarnUnderscoreInIdentifier.
    warnDollarInIdentifier := WarnDollarInIdentifier.
    warnOldStyleAssignment := WarnOldStyleAssignment.
    warnCommonMistakes := WarnCommonMistakes.
    warnPossibleIncompatibilities := WarnPossibleIncompatibilities.
    warnAboutVariableNameConventions := WarnAboutVariableNameConventions.
    warnAboutWrongVariableNames := WarnAboutWrongVariableNames.
    warnAboutBadComments := WarnAboutBadComments.
    warnAboutReferenceToPrivateClass := WarnAboutReferenceToPrivateClass.
    warnHiddenVariables := WarnHiddenVariables.
    warnInconsistentReturnValues := WarnInconsistentReturnValues.
    warnAboutNonLowercaseLocalVariableNames := WarnAboutNonLowercaseLocalVariableNames.
    warnAboutShortLocalVariableNames := WarnAboutShortLocalVariableNames.
    warnAboutPossibleSTCCompilationProblems := WarnAboutPossibleSTCCompilationProblems.
    warnAboutPossiblyUnimplementedSelectors := WarnAboutPossiblyUnimplementedSelectors.
    warnAboutPeriodInSymbol := WarnAboutPeriodInSymbol.
    warnAboutUnknownCharacterEscapesInJavaScriptStringConstant := WarnAboutUnknownCharacterEscapesInJavaScriptStringConstant.
    warnPlausibilityChecks := WarnPlausibilityChecks.

    allowUnderscoreInIdentifier := AllowUnderscoreInIdentifier.
    allowDollarInIdentifier := AllowDollarInIdentifier.
    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.
    allowHashAsBinarySelector := AllowHashAsBinarySelector.
    allowSTXEOLComments := AllowSTXEOLComments.
    allowVisualWorksMethodAnnotations := AllowVisualWorksMethodAnnotations.
    allowPossibleSTCCompilationProblems := AllowPossibleSTCCompilationProblems.
    allowEmptyStatements := AllowEmptyStatements.
    allowPeriodInSymbol := AllowPeriodInSymbol.
    "/ these are only supported in the new compiler
    allowUnicodeStrings := AllowUnicodeStrings.
    allowUnicodeCharacters := AllowUnicodeCharacters.
    allowCharacterEscapes := AllowCharacterEscapes.
    allowStringEscapes := AllowStringEscapes.
    allowAssignmentToBlockArgument := AllowAssignmentToBlockArgument.
    allowAssignmentToMethodArgument := AllowAssignmentToMethodArgument.
    allowAssignmentToPoolVariable := AllowAssignmentToPoolVariable.

    arraysAreImmutable := ArraysAreImmutable ? true.
    stringsAreImmutable := StringsAreImmutable ? true.
    implicitSelfSends := ImplicitSelfSends ? 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: / 19-01-2012 / 10:39:22 / cg"
! !

!ParserFlags class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libcomp/ParserFlags.st,v 1.83 2012-01-31 11:12:30 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libcomp/ParserFlags.st,v 1.83 2012-01-31 11:12:30 cg Exp $'
! !

ParserFlags initialize!