compilerflags separated into ParserFlags.
authorClaus Gittinger <cg@exept.de>
Tue, 18 Oct 2005 16:26:36 +0200
changeset 1636 98afdcdacde8
parent 1635 7f71c88d1a6d
child 1637 993d58b1789b
compilerflags separated into ParserFlags.
Parser.st
Scanner.st
SyntaxHighlighter.st
--- a/Parser.st	Tue Oct 18 16:25:30 2005 +0200
+++ b/Parser.st	Tue Oct 18 16:26:36 2005 +0200
@@ -22,26 +22,18 @@
 		localVarDefPosition evalExitBlock selfNode superNode nilNode
 		hasPrimitiveCode hasNonOptionalPrimitiveCode primitiveNr
 		primitiveResource logged warnedUndefVars warnedUnknownNamespaces
-		warnSTXHereExtensionUsed warnUnusedVars correctedSource
-		foldConstants lineNumberInfo currentNamespace
-		currentUsedNamespaces warnUndeclared methodNode
-		alreadyWarnedClassInstVarRefs localBlockVarDefPosition
-		endOfSelectorPosition beginOfBodyPosition startOfBlockPosition
-		primitiveContextInfo usedLocalVars modifiedLocalVars
-		alreadyWarnedUninitializedVars
+		correctedSource foldConstants lineNumberInfo currentNamespace
+		currentUsedNamespaces methodNode alreadyWarnedClassInstVarRefs
+		localBlockVarDefPosition endOfSelectorPosition
+		beginOfBodyPosition startOfBlockPosition primitiveContextInfo
+		usedLocalVars modifiedLocalVars alreadyWarnedUninitializedVars
 		alreadyWarnedUnimplementedSelectors returnedValues currentPackage
-		doItTemporaries inFunctionCallArgument implicitSelfSends
-		arraysAreImmutable stringsAreImmutable'
+		doItTemporaries inFunctionCallArgument
+		didWarnAboutSTXNameSpaceUse didWarnAboutSTXHereExtensionUsed'
 	classVariableNames:'PrevClass PrevInstVarNames PrevClassVarNames
-		PrevClassInstVarNames LazyCompilation ArraysAreImmutable
-		ImplicitSelfSends WarnST80Directives WarnUnusedVars FoldConstants
-		LineNumberInfo SuppressDoItCompilation StringsAreImmutable
-		ParseErrorSignal RestartCompilationSignal
-		AllowFunctionCallSyntaxForBlockEvaluation AllowLazyValueExtension
-		AllowVariableReferences AllowReservedWordsAsSelectors
-		AllowLocalVariableDeclarationWithInitializerExpression
-		AllowArrayIndexSyntaxExtension AllowDomainVariables
-		WarnAboutWrongVariableNames WarnAboutVariableNameConventions'
+		PrevClassInstVarNames LazyCompilation FoldConstants
+		LineNumberInfo SuppressDoItCompilation ParseErrorSignal
+		RestartCompilationSignal'
 	poolDictionaries:''
 	category:'System-Compiler'
 !
@@ -373,14 +365,7 @@
 
 initialize
     LazyCompilation := false.      "/ usually set to true in your .rc file
-    ArraysAreImmutable := false.   "/ no longer care for ST-80 compatibility
-    StringsAreImmutable := false.  "/ no longer care for ST-80 compatibility
-
-    ImplicitSelfSends := false.
-    WarnST80Directives := false.
-    WarnUnusedVars := true.
-    WarnAboutWrongVariableNames := true.
-    WarnAboutVariableNameConventions := true.
+
     FoldConstants := #level1.
     LineNumberInfo := false.
 
@@ -405,16 +390,70 @@
 
 !Parser class methodsFor:'controlling compilation'!
 
+allowArrayIndexSyntaxExtension
+    "experimental"
+
+    ^ ParserFlags allowArrayIndexSyntaxExtension
+!
+
+allowArrayIndexSyntaxExtension:aBoolean
+    "experimental"
+
+    ParserFlags allowArrayIndexSyntaxExtension:aBoolean.
+
+    "
+     self allowArrayIndexSyntaxExtension:true
+     self allowArrayIndexSyntaxExtension:false
+    "
+!
+
+allowFunctionCallSyntaxForBlockEvaluation
+    "experimental"
+
+    ^ ParserFlags allowFunctionCallSyntaxForBlockEvaluation
+!
+
+allowFunctionCallSyntaxForBlockEvaluation:aBoolean
+    "experimental"
+
+    ParserFlags allowFunctionCallSyntaxForBlockEvaluation:aBoolean.
+
+    "
+     self allowFunctionCallSyntaxForBlockEvaluation:true
+     self allowFunctionCallSyntaxForBlockEvaluation:false
+    "
+!
+
+allowReservedWordsAsSelectors
+    "return true, if self, super, thisContext, nil, true and false are to be allowed
+     as unary message selectors."
+
+    ^ ParserFlags allowReservedWordsAsSelectors
+!
+
+allowReservedWordsAsSelectors:aBoolean
+    "enable/disable, if self, super, thisContext, nil, true and false are to be allowed
+     as unary message selectors."
+
+    ParserFlags allowReservedWordsAsSelectors:aBoolean.
+    self setupActions
+
+    "
+     self allowReservedWordsAsSelectors:true
+     self allowReservedWordsAsSelectors:false
+    "
+!
+
 arraysAreImmutable
     "return true if arrays are immutable literals"
 
-    ^ ArraysAreImmutable
+    ^ ParserFlags arraysAreImmutable
 !
 
 arraysAreImmutable:aBoolean
     "turn on/off immutable array literals - default is false for ST-80 compatibilty."
 
-    ArraysAreImmutable := aBoolean.
+    ParserFlags arraysAreImmutable:aBoolean.
 
     "
      can be added to your private.rc file:
@@ -474,17 +513,17 @@
      lowercase first character are to be turned
      into implicit self sends"
 
-    ^ ImplicitSelfSends
+    ^ ParserFlags implicitSelfSends
 !
 
 implicitSelfSends:aBoolean
     "turn on/off implicit self sends"
 
-    ImplicitSelfSends := aBoolean
+    ParserFlags implicitSelfSends:aBoolean
 
     "
-     Compiler implicitSelfSends:true
-     Compiler implicitSelfSends:false 
+     ParserFlags implicitSelfSends:true
+     ParserFlags implicitSelfSends:false 
     "
 !
 
@@ -499,7 +538,7 @@
 stringsAreImmutable
     "return true if strings are immutable literals"
 
-    ^ StringsAreImmutable
+    ^ ParserFlags stringsAreImmutable
 
     "Created: / 3.8.1998 / 14:53:25 / cg"
 !
@@ -507,13 +546,13 @@
 stringsAreImmutable:aBoolean
     "turn on/off immutable string literals - default is false for ST-80 compatibilty."
 
-    StringsAreImmutable := aBoolean.
+    ParserFlags stringsAreImmutable:aBoolean.
 
     "
      can be added to your private.rc file:
 
-     Compiler stringsAreImmutable:true     
-     Compiler stringsAreImmutable:false      
+     ParserFlags stringsAreImmutable:true     
+     ParserFlags stringsAreImmutable:false      
     "
 
     "Created: / 3.8.1998 / 14:53:28 / cg"
@@ -522,78 +561,41 @@
 warnAboutVariableNameConventions 
     "controls generation of warning messages about wrong variable names"
     
-    ^ WarnAboutVariableNameConventions
+    ^ ParserFlags warnAboutVariableNameConventions
 !
 
 warnAboutVariableNameConventions:aBoolean 
     "controls generation of warning messages about wrong variable names"
     
-    WarnAboutVariableNameConventions := aBoolean
+    ParserFlags warnAboutVariableNameConventions:aBoolean
 !
 
 warnAboutWrongVariableNames
     "controls generation of warning messages about wrong variable names"
     
-    ^ WarnAboutWrongVariableNames
+    ^ ParserFlags warnAboutWrongVariableNames
 !
 
 warnAboutWrongVariableNames:aBoolean
     "controls generation of warning messages about wrong variable names"
     
-    WarnAboutWrongVariableNames := aBoolean
+    ParserFlags warnAboutWrongVariableNames:aBoolean
 !
 
 warnUnusedVars
     "controls generation of warning messages about unued method variables"
 
-    ^ WarnUnusedVars
+    ^ ParserFlags warnUnusedVars
 !
 
 warnUnusedVars:aBoolean
     "controls generation of warning messages about unued method variables"
 
-    WarnUnusedVars := aBoolean
+    ParserFlags warnUnusedVars:aBoolean
 ! !
 
 !Parser class methodsFor:'defaults'!
 
-allowArrayIndexSyntaxExtension
-    "experimental"
-
-    ^ AllowArrayIndexSyntaxExtension ? false
-!
-
-allowArrayIndexSyntaxExtension:aBoolean
-    "experimental"
-
-    AllowArrayIndexSyntaxExtension := aBoolean.
-
-    "
-     self allowArrayIndexSyntaxExtension:true
-     self allowArrayIndexSyntaxExtension: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 setupActions
-
-    "
-     self allowReservedWordsAsSelectors:true
-     self allowReservedWordsAsSelectors:false
-    "
-!
-
 maxLineNumber
     "return the maximum lineNumber that is possibly
      encoded in a methods byteCode debugging information.
@@ -1921,10 +1923,14 @@
     "Modified: 8.11.1996 / 13:45:35 / cg"
 !
 
+implicitSelfSends
+    ^ parserFlags implicitSelfSends
+!
+
 implicitSelfSends:aBoolean
     "turn on/off implicit self sends"
 
-    implicitSelfSends := aBoolean
+    parserFlags implicitSelfSends:aBoolean
 !
 
 primitiveNumber
@@ -1979,9 +1985,11 @@
 !
 
 warnSTXHereExtensionUsed
-    "return the value of the instance variable 'warnSTXHereExtensionUsed' (automatically generated)"
-
-    ^ warnSTXHereExtensionUsed
+    ^ parserFlags warnSTXHereExtensionUsed
+!
+
+warnSTXHereExtensionUsed:aBoolean
+    parserFlags warnSTXHereExtensionUsed:aBoolean
 ! !
 
 !Parser methodsFor:'dummy-syntax detection'!
@@ -2323,10 +2331,10 @@
 !
 
 checkLocalVariableNameConventionsFor:aVariableName 
-    WarnAboutVariableNameConventions == true ifTrue:[
+    parserFlags warnAboutVariableNameConventions == true ifTrue:[
         self checkForLowercaseVariableName:aVariableName.
     ].
-    WarnAboutWrongVariableNames == true ifTrue:[
+    parserFlags warnAboutWrongVariableNames == true ifTrue:[
         self checkForProperUseOfArticleInVariableName:aVariableName.
     ].
 !
@@ -3476,7 +3484,7 @@
         ^ doCorrect
     ].
 
-    warnUndeclared ifFalse:[^ false].
+    parserFlags warnUndeclared ifFalse:[^ false].
     ignoreWarnings ifTrue:[^ false].
 
     "
@@ -3526,12 +3534,45 @@
     "Modified: 7.9.1997 / 02:14:36 / cg"
 !
 
+warnSTXHereExtensionUsedAt:position
+    ignoreWarnings ifFalse:[
+        didWarnAboutSTXHereExtensionUsed ifFalse:[
+            parserFlags warnSTXHereExtensionUsed ifTrue:[
+                self warning:'here-sends are a nonstandard feature of ST/X' 
+                     position:position to:position+3.
+                "
+                 only warn once
+                "
+                didWarnAboutSTXHereExtensionUsed := true
+            ].
+        ].
+    ].
+!
+
+warnSTXNameSpaceUseAt:position
+    ignoreWarnings ifFalse:[
+        didWarnAboutSTXNameSpaceUse ifFalse:[
+            parserFlags warnSTXNameSpaceUse ifTrue:[
+                self warning:'nameSpaces are a nonstandard feature of ST/X' 
+                     doNotShowAgainAction:[ ParserFlags warnSTXSpecials:false ]
+                     position:position to:(source position1Based).
+                "
+                 only warn once
+                "
+                didWarnAboutSTXNameSpaceUse := false
+            ]
+        ]
+    ].
+!
+
 warnUnused:aNameCollection
     "report an unused method variable"
 
     |s msg answer|
 
-    (ignoreErrors not and:[ignoreWarnings not and:[warnUnusedVars]]) ifTrue:[
+    (ignoreErrors not 
+    and:[ignoreWarnings not 
+    and:[parserFlags warnUnusedVars]]) ifTrue:[
         s := '' writeStream.
         s nextPutAll:'Unused method variable(s): '.
         aNameCollection asSortedCollection do:[:name|
@@ -3871,14 +3912,14 @@
             ].
             self nextToken.
 
-            AllowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
+            parserFlags allowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
                 ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
                     self nextToken.
                     "/ Q: should we allow literals only, or arbitrary expressions ?
                     self halt:'unimplemented feature'.
                 ]
             ].
-            AllowDomainVariables == true ifTrue:[
+            parserFlags allowDomainVariables == true ifTrue:[
                 (tokenType == $() ifTrue:[
                     self variableTypeDeclarationFor:var.
                 ].
@@ -4276,14 +4317,14 @@
                 lastDirective := nil.
             ].
 
-            AllowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
+            parserFlags allowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
                 ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
                     self nextToken.
                     "/ Q: should we allow literals only, or arbitrary expressions ?
                     self halt:'unimplemented feature'.
                 ]
             ].
-            AllowDomainVariables == true ifTrue:[
+            parserFlags allowDomainVariables == true ifTrue:[
                 (tokenType == $() ifTrue:[
                     self variableTypeDeclarationFor:var.
                 ].
@@ -4307,7 +4348,7 @@
         self nextToken
     ].
 
-    allowSqueakExtensions ifTrue:[
+    parserFlags allowSqueakExtensions ifTrue:[
         "/ allow for primitiveSpec after local-var decl.
 
         ((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
@@ -4463,7 +4504,7 @@
     ].
 
     (tokenType == $.) ifTrue:[
-        allowSqueakExtensions == true ifTrue:[
+        parserFlags allowSqueakExtensions == true ifTrue:[
             "/ allow empty statement
             ^ StatementNode expression:nil.
         ].
@@ -4672,7 +4713,7 @@
     ].
     arr := Array withAll:elements.
 
-    arraysAreImmutable ifTrue:[
+    parserFlags arraysAreImmutable ifTrue:[
         ^ self makeImmutableArray:arr
     ].
     ^ arr
@@ -4691,7 +4732,7 @@
         ^ tokenValue
     ].
     (tokenType == #String) ifTrue:[
-        stringsAreImmutable ifTrue:[^ self makeImmutableString:tokenValue].
+        parserFlags stringsAreImmutable ifTrue:[^ self makeImmutableString:tokenValue].
         ^ tokenValue
     ].
     (tokenType == #Character) ifTrue:[
@@ -4782,7 +4823,7 @@
 
     receiver := self functionCallExpression.
     tokenType == $[ ifFalse:[^ receiver].
-    AllowArrayIndexSyntaxExtension == true ifFalse:[^ receiver.].
+    parserFlags allowArrayIndexSyntaxExtension == true ifFalse:[^ receiver.].
     (receiver == #Error) ifTrue:[^ #Error].
 
     selectorStream := WriteStream on: (String new: 32).
@@ -5192,14 +5233,19 @@
 !
 
 functionCallExpression
-    "parse a functionCall; this is an st/x extension.
-     foo(x) is syntactic sugar for foo value:x"
+    "parse a functionCall; 
+     this is an st/x extension.
+        foo(x) 
+     is syntactic sugar for 
+        foo value:x
+    "
 
     |receiver numArgs argList evalSelectors evalSelector|
 
     receiver := self primary.
     tokenType == $( ifFalse:[^ receiver].
-    AllowFunctionCallSyntaxForBlockEvaluation == true ifFalse:[^ receiver.].
+    parserFlags allowFunctionCallSyntaxForBlockEvaluation ifFalse:[^ receiver.].
+
     (receiver == #Error) ifTrue:[^ #Error].
 
     receiver isVariable ifFalse:[
@@ -5241,7 +5287,7 @@
             args:(self genMakeArrayWith:argList).
 
     "
-     AllowFunctionCallSyntaxForBlockEvaluation := true.
+     Parser allowFunctionCallSyntaxForBlockEvaluation:true.
     "
 
     "
@@ -5329,7 +5375,7 @@
     tokenType == #Identifier ifTrue:[^true].
     tokenType == #Here ifTrue:[^true].
 
-    AllowReservedWordsAsSelectors == true ifTrue:[
+    parserFlags allowReservedWordsAsSelectors == true ifTrue:[
         tokenType == #Self ifTrue:[^true].
         tokenType == #Nil ifTrue:[^true].
         tokenType == #True ifTrue:[^true].
@@ -5340,8 +5386,11 @@
     ^ false
 
     "
-     AllowReservedWordsAsSelectors := true
-     AllowReservedWordsAsSelectors := false
+     ParserFlags allowReservedWordsAsSelectors:true.
+     1234 self.
+
+     ParserFlags allowReservedWordsAsSelectors:false
+     1234 self.
     "
 
     "
@@ -5523,15 +5572,8 @@
         "
         tokenName = 'here' ifTrue:[
             (self variableOrError:tokenName) == #Error ifTrue:[
+                self warnSTXHereExtensionUsedAt:pos.
                 tokenType := #Here.
-                warnSTXHereExtensionUsed ifTrue:[
-                    self warning:'here-sends are a nonstandard feature of ST/X' 
-                         position:pos to:pos+3.
-                    "
-                     only warn once
-                    "
-                    warnSTXHereExtensionUsed := false
-                ].
                 ^ self primary_here.
             ]
         ].
@@ -5547,7 +5589,7 @@
     ].
 
     (tokenType == #FixedPoint) ifTrue:[
-        AllowFixedPointLiterals == true ifFalse:[
+        parserFlags allowFixedPointLiterals == true ifFalse:[
             self parseError:'non-Standard literal: FixedPoint. Please enable in settings.' position:pos to:tokenPosition.
             ^ #Error
         ].
@@ -5618,7 +5660,7 @@
     ].
 
     "/ EXPERIMENTAL - may be in next release
-    AllowVariableReferences == true ifTrue:[
+    parserFlags allowVariableReferences == true ifTrue:[
         ((tokenType == #BinaryOperator) and:[token = '&']) ifTrue:[
             self nextToken.
             node := self primary_identifier.
@@ -5628,7 +5670,7 @@
     ].
 
     (tokenType == ${ ) ifTrue:[
-        allowSqueakExtensions == true ifFalse:[
+        parserFlags allowSqueakExtensions == true ifFalse:[
             self parseError:'non-Standard Squeak extension: Brace Computed Array. Enable in settings.' position:pos to:tokenPosition.
             errorFlag := false.
         ].
@@ -5646,7 +5688,7 @@
     tokenType == #HashHashLeftParen ifTrue:[
 self halt.
         self nextToken.
-        AllowDolphinExtensions == true ifFalse:[
+        parserFlags allowDolphinExtensions == true ifFalse:[
             self parseError:'non-Standard Dolphin extension: ##(..). Enable in settings.' position:pos to:tokenPosition.
             ^ #Error
         ].
@@ -5654,7 +5696,7 @@
     ].
     tokenType == #ExclaLeftBrack ifTrue:[
         self nextToken.
-        AllowLazyValueExtension == true ifFalse:[
+        parserFlags allowLazyValueExtension == true ifFalse:[
             self parseError:'non-Standard LazyValue extension. Enable in classVariable.' position:pos to:tokenPosition.
             ^ #Error
         ].
@@ -5667,7 +5709,7 @@
         ^ self primary_simpleLiteral.
     ].
 
-    allowSqueakExtensions == true ifTrue:[
+    parserFlags allowSqueakExtensions == true ifTrue:[
         ((tokenType == #BinaryOperator) and:[token = '#']) ifTrue:[
             self nextToken.
             (tokenType == $( ) ifFalse:[
@@ -5698,7 +5740,7 @@
             self parseError:'number expected after sign.' position:pos to:tokenPosition.
             ^ #Error.
         ].
-        allowSqueakExtensions == true ifFalse:[
+        parserFlags allowSqueakExtensions == true ifFalse:[
             self parseError:'non-Standard Squeak extension: space between sign and number. Enable in settings.' position:pos to:tokenPosition.
             errorFlag := false.
         ].
@@ -5922,17 +5964,7 @@
 
             self nextToken.
             (tokenType == #Identifier) ifTrue:[
-                ignoreWarnings ifFalse:[
-                    warnSTXNameSpaceUse ifTrue:[
-                        self warning:'nameSpaces are a nonstandard feature of ST/X' 
-                             doNotShowAgainAction:[ WarnSTXSpecials := false ]
-                             position:pos1 to:(source position1Based).
-                        "
-                         only warn once
-                        "
-                        warnSTXNameSpaceUse := false
-                    ]
-                ].
+                self warnSTXNameSpaceUseAt:pos1.
                 varName := tokenName.
 
                 globlName := (nameSpace , '::' , varName).
@@ -6007,7 +6039,7 @@
     "/ assignment...
 
     "/ careful: it could already be an implicit self send
-    implicitSelfSends ifTrue:[
+    parserFlags implicitSelfSends ifTrue:[
         var isMessage ifTrue:[
             self nextToken.
             expr := self expression.
@@ -6034,7 +6066,7 @@
             "/ (not really a beginners bug, but may happen as a typo or missing local variable;
             "/  and is hard to track down later)
 
-            warnCommonMistakes ifTrue:[
+            parserFlags warnCommonMistakes ifTrue:[
                 classToCompileFor isMeta ifTrue:[
                     (classToCompileFor isSubclassOf:Class) ifTrue:[
                         (Class allInstVarNames includes:(var name)) ifTrue:[
@@ -6110,7 +6142,7 @@
     self isSyntaxHighlighter ifTrue:[
         (expr == #Error) ifTrue:[^ #Error].
     ] ifFalse:[
-        warnCommonMistakes ifTrue:[
+        parserFlags warnCommonMistakes ifTrue:[
             (expr ~~ #Error and:[expr isSuper]) ifTrue:[
                 self warning:'followup messageSends to "' , var name , '" will have normal send semantics\(i.e. NO super- or here-sends). Use self to avoid confusion.' withCRs position:pos1 to:pos2.
             ].
@@ -6197,7 +6229,7 @@
     "/ ImmutableStrings are experimental
     "/
     ((tokenType == #String)
-    and:[(stringsAreImmutable == true)]) ifTrue:[
+    and:[(parserFlags stringsAreImmutable)]) ifTrue:[
         token := tokenValue := self makeImmutableString:tokenValue.
     ].
     (tokenType == #Symbol) ifTrue:[
@@ -6439,7 +6471,7 @@
 
         self nextToken.
         tokenType == $( ifTrue:[
-            allowSqueakExtensions == true ifTrue:[
+            parserFlags allowSqueakExtensions == true ifTrue:[
                 "/ croquet/squeak extension - c/java-style arguments
                 arguments := self functionCallArgList.
                 "/ synthetic selector: foo[:[with:[with:[...]]]]
@@ -6522,7 +6554,7 @@
         self rememberGlobalUsed:tokenName.
     ] ifTrue:[
         tokenName first isLowercase ifTrue:[
-            implicitSelfSends ifTrue:[
+            parserFlags implicitSelfSends ifTrue:[
                 ^ UnaryNode receiver:(self selfNode) selector:('__' , tokenName) asSymbol.
             ].
             ^ #Error
@@ -6989,7 +7021,7 @@
 
         primNr notNil ifTrue:[
             primNr < 0 ifTrue:[
-                WarnST80Directives == true ifTrue:[
+                parserFlags warnST80Directives == true ifTrue:[
                     wmsg := 'ST-80/Squeak directive ignored'.
                 ].
             ] ifFalse:[
@@ -7053,7 +7085,7 @@
 
     self nextToken.
     (tokenType == #Integer) ifFalse:[
-        allowSqueakExtensions ifTrue:[
+        parserFlags allowSqueakExtensions ifTrue:[
             (tokenType == #String) ifFalse:[
                 self parseError:'primitive number or name expected'.
                 ^ #Error
@@ -7663,8 +7695,12 @@
 
 !Parser methodsFor:'setup'!
 
+arraysAreImmutable
+    ^ parserFlags arraysAreImmutable
+!
+
 arraysAreImmutable:aBoolean
-    arraysAreImmutable := aBoolean.
+    parserFlags arraysAreImmutable:aBoolean.
 !
 
 classToCompileFor
@@ -7686,27 +7722,17 @@
     super initialize.
 
     hasPrimitiveCode := hasNonOptionalPrimitiveCode := false.
-    warnSTXHereExtensionUsed := WarnSTXSpecials.
     usesSuper := false.
     parseForCode := false.
     foldConstants := FoldConstants.
     lineNumberInfo := LineNumberInfo.
-    warnUndeclared := true.
-    warnUnusedVars := WarnUnusedVars.
-    implicitSelfSends := ImplicitSelfSends ? false.
-    arraysAreImmutable := ArraysAreImmutable ? true.
-    stringsAreImmutable := StringsAreImmutable ? true.
+
+    didWarnAboutSTXNameSpaceUse := false.
+    didWarnAboutSTXHereExtensionUsed := false.
 
     "Modified: 7.9.1997 / 02:04:34 / cg"
 !
 
-initializeFlagsFrom:aParser
-    "initialize flags from another scanner"
-
-    super initializeFlagsFrom:aParser.
-    warnSTXHereExtensionUsed := aParser warnSTXHereExtensionUsed.
-!
-
 parseForCode
     "turns off certain statistics (keeping referenced variables, modified vars etc.)
      Use this when parsing for compilation or evaluation"
@@ -7743,18 +7769,32 @@
     ]
 !
 
+stringsAreImmutable
+    ^ parserFlags stringsAreImmutable.
+!
+
 stringsAreImmutable:aBoolean
-    stringsAreImmutable := aBoolean.
+    parserFlags stringsAreImmutable:aBoolean.
+!
+
+warnUndeclared
+    ^ parserFlags warnUndeclared
+
+    "Created: 7.9.1997 / 02:05:00 / cg"
 !
 
 warnUndeclared:aBoolean
-    warnUndeclared := aBoolean.
+    parserFlags warnUndeclared:aBoolean.
 
     "Created: 7.9.1997 / 02:05:00 / cg"
 !
 
+warnUnusedVars
+    ^ parserFlags warnUnusedVars
+!
+
 warnUnusedVars:aBoolean
-    warnUnusedVars := aBoolean.
+    parserFlags warnUnusedVars:aBoolean.
 ! !
 
 !Parser methodsFor:'statistic'!
@@ -7941,7 +7981,7 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.467 2005-10-05 08:58:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.468 2005-10-18 14:26:30 cg Exp $'
 ! !
 
 Parser initialize!
--- a/Scanner.st	Tue Oct 18 16:25:30 2005 +0200
+++ b/Scanner.st	Tue Oct 18 16:26:36 2005 +0200
@@ -16,22 +16,11 @@
 	instanceVariableNames:'typeArray actionArray source lineNr token tokenType tokenPosition
 		tokenValue tokenName tokenLineNr hereChar peekChar peekChar2
 		requestor exitBlock errorFlag ignoreErrors ignoreWarnings
-		saveComments currentComments collectedSource
-		allowUnderscoreInIdentifier allowDollarInIdentifier
-		allowOldStyleAssignment scanColonAsKeyword allowSqueakExtensions
-		warnSTXSpecialComment warnUnderscoreInIdentifier
-		warnOldStyleAssignment warnCommonMistakes outStream outCol
-		warnSTXNameSpaceUse warnPossibleIncompatibilities
-		warnDollarInIdentifier inArrayLiteral
-		allowLiteralNameSpaceSymbols lastDirective'
-	classVariableNames:'TypeArray ActionArray Warnings EmptySourceNotificationSignal
-		WarnSTXSpecials WarnOldStyleAssignment WarnUnderscoreInIdentifier
-		WarnCommonMistakes WarnPossibleIncompatibilities
-		WarnDollarInIdentifier AllowUnderscoreInIdentifier
-		AllowDollarInIdentifier AllowSqueakExtensions AllowQualifiedNames
-		AllowDolphinExtensions AllowOldStyleAssignment
-		AllowExtendedBinarySelectors AllowExtendedSTXSyntax
-		AllowFixedPointLiterals AllowLiteralNameSpaceSymbols'
+		saveComments currentComments collectedSource scanColonAsKeyword
+		outStream outCol inArrayLiteral lastDirective parserFlags
+		didWarnAboutSTXSpecialComment didWarnAboutUnderscoreInIdentifier
+		didWarnAboutOldStyleAssignment didWarnAboutDollarInIdentifier'
+	classVariableNames:'TypeArray ActionArray Warnings EmptySourceNotificationSignal'
 	poolDictionaries:''
 	category:'System-Compiler'
 !
@@ -142,23 +131,22 @@
 !Scanner class methodsFor:'initialization'!
 
 binarySelectorCharacters
-    "return a collection of characters which are allowed in
-     binary selectors"
+    "return a collection of characters which are allowed in binary selectors"
+
+    ^ #( $& $- $+ $= $* $/ $\ $< $> $~ $@ $, $? $!! $| $% $#).
+!
+
+extendedBinarySelectorCharacters
+    "return a collection of characters which are optionally allowed in binary selectors"
 
     |characters|
 
-    characters := #( $& $- $+ $= $* $/ $\ $< $> $~ $@ $, $? $!! $| $% $#).
-    AllowExtendedBinarySelectors ifTrue:[
-        characters := characters asOrderedCollection.
-        characters add:(Character value:16rB1).  "/ plus-minus
-        characters add:(Character value:16rD7).  "/ times
-        characters add:(Character value:16rB7).  "/ centered dot
-        characters add:(Character value:16rF7).  "/ divide
-    ].
+    characters := OrderedCollection new.
+    characters add:(Character value:16rB1).  "/ plus-minus
+    characters add:(Character value:16rD7).  "/ times
+    characters add:(Character value:16rB7).  "/ centered dot
+    characters add:(Character value:16rF7).  "/ divide
     ^ characters
-
-    "Created: / 4.1.1997 / 14:13:24 / cg"
-    "Modified: / 27.2.1998 / 02:01:28 / cg"
 !
 
 setupActions
@@ -183,6 +171,11 @@
         TypeArray at:(binop codePoint) put:#special.
         ActionArray at:(binop codePoint) put:block
     ].
+    block := [:s :char | s nextExtendedSpecial].
+    self extendedBinarySelectorCharacters do:[:binop |
+        TypeArray at:(binop codePoint) put:#extendedSpecial.
+        ActionArray at:(binop codePoint) put:block
+    ].
 
     "/ that one is a special case (both binarySelector AND syntax).
     TypeArray at:($| codePoint) put:nil.
@@ -265,20 +258,6 @@
     ].
 
     Warnings := true.
-    WarnSTXSpecials := false.
-    WarnUnderscoreInIdentifier := false.
-    WarnDollarInIdentifier := true.
-    WarnOldStyleAssignment := true.
-    WarnCommonMistakes := true.
-    WarnPossibleIncompatibilities := false.
-
-    AllowUnderscoreInIdentifier := true.        "/ underscores in identifiers
-    AllowDollarInIdentifier := false.           "/ st80-vms dollars in identifiers
-    AllowOldStyleAssignment := true.            "/ st80 underscore as assignment
-    AllowSqueakExtensions := false.             "/ squeak computed array
-    AllowQualifiedNames := false.               "/ vw3 qualified names
-    AllowExtendedBinarySelectors := false.      "/ vw5.4 extended binary selectors
-    AllowLiteralNameSpaceSymbols := true.       "/ st/x literal nameSpace-symbols (#foo::bar)
 
     "
      self initialize
@@ -293,7 +272,7 @@
     "return true, if $-characters are allowed in identifiers.
      Notice, that dollars are NEVER allowed as the first character in an identifier."
 
-    ^ AllowDollarInIdentifier
+    ^ ParserFlags allowDollarInIdentifier
 
     "Created: 7.9.1997 / 01:32:18 / cg"
     "Modified: 7.9.1997 / 01:39:44 / cg"
@@ -310,24 +289,24 @@
      before filing them in; i.e.:
         Compiler allowDollarInIdentifiers:false"
 
-    AllowDollarInIdentifier := aBoolean.
+    ParserFlags 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
+    "return true, if ##(..) computed literal Arrays are allowed"
+
+    ^ ParserFlags allowDolphinExtensions
 !
 
 allowDolphinExtensions:aBoolean
-    "this allows turning on/off support for computed arrays ##(..) as in dolphin.
+    "this allows turning on/off support for computed literal Arrays ##(..) as in dolphin.
      If you want to fileIn Dolphin classes, enable this with:
         Compiler allowDolphinComputedArrays:true"
 
-    AllowDolphinExtensions := aBoolean.
+    ParserFlags allowDolphinExtensions:aBoolean.
 
     "
      self allowDolphinExtensions:true
@@ -344,20 +323,20 @@
 allowOldStyleAssignment
     "return true, if underscore-assignment (pre ST-80v4 syntax) are to be allowed"
 
-    ^ AllowOldStyleAssignment
+    ^ ParserFlags 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
+    ParserFlags allowOldStyleAssignment:aBoolean
 !
 
 allowQualifiedNames
     "return true, if #{..} qualified names are allowed"
 
-    ^ AllowQualifiedNames
+    ^ ParserFlags allowQualifiedNames
 !
 
 allowQualifiedNames:aBoolean
@@ -368,7 +347,7 @@
      (they are parsed, but treated like regular globals)
     "
 
-    AllowQualifiedNames := aBoolean.
+    ParserFlags allowQualifiedNames:aBoolean.
 
     "
      self allowQualifiedNames:true
@@ -382,7 +361,7 @@
         c/java style arguments in message sends rec foo(arg1, ... argN)
      is enabled."
 
-    ^ AllowSqueakExtensions
+    ^ ParserFlags allowSqueakExtensions
 !
 
 allowSqueakExtensions:aBoolean
@@ -393,7 +372,7 @@
      If you want to fileIn Squeak classes, enable this with:
         Compiler allowSqueakComputedArrays:true"
 
-    AllowSqueakExtensions := aBoolean.
+    ParserFlags allowSqueakExtensions:aBoolean.
 
     "
      self allowSqueakExtensions:true
@@ -404,7 +383,7 @@
 allowUnderscoreInIdentifier
     "return true, if underscores are allowed in identifiers"
 
-    ^ AllowUnderscoreInIdentifier
+    ^ ParserFlags allowUnderscoreInIdentifier
 !
 
 allowUnderscoreInIdentifier:aBoolean
@@ -417,7 +396,7 @@
      turn them off with:
         Compiler allowUnderscoreInIdentifiers:false"
 
-    AllowUnderscoreInIdentifier := aBoolean.
+    ParserFlags allowUnderscoreInIdentifier:aBoolean.
 
     "Modified: 7.9.1997 / 01:35:19 / cg"
 !
@@ -425,7 +404,7 @@
 warnCommonMistakes
     "return true, if common beginners mistakes are to be warned about"
 
-    ^ Warnings and:[WarnCommonMistakes]
+    ^ Warnings and:[ParserFlags warnCommonMistakes]
 !
 
 warnCommonMistakes:aBoolean
@@ -438,13 +417,13 @@
         Compiler warnCommonMistakes:false
      in your 'private.rc' file"
 
-    WarnCommonMistakes := aBoolean
+    ParserFlags warnCommonMistakes:aBoolean
 !
 
 warnDollarInIdentifier
     "return true, if $-characters in identifiers are to be warned about"
 
-    ^ Warnings and:[WarnDollarInIdentifier]
+    ^ Warnings and:[ParserFlags warnDollarInIdentifier]
 
     "Created: 7.9.1997 / 01:36:17 / cg"
 !
@@ -460,7 +439,7 @@
         Compiler warnDollarInIdentifier:false
      in your 'private.rc' file"
 
-    WarnDollarInIdentifier := aBoolean
+    ParserFlags warnDollarInIdentifier:aBoolean
 
     "Created: 7.9.1997 / 01:37:42 / cg"
     "Modified: 7.9.1997 / 01:40:02 / cg"
@@ -469,7 +448,7 @@
 warnOldStyleAssignment
     "return true, if underscore-assignment (pre ST-80v4 syntax) are to be warned about"
 
-    ^ Warnings and:[WarnOldStyleAssignment]
+    ^ Warnings and:[ParserFlags warnOldStyleAssignment]
 !
 
 warnOldStyleAssignment:aBoolean
@@ -479,14 +458,14 @@
         Compiler warnOldStyleAssignment:false
      in your 'private.rc' file"
 
-    WarnOldStyleAssignment := aBoolean
+    ParserFlags warnOldStyleAssignment:aBoolean
 !
 
 warnPossibleIncompatibilities
     "return true, if possible incompatibilities (with other ST systems)
      are to be warned about"
 
-    ^ Warnings and:[WarnPossibleIncompatibilities]
+    ^ Warnings and:[ParserFlags warnPossibleIncompatibilities]
 
     "Modified: 23.5.1997 / 12:02:02 / cg"
 !
@@ -499,7 +478,7 @@
         Compiler warnPossibleIncompatibilities:false
      in your 'private.rc' file."
 
-    WarnPossibleIncompatibilities := aBoolean
+    ParserFlags warnPossibleIncompatibilities:aBoolean
 
     "Created: 23.5.1997 / 12:02:45 / cg"
 !
@@ -507,7 +486,7 @@
 warnSTXSpecials
     "return true, if ST/X specials are to be warned about"
 
-    ^ Warnings and:[WarnSTXSpecials]
+    ^ Warnings and:[ParserFlags warnSTXSpecials]
 !
 
 warnSTXSpecials:aBoolean
@@ -517,13 +496,13 @@
         Compiler warnSTXSpecials:false
      in your 'private.rc' file"
 
-    WarnSTXSpecials := aBoolean
+    ParserFlags warnSTXSpecials:aBoolean
 !
 
 warnUnderscoreInIdentifier
     "return true, if underscores in identifiers are to be warned about"
 
-    ^ Warnings and:[WarnUnderscoreInIdentifier]
+    ^ Warnings and:[ParserFlags warnUnderscoreInIdentifier]
 !
 
 warnUnderscoreInIdentifier:aBoolean
@@ -536,7 +515,7 @@
         Compiler warnUnderscoreInIdentifier:false
      in your 'private.rc' file"
 
-    WarnUnderscoreInIdentifier := aBoolean
+    ParserFlags warnUnderscoreInIdentifier:aBoolean
 
     "Modified: 7.9.1997 / 01:37:13 / cg"
 !
@@ -723,50 +702,32 @@
     ^ tokenValue
 
     "Created: / 21.12.2001 / 22:38:08 / cg"
-!
-
-warnDollarInIdentifier
-    "return the value of the instance variable 'warnDollarInIdentifier' (automatically generated)"
-
-    ^ warnDollarInIdentifier
-!
-
-warnPossibleIncompatibilities
-    "return the value of the instance variable 'warnPossibleIncompatibilities' (automatically generated)"
-
-    ^ warnPossibleIncompatibilities
-!
-
-warnSTXNameSpaceUse
-    "return the value of the instance variable 'warnSTXNameSpaceUse' (automatically generated)"
-
-    ^ warnSTXNameSpaceUse
 ! !
 
 !Scanner methodsFor:'accessing-flags'!
 
 allowDollarInIdentifier
-    ^ allowDollarInIdentifier
+    ^ parserFlags allowDollarInIdentifier
 !
 
 allowDollarInIdentifier:something
-    allowDollarInIdentifier := something.
+    parserFlags allowDollarInIdentifier:something
 !
 
 allowLiteralNameSpaceSymbols
-    ^ allowLiteralNameSpaceSymbols
+    ^ parserFlags allowLiteralNameSpaceSymbols
 !
 
 allowLiteralNameSpaceSymbols:aBoolean
-    allowLiteralNameSpaceSymbols := aBoolean
+    parserFlags allowLiteralNameSpaceSymbols:aBoolean
 !
 
 allowOldStyleAssignment
-    ^ allowOldStyleAssignment
+    ^ parserFlags allowOldStyleAssignment
 !
 
 allowOldStyleAssignment:aBoolean
-    allowOldStyleAssignment := aBoolean
+    parserFlags allowOldStyleAssignment:aBoolean
 !
 
 allowSqueakExtensions
@@ -775,7 +736,7 @@
         c/java style arguments in message sends rec foo(arg1, ... argN)
      is enabled."
 
-    ^ allowSqueakExtensions
+    ^ parserFlags allowSqueakExtensions
 !
 
 allowSqueakExtensions:aBoolean
@@ -784,35 +745,84 @@
         c/java style arguments in message sends rec foo(arg1, ... argN)
     "
 
-    allowSqueakExtensions := aBoolean
+    parserFlags allowSqueakExtensions:aBoolean
 !
 
 allowUnderscoreInIdentifier
-    ^ allowUnderscoreInIdentifier
+    ^ parserFlags allowUnderscoreInIdentifier
 !
 
 allowUnderscoreInIdentifier:aBoolean
-    allowUnderscoreInIdentifier := aBoolean
+    parserFlags allowUnderscoreInIdentifier:aBoolean
+!
+
+parserFlags
+    ^ parserFlags
+!
+
+parserFlags:aParserFlagsInstance
+    parserFlags := aParserFlagsInstance
 !
 
 scanColonAsKeyword
+    "/ not used here, but eases subclassing for other languages.
     ^ scanColonAsKeyword
 !
 
 warnCommonMistakes
-    ^ warnCommonMistakes
+    ^ parserFlags warnCommonMistakes
+!
+
+warnCommonMistakes:aBoolean
+    parserFlags warnCommonMistakes:aBoolean
+!
+
+warnDollarInIdentifier
+    ^ parserFlags warnDollarInIdentifier
+!
+
+warnDollarInIdentifier:aBoolean
+    parserFlags warnDollarInIdentifier:aBoolean
 !
 
 warnOldStyleAssignment
-    ^ warnOldStyleAssignment
+    ^ parserFlags warnOldStyleAssignment
+!
+
+warnOldStyleAssignment:aBoolean
+    parserFlags warnOldStyleAssignment:aBoolean
+!
+
+warnPossibleIncompatibilities
+    ^ parserFlags warnPossibleIncompatibilities
+!
+
+warnPossibleIncompatibilities:aBoolean
+    parserFlags warnPossibleIncompatibilities:aBoolean
+!
+
+warnSTXNameSpaceUse
+    ^ parserFlags warnSTXNameSpaceUse
+!
+
+warnSTXNameSpaceUse:aBoolean
+    parserFlags warnSTXNameSpaceUse:aBoolean
 !
 
 warnSTXSpecialComment
-    ^ warnSTXSpecialComment
+    ^ parserFlags warnSTXSpecialComment
+!
+
+warnSTXSpecialComment:aBoolean
+    parserFlags warnSTXSpecialComment:aBoolean
 !
 
 warnUnderscoreInIdentifier
-    ^ warnUnderscoreInIdentifier
+    ^ parserFlags warnUnderscoreInIdentifier
+!
+
+warnUnderscoreInIdentifier:aBoolean
+    parserFlags warnUnderscoreInIdentifier:aBoolean
 ! !
 
 !Scanner methodsFor:'directives'!
@@ -1294,7 +1304,7 @@
     "warn about a common beginners mistake"
 
     ignoreWarnings ifFalse:[
-        warnCommonMistakes ifTrue:[
+        parserFlags warnCommonMistakes ifTrue:[
             self 
                 warning:msg
                 position:pos1 to:pos2.
@@ -1309,14 +1319,16 @@
     "warn about $-character in an identifier"
 
     ignoreWarnings ifFalse:[
-        warnDollarInIdentifier ifTrue:[
-            self 
-                warning:'$-characters in identifiers/symbols are nonportable' 
-                position:position to:position.
-            "
-             only warn once (per method)
-            "
-            warnDollarInIdentifier := false
+        didWarnAboutDollarInIdentifier ifFalse:[
+            parserFlags warnDollarInIdentifier ifTrue:[
+                self 
+                    warning:'$-characters in identifiers/symbols are nonportable' 
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                didWarnAboutDollarInIdentifier := true
+            ]
         ]
     ]
 
@@ -1328,16 +1340,18 @@
     "warn about an oldStyle assignment"
 
     ignoreWarnings ifFalse:[
-        warnOldStyleAssignment ifTrue:[
-            self 
-                warning:'Old style assignment - please change to use '':='''
-                doNotShowAgainAction:[ WarnOldStyleAssignment := false ]
-                position:position to:position.
-                
-            "
-             only warn once (per method)
-            "
-            warnOldStyleAssignment := false
+        didWarnAboutOldStyleAssignment ifFalse:[
+            parserFlags warnOldStyleAssignment ifTrue:[
+                self 
+                    warning:'Old style assignment - please change to use '':='''
+                    doNotShowAgainAction:[ ParserFlags warnOldStyleAssignment:false ]
+                    position:position to:position.
+                    
+                "
+                 only warn once (per method)
+                "
+                didWarnAboutOldStyleAssignment := true
+            ]
         ]
     ]
 
@@ -1348,7 +1362,7 @@
     "warn about a possible incompatibility with other ST systems"
 
     ignoreWarnings ifFalse:[
-        warnPossibleIncompatibilities ifTrue:[
+        parserFlags  warnPossibleIncompatibilities ifTrue:[
             self 
                 warning:('Possible incompatibility.\\' , msg) withCRs
                 position:pos1 to:pos2.
@@ -1359,18 +1373,36 @@
     "Modified: 23.5.1997 / 12:22:37 / cg"
 !
 
+warnSTXSpecialCommentAt:position
+    ignoreWarnings ifFalse:[
+        didWarnAboutSTXSpecialComment ifFalse:[
+            parserFlags warnSTXSpecialComment ifTrue:[
+                self warning:'end-of-line comments are a nonstandard feature of ST/X' 
+                     doNotShowAgainAction:[ ParserFlags warnSTXSpecials:false ]
+                     position:position to:(source position1Based).
+                "
+                 only warn once
+                "
+                didWarnAboutSTXSpecialComment := true
+            ]
+        ]
+    ].
+!
+
 warnUnderscoreAt:position
     "warn about an underscore in an identifier"
 
     ignoreWarnings ifFalse:[
-        warnUnderscoreInIdentifier ifTrue:[
-            self 
-                warning:'underscores in identifiers/symbols are nonportable' 
-                position:position to:position.
-            "
-             only warn once (per method)
-            "
-            warnUnderscoreInIdentifier := false
+        didWarnAboutUnderscoreInIdentifier ifFalse:[
+            parserFlags warnUnderscoreInIdentifier ifTrue:[
+                self 
+                    warning:'underscores in identifiers/symbols are nonportable' 
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                didWarnAboutUnderscoreInIdentifier := true
+            ]
         ]
     ]
 
@@ -1504,22 +1536,29 @@
     tokenLineNr := lineNr := 1.
     currentComments := nil.
     saveComments := false.
+
+    parserFlags := ParserFlags new.
+
     ignoreErrors := false.
     ignoreWarnings := Warnings not.
-
-    warnSTXSpecialComment := WarnSTXSpecials.
-    warnSTXNameSpaceUse := WarnSTXSpecials.
-    warnUnderscoreInIdentifier := WarnUnderscoreInIdentifier.
-    warnDollarInIdentifier := WarnDollarInIdentifier.
-    warnOldStyleAssignment := WarnOldStyleAssignment.
-    warnCommonMistakes := WarnCommonMistakes.
-    warnPossibleIncompatibilities := WarnPossibleIncompatibilities.
-
-    allowUnderscoreInIdentifier := AllowUnderscoreInIdentifier.
-    allowDollarInIdentifier := AllowDollarInIdentifier.
-    allowOldStyleAssignment := AllowOldStyleAssignment.
-    allowSqueakExtensions := AllowSqueakExtensions.
-    allowLiteralNameSpaceSymbols := AllowLiteralNameSpaceSymbols.
+    didWarnAboutSTXSpecialComment := false.
+    didWarnAboutUnderscoreInIdentifier := false.
+    didWarnAboutDollarInIdentifier := false.
+    didWarnAboutOldStyleAssignment := false.
+
+"/    warnSTXSpecialComment := WarnSTXSpecials.
+"/    warnSTXNameSpaceUse := WarnSTXSpecials.
+"/    warnUnderscoreInIdentifier := WarnUnderscoreInIdentifier.
+"/    warnDollarInIdentifier := WarnDollarInIdentifier.
+"/    warnOldStyleAssignment := WarnOldStyleAssignment.
+"/    warnCommonMistakes := WarnCommonMistakes.
+"/    warnPossibleIncompatibilities := WarnPossibleIncompatibilities.
+
+"/    allowUnderscoreInIdentifier := AllowUnderscoreInIdentifier.
+"/    allowDollarInIdentifier := AllowDollarInIdentifier.
+"/    allowOldStyleAssignment := AllowOldStyleAssignment.
+"/    allowSqueakExtensions := AllowSqueakExtensions.
+"/    allowLiteralNameSpaceSymbols := AllowLiteralNameSpaceSymbols.
 
     "/ not used here, but eases subclassing for other languages.
     scanColonAsKeyword := true. 
@@ -1538,22 +1577,9 @@
 
     ignoreErrors := aScanner ignoreErrors.
     ignoreWarnings := aScanner ignoreWarnings.
-
-    warnSTXSpecialComment := aScanner warnSTXSpecialComment.
-    warnSTXNameSpaceUse := aScanner warnSTXNameSpaceUse.
-    warnUnderscoreInIdentifier := aScanner warnUnderscoreInIdentifier.
-    warnDollarInIdentifier := aScanner warnDollarInIdentifier.
-    warnOldStyleAssignment := aScanner warnOldStyleAssignment.
-    warnCommonMistakes := aScanner warnCommonMistakes.
-    warnPossibleIncompatibilities := aScanner warnPossibleIncompatibilities.
-
-    allowUnderscoreInIdentifier := aScanner allowUnderscoreInIdentifier.
-    allowDollarInIdentifier := aScanner allowDollarInIdentifier.
-    allowOldStyleAssignment := aScanner allowOldStyleAssignment.
-    allowSqueakExtensions := aScanner allowSqueakExtensions.
-
-    allowLiteralNameSpaceSymbols := aScanner allowLiteralNameSpaceSymbols.
-
+    parserFlags := aScanner parserFlags copy.
+
+    "/ not used here, but eases subclassing for other languages.
     scanColonAsKeyword := aScanner scanColonAsKeyword. 
 !
 
@@ -1758,7 +1784,7 @@
     ^ aCharacter
 
     "
-     AllowExtendedSTXSyntax := true
+     ParserFlags allowExtendedSTXSyntax:true
     "
     "
      'hello`nworld'          
@@ -1825,6 +1851,25 @@
 
 !Scanner methodsFor:'reading next token'!
 
+invalidCharacter:ch
+    |errMsg v|
+
+    v := ch codePoint.
+    ch isPrintable ifTrue:[
+        errMsg := 'Scanner - invalid character: ''' , ch asString , ''' ', '(' , (v radixPrintStringRadix:16) , ').'.
+    ] ifFalse:[
+        errMsg := 'Scanner - invalid character: ' , (v radixPrintStringRadix:16) , '.'.
+    ].
+    v > 16r7F ifTrue:[
+        errMsg := errMsg , '\\Notice: only 7-bit ascii allowed (for compatibility).' withCRs.
+    ].
+    self syntaxError:errMsg position:tokenPosition to:tokenPosition.
+    source next.
+    tokenName := token := nil.
+    tokenType := #Error.
+    ^ #Error
+!
+
 nextCharacter
     "a $ has been read - return a character token"
 
@@ -1890,7 +1935,7 @@
     |nextChar|
 
     nextChar := source nextPeek.
-    AllowExtendedSTXSyntax == true ifTrue:[
+    parserFlags allowExtendedSTXSyntax == true ifTrue:[
         (nextChar == $( ) ifTrue:[
             source next.
             token := '!!('.
@@ -1923,6 +1968,13 @@
     ^ self nextSpecialWith:$!!.
 !
 
+nextExtendedSpecial:ch
+    parserFlags allowExtendedBinarySelectors ifTrue:[
+        ^ self nextSpecial
+    ].
+    ^ self invalidCharacter:source peek.
+!
+
 nextHash
     "a # has been read - return either
         a symbol, 
@@ -1934,17 +1986,19 @@
         HashHash          (for '##' )
     "
 
-    |nextChar string part isNameSpaceSymbol|
+    |nextChar string part isNameSpaceSymbol allowUnderscoreInIdentifier|
+
+    allowUnderscoreInIdentifier := parserFlags allowUnderscoreInIdentifier.
 
     nextChar := source nextPeek.
     nextChar notNil ifTrue:[
         isNameSpaceSymbol := false.
         (nextChar isLetter
-        or:[(allowUnderscoreInIdentifier == true) and:[nextChar == $_]]) ifTrue:[
+        or:[(nextChar == $_) and:[allowUnderscoreInIdentifier]]) ifTrue:[
             string := ''.
             [nextChar notNil 
              and:[nextChar isLetterOrDigit 
-                  or:[allowUnderscoreInIdentifier == true and:[nextChar == $_]]
+                  or:[nextChar == $_ and:[allowUnderscoreInIdentifier]]
                  ]
             ] whileTrue:[
                 nextChar == $_ ifTrue:[
@@ -1956,6 +2010,7 @@
                     string := string , part.
                 ].
                 nextChar := source peek.
+
                 allowUnderscoreInIdentifier == true ifTrue:[
                     nextChar == $_ ifTrue:[
                         self warnUnderscoreAt:source position1Based.
@@ -1963,7 +2018,7 @@
                     [nextChar == $_] whileTrue:[
                         string := string copyWith:nextChar.
                         nextChar := source nextPeek.
-                        (nextChar isLetterOrDigit) ifTrue:[
+                        (nextChar notNil and:[nextChar isLetterOrDigit]) ifTrue:[
                             string := string , source nextAlphaNumericWord.
                             nextChar := source peek.
                         ]
@@ -1977,7 +2032,7 @@
                 ].
                 string := string copyWith:nextChar.
                 nextChar := source nextPeek.
-                allowLiteralNameSpaceSymbols ifTrue:[
+                parserFlags allowLiteralNameSpaceSymbols ifTrue:[
                     (nextChar == $:) ifTrue:[
                         string := string copyWith:nextChar.
                         nextChar := source nextPeek.
@@ -2033,7 +2088,7 @@
 
         (nextChar == $#) ifTrue:[
             nextChar := source nextPeek.
-            AllowDolphinExtensions == true ifTrue:[
+            parserFlags allowDolphinExtensions == true ifTrue:[
                 "dolphin does computed literals as ##( ... )"
                 nextChar == $( ifTrue:[
                     source next.    
@@ -2113,7 +2168,9 @@
     "an alpha character (or underscore if AllowUnderscore) has been read.
      Return the next identifier."
 
-    |nextChar string ok pos ch2|
+    |nextChar string ok pos ch2 allowUnderscoreInIdentifier|
+
+    allowUnderscoreInIdentifier := parserFlags allowUnderscoreInIdentifier.
 
     hereChar == $_ ifTrue:[
         "/
@@ -2121,7 +2178,7 @@
         "/ could not arrive here if it was off
         "/
         nextChar := source nextPeek.
-        allowOldStyleAssignment ifTrue:[
+        parserFlags allowOldStyleAssignment ifTrue:[
             (nextChar isLetterOrDigit or:[nextChar == $_]) ifFalse:[
                 "oops: a single underscore is an old-style assignement"
                 nextChar ~~ $: ifTrue:[
@@ -2145,37 +2202,28 @@
     ].
     nextChar := source peekOrNil.
 
-    (nextChar == $_ 
-    or:[nextChar == $$]) ifTrue:[
-        ok := (nextChar == $_) ifTrue:[allowUnderscoreInIdentifier] ifFalse:[allowDollarInIdentifier].
-        ok ifTrue:[
-            pos := source position1Based.
-            nextChar == $_ ifTrue:[
-                self warnUnderscoreAt:pos.
+    (((nextChar == $_) and:[allowUnderscoreInIdentifier]) 
+    or:[((nextChar == $$ ) and:[parserFlags allowDollarInIdentifier])]) ifTrue:[
+        pos := source position1Based.
+        nextChar == $_ ifTrue:[
+            self warnUnderscoreAt:pos.
+        ] ifFalse:[
+            self warnDollarAt:pos.
+        ].
+        ok := true.
+        [ok] whileTrue:[
+            string := string copyWith:nextChar.
+            nextChar := source nextPeek.
+            nextChar isNil ifTrue:[
+                ok := false
             ] ifFalse:[
-                self warnDollarAt:pos.
-            ].
-            [ok] whileTrue:[
-                string := string copyWith:nextChar.
-                nextChar := source nextPeek.
-                nextChar isNil ifTrue:[
-                    ok := false
-                ] ifFalse:[
-                    (nextChar isLetterOrDigit) ifTrue:[
-                        string := string , source nextAlphaNumericWord.
-                        nextChar := source peekOrNil.
-                    ].
-                    (nextChar == $_) ifTrue:[
-                        ok := allowUnderscoreInIdentifier
-                    ] ifFalse:[
-                        (nextChar == $$) ifTrue:[
-                            ok := allowDollarInIdentifier
-                        ] ifFalse:[
-                            ok := false
-                        ]
-                    ]
-                ]
-            ].
+                (nextChar isLetterOrDigit) ifTrue:[
+                    string := string , source nextAlphaNumericWord.
+                    nextChar := source peekOrNil.
+                ].
+                ok := ((nextChar == $_) and:[allowUnderscoreInIdentifier]) 
+                      or:[((nextChar == $$ ) and:[parserFlags allowDollarInIdentifier])].
+            ]
         ].
     ].
 
@@ -2209,7 +2257,7 @@
             peekChar2 := $=.
         ]
     ] ifFalse:[
-        (nextChar == $. and:[AllowQualifiedNames]) ifTrue:[
+        (nextChar == $. and:[parserFlags allowQualifiedNames]) ifTrue:[
             "/ period follows - if next-after character is an identifier character,
             "/ make peekSym a #NameSpaceSeparator; otherwise a $.
             source next.
@@ -2462,7 +2510,7 @@
     "a special character has been read, look for another one.
      also -number is handled here"
 
-    |secondChar thirdChar fourthChar string p|
+    |secondChar thirdChar fourthChar string p charType|
 
     secondChar := source peekOrNil.
     ((firstChar == $-) and:[secondChar notNil]) ifTrue:[
@@ -2474,7 +2522,9 @@
     ].
     string := firstChar asString.
     secondChar notNil ifTrue:[
-        ((typeArray at:(secondChar codePoint)) == #special) ifTrue:[
+        charType := typeArray at:(secondChar codePoint).
+        ((charType == #special) 
+        or:[ (charType == #extendedSpecial) and:[parserFlags allowExtendedBinarySelectors] ]) ifTrue:[
             (secondChar == $-) ifTrue:[
                 "special- look if minus belongs to number following"
                 p := source position1Based.
@@ -2496,7 +2546,9 @@
 
             thirdChar := source peekOrNil.
             thirdChar notNil ifTrue:[
-                ((typeArray at:(thirdChar codePoint)) == #special) ifTrue:[
+                charType := typeArray at:(thirdChar codePoint).
+                ((charType == #special) 
+                or:[ (charType == #extendedSpecial) and:[parserFlags allowExtendedBinarySelectors] ]) ifTrue:[
                     (thirdChar == $-) ifTrue:[
                         "special- look if minus belongs to number following"
                         p := source position1Based.
@@ -2561,7 +2613,7 @@
                     inString := false
                 ]
             ] ifFalse:[
-                AllowExtendedSTXSyntax == true ifTrue:[
+                parserFlags allowExtendedSTXSyntax == true ifTrue:[
                     (nextChar == $`) ifTrue:[
                         peekChar := source peekOrNil.    
                         peekChar notNil ifTrue:[
@@ -2601,7 +2653,7 @@
 nextToken
     "return the next token from the source-stream"
 
-    |skipping actionBlock v ch tok errMsg|
+    |skipping actionBlock v ch tok|
 
     [true] whileTrue:[
         peekChar notNil ifTrue:[
@@ -2693,20 +2745,9 @@
             tok notNil ifTrue:[
                 ^ tok
             ].
+            "/ a nil token means: continue reading
         ] ifFalse:[
-            ch isPrintable ifTrue:[
-                errMsg := 'Scanner - invalid character: ''' , ch asString , ''' ', '(' , (v radixPrintStringRadix:16) , ').'.
-            ] ifFalse:[
-                errMsg := 'Scanner - invalid character: ' , (v radixPrintStringRadix:16) , '.'.
-            ].
-            v > 16r7F ifTrue:[
-                errMsg := errMsg , '\\Notice: only 7-bit ascii allowed (for compatibility).' withCRs.
-            ].
-            self syntaxError:errMsg position:tokenPosition to:tokenPosition.
-            source next.
-            tokenName := token := nil.
-            tokenType := #Error.
-            ^ #Error
+            ^ self invalidCharacter:ch.
         ]
     ].
 
@@ -2727,11 +2768,10 @@
 nextUnderline
     "return a character token"
 
-    allowUnderscoreInIdentifier ifTrue:[
+    parserFlags allowUnderscoreInIdentifier ifTrue:[
         ^ self nextIdentifier
-    ] ifFalse:[
-        ^ self nextToken:$_
-    ]
+    ].
+    ^ self nextToken:$_
 !
 
 skipComment
@@ -2777,17 +2817,7 @@
         ].
         self markCommentFrom:startPos to:(source position1Based).
         lineNr := lineNr + 1.
-        ignoreWarnings ifFalse:[
-            warnSTXSpecialComment ifTrue:[
-                self warning:'end-of-line comments are a nonstandard feature of ST/X' 
-                     doNotShowAgainAction:[ WarnSTXSpecials := false ]
-                     position:startPos to:(source position1Based).
-                "
-                 only warn once
-                "
-                warnSTXSpecialComment := false
-            ]
-        ].
+        self warnSTXSpecialCommentAt:startPos.
         outStream notNil ifTrue:[
             outStream cr.
             outCol := 1
@@ -2948,7 +2978,7 @@
 !Scanner class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.202 2005-07-26 08:50:48 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.203 2005-10-18 14:26:34 cg Exp $'
 ! !
 
 Scanner initialize!
--- a/SyntaxHighlighter.st	Tue Oct 18 16:25:30 2005 +0200
+++ b/SyntaxHighlighter.st	Tue Oct 18 16:26:36 2005 +0200
@@ -256,7 +256,7 @@
     super initialize.
 
     foldConstants := false.
-    allowDollarInIdentifier := true.
+"/    parserFlags allowDollarInIdentifier:true.
 
     preferences := UserPreferences current.
 
@@ -658,5 +658,5 @@
 !SyntaxHighlighter class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.47 2004-09-20 08:47:02 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.48 2005-10-18 14:26:36 cg Exp $'
 ! !