Scanner.st
changeset 4572 88aa6f2bcfbd
parent 4571 2e505427eda3
child 4592 d14e38aec6de
--- a/Scanner.st	Sat Sep 28 14:50:41 2019 +0200
+++ b/Scanner.st	Sat Sep 28 15:43:30 2019 +0200
@@ -2,7 +2,7 @@
 
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -16,19 +16,19 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#Scanner
-	instanceVariableNames:'typeArray actionArray source lineNr token tokenType tokenPosition
-		tokenValue tokenName tokenLineNr tokenLastEndPosition hereChar
-		peekChar peekChar2 requestor exitBlock errorFlag ignoreErrors
-		ignoreWarnings saveComments currentComments collectedSource
-		scanColonAsKeyword outStream outCol inArrayLiteral lastDirective
-		parserFlags didWarnAboutSTXSpecialComment
-		didWarnAboutUnderscoreInIdentifier didWarnAboutOldStyleAssignment
-		didWarnAboutDollarInIdentifier didWarnAboutPeriodInSymbol
-		unicodeActions'
-	classVariableNames:'DefaultActionArray DefaultTypeArray DefaultUnicodeActions
-		EmptySourceNotificationSignal'
-	poolDictionaries:''
-	category:'System-Compiler'
+        instanceVariableNames:'typeArray actionArray source lineNr token tokenType tokenPosition
+                tokenValue tokenName tokenLineNr tokenLastEndPosition hereChar
+                peekChar peekChar2 requestor exitBlock errorFlag ignoreErrors
+                ignoreWarnings saveComments currentComments collectedSource
+                scanColonAsKeyword outStream outCol inArrayLiteral lastDirective
+                parserFlags didWarnAboutSTXSpecialComment
+                didWarnAboutUnderscoreInIdentifier didWarnAboutOldStyleAssignment
+                didWarnAboutDollarInIdentifier didWarnAboutPeriodInSymbol
+                unicodeActions'
+        classVariableNames:'DefaultActionArray DefaultTypeArray DefaultUnicodeActions
+                EmptySourceNotificationSignal'
+        poolDictionaries:''
+        category:'System-Compiler'
 !
 
 Scanner class instanceVariableNames:'TypeArray ActionArray UnicodeActions'
@@ -39,31 +39,31 @@
 !
 
 Object subclass:#Comment
-	instanceVariableNames:'commentType commentString startPosition endPosition'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Scanner
+        instanceVariableNames:'commentType commentString startPosition endPosition'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Scanner
 !
 
 Object subclass:#Directive
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Scanner
+        instanceVariableNames:''
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Scanner
 !
 
 Scanner::Directive subclass:#ClassDirective
-	instanceVariableNames:'className'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Scanner::Directive
+        instanceVariableNames:'className'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Scanner::Directive
 !
 
 Scanner::Directive::ClassDirective subclass:#ClassHintDirective
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:Scanner::Directive
+        instanceVariableNames:''
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:Scanner::Directive
 !
 
 !Scanner class methodsFor:'documentation'!
@@ -71,19 +71,19 @@
 bugs
 "
    array constant containing keywords as in:
-	#(
-		foo:bar:
-		fee:baz:
-	 )
+        #(
+                foo:bar:
+                fee:baz:
+         )
 
    is scanned as 4-element array containing ( #foo: #bar: #fee: #baz: )
    this MUST be fixed.
 
    workaround:
-	#(
-		#'foo:bar:'
-		#'fee:baz:'
-	 )
+        #(
+                #'foo:bar:'
+                #'fee:baz:'
+         )
 
 "
 !
@@ -91,7 +91,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-	      All Rights Reserved
+              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
@@ -110,27 +110,27 @@
     instance variables as a side effect.
 
     TODO:
-	some testers noticed that ST-80's scanner methods are called
-	xLetter, xDigit etc. For code using these (internals), the nextNumber,
-	nextIdentifier etc. methods should be renamed.
-	(to me, these seem to be internal private methods;
-	 their public use is not a good idea ..)
-
-	Scanner is typically subclassed for parsing and #nextToken
-	invoked via #self-sends.
-	This should be changed and scanner ought to be an instance variable
-	of Parser - this allows more flexible use of the scanner/parser
-	framework (i.e. changing the scanner without affecting the parser).
+        some testers noticed that ST-80's scanner methods are called
+        xLetter, xDigit etc. For code using these (internals), the nextNumber,
+        nextIdentifier etc. methods should be renamed.
+        (to me, these seem to be internal private methods;
+         their public use is not a good idea ..)
+
+        Scanner is typically subclassed for parsing and #nextToken
+        invoked via #self-sends.
+        This should be changed and scanner ought to be an instance variable
+        of Parser - this allows more flexible use of the scanner/parser
+        framework (i.e. changing the scanner without affecting the parser).
 
     Extensions:
-	this scanner allows for 3-character binary selectors.
-	also, # is a valid selector. (however, ## is currently scanned as a symbol literal).
+        this scanner allows for 3-character binary selectors.
+        also, # is a valid selector. (however, ## is currently scanned as a symbol literal).
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [see also:]
-	Parser
+        Parser
 "
 ! !
 
@@ -147,12 +147,12 @@
 
     "/ ^ '±×·÷«»'.
     ^ String
-	with:(Character value:16rB1)  "/ plus-minus
-	with:(Character value:16rD7)  "/ times
-	with:(Character value:16rB7)  "/ centered dot
-	with:(Character value:16rF7)  "/ divide
-	with:(Character value:16rAB)  "/ <<
-	with:(Character value:16rBB). "/ >>
+        with:(Character value:16rB1)  "/ plus-minus
+        with:(Character value:16rD7)  "/ times
+        with:(Character value:16rB7)  "/ centered dot
+        with:(Character value:16rF7)  "/ divide
+        with:(Character value:16rAB)  "/ <<
+        with:(Character value:16rBB). "/ >>
 
     "Modified (comment): / 17-11-2016 / 09:22:42 / cg"
 !
@@ -280,7 +280,7 @@
 
 actionArray
     ActionArray isNil ifTrue:[
-	self setupActions
+        self setupActions
     ].
     ^ ActionArray ? DefaultActionArray
 !
@@ -302,14 +302,14 @@
 
 typeArray
     TypeArray isNil ifTrue:[
-	self setupActions
+        self setupActions
     ].
     ^ TypeArray ? DefaultTypeArray
 !
 
 unicodeActions
     UnicodeActions isNil ifTrue:[
-	self setupActions
+        self setupActions
     ].
     ^ UnicodeActions ? DefaultUnicodeActions
 
@@ -323,9 +323,9 @@
      later in the 'private.rc' file."
 
     EmptySourceNotificationSignal isNil ifTrue:[
-	EmptySourceNotificationSignal := QuerySignal new mayProceed:true.
-	EmptySourceNotificationSignal notifierString:'empty source given to evaluate'.
-	EmptySourceNotificationSignal nameClass:self message:#emptySourceNotificationSignal.
+        EmptySourceNotificationSignal := QuerySignal new mayProceed:true.
+        EmptySourceNotificationSignal notifierString:'empty source given to evaluate'.
+        EmptySourceNotificationSignal nameClass:self message:#emptySourceNotificationSignal.
     ].
 
     "
@@ -357,7 +357,7 @@
      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"
+        Compiler allowDollarInIdentifiers:false"
 
     ParserFlags allowDollarInIdentifier:aBoolean.
 
@@ -374,7 +374,7 @@
 allowDolphinExtensions:aBoolean
     "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"
+        Compiler allowDolphinComputedArrays:true"
 
     ParserFlags allowDolphinExtensions:aBoolean.
 
@@ -416,7 +416,7 @@
 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
+        Compiler allowQualifiedNames:true
      Notice, that qualified names are not really supported semantically
      (they are parsed, but treated like regular globals)
     "
@@ -432,8 +432,8 @@
 allowSqueakExtensions
     <resource: #obsolete>
     "return true, if support for squeak extensions
-	computed arrays { .., }
-	c/java style arguments in message sends rec foo(arg1, ... argN)
+        computed arrays { .., }
+        c/java style arguments in message sends rec foo(arg1, ... argN)
      is enabled."
 
     ^ ParserFlags allowSqueakExtensions
@@ -441,11 +441,11 @@
 
 allowSqueakExtensions:aBoolean
     "this allows turning on/off support for squeak extensions:
-	computed arrays { .., }
-	c/java style arguments in message sends rec foo(arg1, ... argN)
+        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"
+        Compiler allowSqueakComputedArrays:true"
 
     ParserFlags allowSqueakExtensions:aBoolean.
 
@@ -470,7 +470,7 @@
      underscores are still scanned as assignment.
      If you have to fileIn old VW-Vsn2.x classes,
      turn them off with:
-	Compiler allowUnderscoreInIdentifiers:false"
+        Compiler allowUnderscoreInIdentifiers:false"
 
     ParserFlags allowUnderscoreInIdentifier:aBoolean.
 
@@ -495,7 +495,7 @@
      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:
-	Compiler warnCommonMistakes:false
+        Compiler warnCommonMistakes:false
      in your 'private.rc' file"
 
     ParserFlags warnCommonMistakes:aBoolean
@@ -518,7 +518,7 @@
      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:
-	Compiler warnDollarInIdentifier:false
+        Compiler warnDollarInIdentifier:false
      in your 'private.rc' file"
 
     ParserFlags warnDollarInIdentifier:aBoolean
@@ -538,7 +538,7 @@
     "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:
-	Compiler warnOldStyleAssignment:false
+        Compiler warnOldStyleAssignment:false
      in your 'private.rc' file"
 
     ParserFlags warnOldStyleAssignment:aBoolean
@@ -559,7 +559,7 @@
      on or off.
      If you get bored by those warnings, turn them off by adding
      a line as:
-	Compiler warnPossibleIncompatibilities:false
+        Compiler warnPossibleIncompatibilities:false
      in your 'private.rc' file."
 
     ParserFlags warnPossibleIncompatibilities:aBoolean
@@ -578,7 +578,7 @@
     "this allows turning on/off warnings about stx specials.
      If you get bored by those warnings, turn them off by adding
      a line as:
-	Compiler warnSTXSpecials:false
+        Compiler warnSTXSpecials:false
      in your 'private.rc' file"
 
     ParserFlags warnSTXSpecials:aBoolean
@@ -598,7 +598,7 @@
      (i.e. VW releases 2.x).
      If you get bored by those warnings, turn them off by adding
      a line as:
-	Compiler warnUnderscoreInIdentifier:false
+        Compiler warnUnderscoreInIdentifier:false
      in your 'private.rc' file"
 
     ParserFlags warnUnderscoreInIdentifier:aBoolean
@@ -615,7 +615,7 @@
 warnings:aBoolean
     "this allows turning on/off all warnings; the default is on.
      You can turn off warnings in your 'private.rc' file with
-	 Compiler warnings:false
+         Compiler warnings:false
     "
 
     ParserFlags warnings:aBoolean
@@ -690,7 +690,7 @@
     |t|
 
     [(t := self nextToken) ~~ #EOF] whileTrue:[
-	aBlock value:t.
+        aBlock value:t.
     ].
 !
 
@@ -731,13 +731,13 @@
     self nextToken.
 
     [token notNil] whileTrue:[
-	token == $( ifTrue:[
-	    self nextToken.
-	    tokens add:(readArray value)
-	] ifFalse:[
-	    tokens add:token
-	].
-	self nextToken
+        token == $( ifTrue:[
+            self nextToken.
+            tokens add:(readArray value)
+        ] ifFalse:[
+            tokens add:token
+        ].
+        self nextToken
     ].
     ^ tokens
 
@@ -747,12 +747,12 @@
      Scanner new scanTokens:'translate (200px 100px)'
 
      Scanner new
-	scanTokens:'Boolean subclass:#True
-				instanceVariableNames:''''
-				classVariableNames:''''
-				poolDictionaries:''''
-				category:''Kernel-Objects''
-	'
+        scanTokens:'Boolean subclass:#True
+                                instanceVariableNames:''''
+                                classVariableNames:''''
+                                poolDictionaries:''''
+                                category:''Kernel-Objects''
+        '
     "
 
     "Modified: / 23-08-2017 / 23:58:03 / cg"
@@ -938,8 +938,8 @@
 allowSqueakExtensions
     <resource: #obsolete>
     "return true, if support for squeak extensions
-	computed arrays { .., }
-	c/java style arguments in message sends rec foo(arg1, ... argN)
+        computed arrays { .., }
+        c/java style arguments in message sends rec foo(arg1, ... argN)
      is enabled."
 
     ^ parserFlags allowSqueakExtensions
@@ -947,8 +947,8 @@
 
 allowSqueakExtensions:aBoolean
     "this allows turning on/off support for squeak extensions:
-	computed arrays { .., }
-	c/java style arguments in message sends rec foo(arg1, ... argN)
+        computed arrays { .., }
+        c/java style arguments in message sends rec foo(arg1, ... argN)
     "
 
     parserFlags allowSqueakExtensions:aBoolean
@@ -1055,8 +1055,8 @@
 
     className := self parseDirectiveClassNameArg.
     className isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Class'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Class'' directive'.
+        ^ false
     ].
     lastDirective := Directive newClassDirective className:className.
     ^ true
@@ -1071,8 +1071,8 @@
 
     className := self parseDirectiveClassNameArg.
     className isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''ClassHint'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''ClassHint'' directive'.
+        ^ false
     ].
     lastDirective := Directive newClassHintDirective className:className.
     ^ true
@@ -1088,70 +1088,70 @@
     source skipSeparatorsExceptCR.
     hereChar := source peekOrNil.
     hereChar isLetter ifTrue:[
-	directive := source nextAlphaNumericWord asLowercase.
-	source peekOrNil == $: ifTrue:[
-	    source next.
-	    source skipSeparatorsExceptCR.
-	    hereChar := source peekOrNil.
-
-	    "
-	     Package: 'name-of-package'
-	     Package: packageId
-	    "
-	    directive = 'package' ifTrue:[
-		self parsePackageDirective.
-	    ].
-
-	    "
-	     Namespace: 'nameSpaceIdentifier'
-	     Namespace: nameSpaceIdentifier
-	    "
-	    (directive = 'namespace') ifTrue:[
-		self parseNamespaceDirective.
-	    ].
-
-	    "
-	     Uses: 'nameSpace1', ... , 'nameSpaceN'
-	     Uses: nameSpaceId1, ... , nameSpaceIdN
-	    "
-	    directive = 'uses' ifTrue:[
-		self parseUsesDirective.
-	    ].
-
-	    "
-	     reuires: 'name-of-feature'
-	    "
-	    directive = 'requires' ifTrue:[
-		self parseRequiresDirective.
-	    ].
-
-	    "
-	     Prerequisites: 'name-of-package', ... , 'name-of-package'
-	    "
-	    directive = 'prerequisites' ifTrue:[
-		self parsePrerequisitesDirective.
-	    ].
-
-	    "
-	     Syntax: 'name-of-dialect'
-	    "
-	    directive = 'syntax' ifTrue:[
-		self parseSyntaxDirective.
-	    ].
-
-	    "
-	     Class: className
-	    "
-	    directive = 'class' ifTrue:[
-		self parseClassDirective.
-	    ].
-	    "
-	     ClassHint: className
-	    "
-	    directive = 'classhint' ifTrue:[
-		self parseClassHintDirective.
-	    ].
-	]
+        directive := source nextAlphaNumericWord asLowercase.
+        source peekOrNil == $: ifTrue:[
+            source next.
+            source skipSeparatorsExceptCR.
+            hereChar := source peekOrNil.
+
+            "
+             Package: 'name-of-package'
+             Package: packageId
+            "
+            directive = 'package' ifTrue:[
+                self parsePackageDirective.
+            ].
+
+            "
+             Namespace: 'nameSpaceIdentifier'
+             Namespace: nameSpaceIdentifier
+            "
+            (directive = 'namespace') ifTrue:[
+                self parseNamespaceDirective.
+            ].
+
+            "
+             Uses: 'nameSpace1', ... , 'nameSpaceN'
+             Uses: nameSpaceId1, ... , nameSpaceIdN
+            "
+            directive = 'uses' ifTrue:[
+                self parseUsesDirective.
+            ].
+
+            "
+             reuires: 'name-of-feature'
+            "
+            directive = 'requires' ifTrue:[
+                self parseRequiresDirective.
+            ].
+
+            "
+             Prerequisites: 'name-of-package', ... , 'name-of-package'
+            "
+            directive = 'prerequisites' ifTrue:[
+                self parsePrerequisitesDirective.
+            ].
+
+            "
+             Syntax: 'name-of-dialect'
+            "
+            directive = 'syntax' ifTrue:[
+                self parseSyntaxDirective.
+            ].
+
+            "
+             Class: className
+            "
+            directive = 'class' ifTrue:[
+                self parseClassDirective.
+            ].
+            "
+             ClassHint: className
+            "
+            directive = 'classhint' ifTrue:[
+                self parseClassHintDirective.
+            ].
+        ]
     ].
     hereChar := source peekOrNil.
     ^ true.
@@ -1163,8 +1163,8 @@
     "helper for parsing a directive"
 
     ^ self
-	parseDirectiveStringArg:[:ch | ch isLetterOrUnderline]
-			   rest:[:ch | ch isLetterOrDigit or:[ch == $_ or:[ch == $:]]]
+        parseDirectiveStringArg:[:ch | ch isLetterOrUnderline]
+                           rest:[:ch | ch isLetterOrDigit or:[ch == $_ or:[ch == $:]]]
 
     "Modified: / 18-11-2006 / 14:48:07 / cg"
 !
@@ -1175,7 +1175,7 @@
      and consisting of letters, digits, underlines or dots."
 
     ^ self parseDirectiveStringArg:[:ch | ch isLetterOrUnderline]
-			      rest:[:ch | ch isLetterOrDigit or:[ch == $_ or:[ch == $.]]]
+                              rest:[:ch | ch isLetterOrDigit or:[ch == $_ or:[ch == $.]]]
 
     "Modified: / 18-11-2006 / 14:47:12 / cg"
 !
@@ -1188,23 +1188,23 @@
     strBuffer := WriteStream on:''.
 
     hereChar == $' ifTrue:[
-	hereChar := source nextPeek.
-	[hereChar ~~ $'] whileTrue:[
-	    strBuffer nextPut:hereChar.
-	    hereChar := source nextPeek.
-	].
-	hereChar := source nextPeek.
-	^ strBuffer contents
+        hereChar := source nextPeek.
+        [hereChar ~~ $'] whileTrue:[
+            strBuffer nextPut:hereChar.
+            hereChar := source nextPeek.
+        ].
+        hereChar := source nextPeek.
+        ^ strBuffer contents
     ].
 
     (firstCharacterCheckBlock value:hereChar) ifTrue:[
-	strBuffer nextPut:hereChar.
-	hereChar := source nextPeek.
-	[restCharacterCheckBlock value:hereChar] whileTrue:[
-	    strBuffer nextPut:hereChar.
-	    hereChar := source nextPeek.
-	].
-	^ strBuffer contents
+        strBuffer nextPut:hereChar.
+        hereChar := source nextPeek.
+        [restCharacterCheckBlock value:hereChar] whileTrue:[
+            strBuffer nextPut:hereChar.
+            hereChar := source nextPeek.
+        ].
+        ^ strBuffer contents
     ].
 
     ^ nil
@@ -1220,14 +1220,14 @@
     list := OrderedCollection new.
 
     [hereChar == $'] whileTrue:[
-	list addLast:self parseDirectiveStringArg.
-	source skipSeparatorsExceptCR.
-	hereChar := source peekOrNil.
-	(hereChar == $,) ifTrue:[
-	    source next.
-	    source skipSeparatorsExceptCR.
-	    hereChar := source peekOrNil.
-	].
+        list addLast:self parseDirectiveStringArg.
+        source skipSeparatorsExceptCR.
+        hereChar := source peekOrNil.
+        (hereChar == $,) ifTrue:[
+            source next.
+            source skipSeparatorsExceptCR.
+            hereChar := source peekOrNil.
+        ].
     ].
     ^ list
 
@@ -1244,14 +1244,14 @@
 
     namespace := self parseDirectiveStringArg.
     namespace isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Namespace'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Namespace'' directive'.
+        ^ false
     ].
     target := (requestor notNil and:[ requestor respondsTo:#setNameSpace: ]) ifTrue:[requestor] ifFalse:[self].
     Error handle:[:ex |
-	ParseError raiseErrorString:ex description
+        ParseError raiseErrorString:ex description
     ] do:[
-	target setNameSpace:namespace.
+        target setNameSpace:namespace.
     ].
     ^ true
 !
@@ -1266,8 +1266,8 @@
 
     packageName := self parseDirectiveStringArg.
     packageName isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Package'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Package'' directive'.
+        ^ false
     ].
     packageName := packageName asSymbol.
     target := (requestor notNil and:[ requestor respondsTo:#setPackage: ]) ifTrue:[requestor] ifFalse:[self].
@@ -1284,11 +1284,11 @@
 
     list := self parseDirectiveStringListArg.
     list isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Prerequisites'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Prerequisites'' directive'.
+        ^ false
     ].
     (requestor notNil and:[requestor respondsTo:#requirePackages:]) ifTrue:[
-	requestor requirePackages:list
+        requestor requirePackages:list
     ].
     ^ true
 !
@@ -1302,12 +1302,12 @@
 
     list := self parseDirectiveStringListArg.
     list isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Requires'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Requires'' directive'.
+        ^ false
     ].
 "/ self halt.
     (requestor notNil and:[requestor respondsTo:#requireFeatures:]) ifTrue:[
-	requestor requireFeatures:list
+        requestor requireFeatures:list
     ].
     ^ true
 
@@ -1323,8 +1323,8 @@
 
     syntax := self parseDirectiveStringArg.
     syntax isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Syntax'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Syntax'' directive'.
+        ^ false
     ].
     target := (requestor notNil and:[ requestor respondsTo:#setSyntax: ]) ifTrue:[requestor] ifFalse:[self].
     target setSyntax:syntax.
@@ -1341,11 +1341,11 @@
 
     list := self parseDirectiveStringListArg.
     list isNil ifTrue:[
-	Transcript showCR:'Scanner [warning]: unrecognized ''Uses'' directive'.
-	^ false
+        Transcript showCR:'Scanner [warning]: unrecognized ''Uses'' directive'.
+        ^ false
     ].
     (requestor notNil and:[requestor respondsTo:#addNameSpaces:]) ifTrue:[
-	requestor addNameSpaces:list
+        requestor addNameSpaces:list
     ].
     ^ true
 ! !
@@ -1421,18 +1421,18 @@
     |correctIt|
 
     requestor isNil ifTrue:[
-	correctIt := false
+        correctIt := false
     ] ifFalse:[
-	DoNotShowCompilerWarningAgainActionQuery handle:[:ex |
-	    parserFlags warnAboutPossiblyUnimplementedSelectors:false.
-	    ParserFlags warnAboutPossiblyUnimplementedSelectors:false.
-	    ex proceed.
-	] do:[
-	    correctIt := requestor correctableSelectorWarning:message position:pos1 to:pos2 from:self
-	]
+        DoNotShowCompilerWarningAgainActionQuery handle:[:ex |
+            parserFlags warnAboutPossiblyUnimplementedSelectors:false.
+            ParserFlags warnAboutPossiblyUnimplementedSelectors:false.
+            ex proceed.
+        ] do:[
+            correctIt := requestor correctableSelectorWarning:message position:pos1 to:pos2 from:self
+        ]
     ].
     correctIt == false ifTrue:[
-	exitBlock value
+        exitBlock value
     ].
     ^ correctIt
 
@@ -1449,28 +1449,28 @@
     parserFlags warnings ifFalse:[^ false].
 
     requestor isNil ifTrue:[
-	^ false
+        ^ false
     ].
 
     warnAction := [ answer := requestor correctableWarning:aMessage position:position to:endPos from:self ].
 
     doNotShowAgainAction notNil ifTrue:[
-	realAction := warnAction.
-	warnAction :=
-	    [
-		DoNotShowCompilerWarningAgainActionQuery
-		    answer:doNotShowAgainAction
-		    do:realAction
-	    ].
+        realAction := warnAction.
+        warnAction :=
+            [
+                DoNotShowCompilerWarningAgainActionQuery
+                    answer:doNotShowAgainAction
+                    do:realAction
+            ].
     ].
     (doNotShowAgainForThisMethodAction notNil and:[ self isDoIt not ]) ifTrue:[
-	real2Action := warnAction.
-	warnAction :=
-	    [
-		DoNotShowCompilerWarningAgainForThisMethodActionQuery
-		    answer:doNotShowAgainForThisMethodAction
-		    do:real2Action
-	    ].
+        real2Action := warnAction.
+        warnAction :=
+            [
+                DoNotShowCompilerWarningAgainForThisMethodActionQuery
+                    answer:doNotShowAgainForThisMethodAction
+                    do:real2Action
+            ].
     ].
 
     warnAction value.
@@ -1487,14 +1487,14 @@
     |correctIt|
 
     requestor isNil ifTrue:[
-	"/ self showErrorMessage:message position:pos1.
-	correctIt := false
+        "/ self showErrorMessage:message position:pos1.
+        correctIt := false
     ] ifFalse:[
-	correctIt := requestor correctableWarning:message position:pos1 to:pos2 from:self
+        correctIt := requestor correctableWarning:message position:pos1 to:pos2 from:self
     ].
 
     (correctIt == false or:[correctIt == #Error]) ifTrue:[
-	exitBlock value
+        exitBlock value
     ].
     ^ correctIt
 
@@ -1638,28 +1638,28 @@
 
     requestor isNil ifTrue:[
 "/        self showErrorMessage:aMessage position:position.
-	^ false
+        ^ false
     ].
 
     warnAction := [ answer := requestor warning:aMessage position:position to:endPos from:self ].
 
     doNotShowAgainAction notNil ifTrue:[
-	realAction := warnAction.
-	warnAction :=
-	    [
-		DoNotShowCompilerWarningAgainActionQuery
-		    answer:doNotShowAgainAction
-		    do:realAction
-	    ].
+        realAction := warnAction.
+        warnAction :=
+            [
+                DoNotShowCompilerWarningAgainActionQuery
+                    answer:doNotShowAgainAction
+                    do:realAction
+            ].
     ].
     (doNotShowAgainForThisMethodAction notNil and:[ self isDoIt not ]) ifTrue:[
-	real2Action := warnAction.
-	warnAction :=
-	    [
-		DoNotShowCompilerWarningAgainForThisMethodActionQuery
-		    answer:doNotShowAgainForThisMethodAction
-		    do:real2Action
-	    ].
+        real2Action := warnAction.
+        warnAction :=
+            [
+                DoNotShowCompilerWarningAgainForThisMethodActionQuery
+                    answer:doNotShowAgainForThisMethodAction
+                    do:real2Action
+            ].
     ].
 
     warnAction value.
@@ -1673,10 +1673,10 @@
      Return the result passed back from the requestor (or false, if there is none)."
 
     ^ self
-	notifyWarning:aMessage
-	doNotShowAgainAction:doNotShowAgainAction
-	doNotShowAgainForThisMethodAction:nil
-	position:position to:endPos
+        notifyWarning:aMessage
+        doNotShowAgainAction:doNotShowAgainAction
+        doNotShowAgainForThisMethodAction:nil
+        position:position to:endPos
 
     "Modified: / 28-02-2012 / 08:44:45 / cg"
 !
@@ -1687,9 +1687,9 @@
      Return the result passed back by the requestor."
 
     ^ self
-	notifyWarning:aMessage
-	doNotShowAgainAction:nil
-	position:position to:endPos.
+        notifyWarning:aMessage
+        doNotShowAgainAction:nil
+        position:position to:endPos.
 
     "Modified (format): / 28-02-2012 / 08:44:13 / cg"
 !
@@ -1754,7 +1754,7 @@
 
 positionFromLineNumber:lNr
     (requestor notNil and:[requestor isTextView]) ifTrue:[
-	^ requestor characterPositionOfLine:lNr col:1.
+        ^ requestor characterPositionOfLine:lNr col:1.
     ].
     ^ nil
 
@@ -1819,13 +1819,13 @@
     "warn about a common beginners mistake"
 
     ignoreWarnings ifFalse:[
-	parserFlags warnings ifTrue:[
-	    parserFlags warnCommonMistakes ifTrue:[
-		self
-		    warning:msg
-		    position:pos1 to:pos2.
-	    ]
-	]
+        parserFlags warnings ifTrue:[
+            parserFlags warnCommonMistakes ifTrue:[
+                self
+                    warning:msg
+                    position:pos1 to:pos2.
+            ]
+        ]
     ]
 
     "Created: 18.7.1996 / 10:28:38 / cg"
@@ -1836,18 +1836,18 @@
     "warn about $-character in an identifier"
 
     ignoreWarnings ifFalse:[
-	didWarnAboutDollarInIdentifier ifFalse:[
-	    parserFlags warnDollarInIdentifier ifTrue:[
-		self
-		    warning:'$-characters in identifiers/symbols are nonportable'
-		    doNotShowAgainAction:[ ParserFlags warnDollarInIdentifier:false ]
-		    position:position to:position.
-		"
-		 only warn once (per method)
-		"
-		didWarnAboutDollarInIdentifier := true
-	    ]
-	]
+        didWarnAboutDollarInIdentifier ifFalse:[
+            parserFlags warnDollarInIdentifier ifTrue:[
+                self
+                    warning:'$-characters in identifiers/symbols are nonportable'
+                    doNotShowAgainAction:[ ParserFlags warnDollarInIdentifier:false ]
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                didWarnAboutDollarInIdentifier := true
+            ]
+        ]
     ]
 
     "Created: 7.9.1997 / 01:50:24 / cg"
@@ -1858,18 +1858,18 @@
     "warn about an oldStyle assignment"
 
     ignoreWarnings ifFalse:[
-	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
-	]
+        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
+        ]
     ]
 
     "Modified: 23.5.1997 / 12:16:48 / cg"
@@ -1879,20 +1879,20 @@
     "warn about §-character in an identifier"
 
     ignoreWarnings ifFalse:[
-	"/ didWarnAboutParagraphInIdentifier ifFalse:[
-	    parserFlags warnParagraphInIdentifier ifTrue:[
-		self
-		    warning:'§-characters in identifiers/symbols are nonportable'
-		    doNotShowAgainAction:[ ParserFlags warnParagraphInIdentifier:false ]
-		    position:position to:position.
-		"
-		 only warn once (per method)
-		"
-		parserFlags := parserFlags copy.
-		parserFlags warnParagraphInIdentifier:false.
-		"/ didWarnAboutParagraphInIdentifier := true
-	    ]
-	"/ ]
+        "/ didWarnAboutParagraphInIdentifier ifFalse:[
+            parserFlags warnParagraphInIdentifier ifTrue:[
+                self
+                    warning:'§-characters in identifiers/symbols are nonportable'
+                    doNotShowAgainAction:[ ParserFlags warnParagraphInIdentifier:false ]
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                parserFlags := parserFlags copy.
+                parserFlags warnParagraphInIdentifier:false.
+                "/ didWarnAboutParagraphInIdentifier := true
+            ]
+        "/ ]
     ]
 
     "Created: / 17-11-2016 / 09:16:22 / cg"
@@ -1902,18 +1902,18 @@
     "warn about a period in an identifier"
 
     ignoreWarnings ifFalse:[
-	didWarnAboutPeriodInSymbol ifFalse:[
-	    parserFlags warnAboutPeriodInSymbol ifTrue:[
-		self
-		    warning:'Period in symbols are nonportable'
-		    doNotShowAgainAction:[ ParserFlags warnAboutPeriodInSymbol:false ]
-		    position:position to:position.
-		"
-		 only warn once (per method)
-		"
-		didWarnAboutPeriodInSymbol := true
-	    ]
-	]
+        didWarnAboutPeriodInSymbol ifFalse:[
+            parserFlags warnAboutPeriodInSymbol ifTrue:[
+                self
+                    warning:'Period in symbols are nonportable'
+                    doNotShowAgainAction:[ ParserFlags warnAboutPeriodInSymbol:false ]
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                didWarnAboutPeriodInSymbol := true
+            ]
+        ]
     ]
 !
 
@@ -1921,13 +1921,13 @@
     "warn about a possible incompatibility with other ST systems"
 
     ignoreWarnings ifFalse:[
-	parserFlags warnPossibleIncompatibilities ifTrue:[
-	    self
-		warning:('Possible incompatibility.\\' , msg) withCRs
-		doNotShowAgainAction:[ ParserFlags warnPossibleIncompatibilities:false.
-				       parserFlags warnPossibleIncompatibilities:false ]
-		position:pos1 to:pos2.
-	]
+        parserFlags warnPossibleIncompatibilities ifTrue:[
+            self
+                warning:('Possible incompatibility.\\' , msg) withCRs
+                doNotShowAgainAction:[ ParserFlags warnPossibleIncompatibilities:false.
+                                       parserFlags warnPossibleIncompatibilities:false ]
+                position:pos1 to:pos2.
+        ]
     ]
 
     "Created: 23.5.1997 / 12:17:54 / cg"
@@ -1936,20 +1936,20 @@
 
 warnSTXSpecialCommentAt:position to:endPosition
     ignoreWarnings ifFalse:[
-	"/ dfo
-	didWarnAboutSTXSpecialComment ifFalse:[
-	    parserFlags warnSTXSpecialComment ifTrue:[
-		self
-		    warning:'End-of-line comments are a nonstandard feature of ST/X'
-		    doNotShowAgainAction:[ parserFlags warnSTXSpecialComment:false. ParserFlags warnSTXSpecials:false. ]
-		    doNotShowAgainForThisMethodAction: [ self disableWarningsOnCurrentMethodFor: #warnSTXSpecials ]
-		    position:position to:endPosition.
-		"
-		 only warn once
-		"
-		didWarnAboutSTXSpecialComment := true
-	    ]
-	]
+        "/ dfo
+        didWarnAboutSTXSpecialComment ifFalse:[
+            parserFlags warnSTXSpecialComment ifTrue:[
+                self
+                    warning:'End-of-line comments are a nonstandard feature of ST/X'
+                    doNotShowAgainAction:[ parserFlags warnSTXSpecialComment:false. ParserFlags warnSTXSpecials:false. ]
+                    doNotShowAgainForThisMethodAction: [ self disableWarningsOnCurrentMethodFor: #warnSTXSpecials ]
+                    position:position to:endPosition.
+                "
+                 only warn once
+                "
+                didWarnAboutSTXSpecialComment := true
+            ]
+        ]
     ].
 
     "Modified: / 16-03-2012 / 18:37:11 / cg"
@@ -1959,18 +1959,18 @@
     "warn about an underscore in an identifier"
 
     ignoreWarnings ifFalse:[
-	didWarnAboutUnderscoreInIdentifier ifFalse:[
-	    parserFlags warnUnderscoreInIdentifier ifTrue:[
-		self
-		    warning:'Underscores in identifiers/symbols are nonportable'
-		    doNotShowAgainAction:[ ParserFlags warnUnderscoreInIdentifier:false ]
-		    position:position to:position.
-		"
-		 only warn once (per method)
-		"
-		didWarnAboutUnderscoreInIdentifier := true
-	    ]
-	]
+        didWarnAboutUnderscoreInIdentifier ifFalse:[
+            parserFlags warnUnderscoreInIdentifier ifTrue:[
+                self
+                    warning:'Underscores in identifiers/symbols are nonportable'
+                    doNotShowAgainAction:[ ParserFlags warnUnderscoreInIdentifier:false ]
+                    position:position to:position.
+                "
+                 only warn once (per method)
+                "
+                didWarnAboutUnderscoreInIdentifier := true
+            ]
+        ]
     ]
 
     "Modified: 23.5.1997 / 12:17:06 / cg"
@@ -1986,10 +1986,10 @@
     "a warning"
 
     ^ self
-	notifyWarning:((self warningMessagePrefix) , ' ' , aMessage)
-	doNotShowAgainAction:doNotShowAgainAction
-	doNotShowAgainForThisMethodAction:doNotShowAgainForThisMethodAction
-	position:position to:endPos
+        notifyWarning:((self warningMessagePrefix) , ' ' , aMessage)
+        doNotShowAgainAction:doNotShowAgainAction
+        doNotShowAgainForThisMethodAction:doNotShowAgainForThisMethodAction
+        position:position to:endPos
 
     "Created: / 28-02-2012 / 08:38:16 / cg"
 !
@@ -1998,10 +1998,10 @@
     "a warning"
 
     ^ self
-	warning:aMessage
-	doNotShowAgainAction:doNotShowAgainAction
-	doNotShowAgainForThisMethodAction:nil
-	position:position to:endPos
+        warning:aMessage
+        doNotShowAgainAction:doNotShowAgainAction
+        doNotShowAgainForThisMethodAction:nil
+        position:position to:endPos
 
     "Modified: / 28-02-2012 / 08:43:00 / cg"
 !
@@ -2027,9 +2027,9 @@
     "a warning"
 
     ^ self
-	notifyWarning:((self warningMessagePrefix) , ' ' , aMessage)
-	doNotShowAgainAction:nil
-	position:position to:endPos
+        notifyWarning:((self warningMessagePrefix) , ' ' , aMessage)
+        doNotShowAgainAction:nil
+        position:position to:endPos
 !
 
 warningMessagePrefix
@@ -2088,8 +2088,7 @@
             posAfter := posAfter - 1
         ].
         tokenValue isInteger ifTrue:[
-            source skipSeparators.
-            source peekOrNil == $/ ifTrue:[
+            source skipSeparators == $/ ifTrue:[
                 numerator := tokenValue.
                 self nextToken. "/ skip /
                 "/ oops - must check for //
@@ -2145,6 +2144,7 @@
     "Created: / 18-06-1998 / 23:05:22 / cg"
     "Modified: / 19-11-1999 / 18:25:52 / cg"
     "Modified (comment): / 23-05-2019 / 11:06:51 / Claus Gittinger"
+    "Modified: / 28-09-2019 / 15:21:32 / Stefan Vogel"
 !
 
 scanPositionsFor:aTokenString inString:aSourceString
@@ -2155,14 +2155,14 @@
     |searchType searchName searchValue positions t|
 
     aTokenString notNil ifTrue:[
-	"
-	 first, look what kind of token we have to search for
-	"
-	self initializeFor:(ReadStream on:aTokenString).
-	self nextToken.
-	searchType := tokenType.
-	searchName := tokenName.
-	searchValue := tokenValue.
+        "
+         first, look what kind of token we have to search for
+        "
+        self initializeFor:(ReadStream on:aTokenString).
+        self nextToken.
+        searchType := tokenType.
+        searchName := tokenName.
+        searchValue := tokenValue.
     ].
 
     "
@@ -2172,13 +2172,13 @@
     positions := OrderedCollection new.
 
     [(t := self nextToken) ~~ #EOF] whileTrue:[
-	searchType == t ifTrue:[
-	    (searchName isNil or:[tokenName = searchName]) ifTrue:[
-		(searchValue isNil or:[tokenValue = searchValue]) ifTrue:[
-		    positions add:tokenPosition.
-		]
-	    ]
-	]
+        searchType == t ifTrue:[
+            (searchName isNil or:[tokenName = searchName]) ifTrue:[
+                (searchValue isNil or:[tokenValue = searchValue]) ifTrue:[
+                    positions add:tokenPosition.
+                ]
+            ]
+        ]
     ].
 
     ^ positions
@@ -2243,8 +2243,8 @@
     "initialize the new scanner & prepare for reading from aStringOrStream"
 
     actionArray isNil ifTrue:[
-	"/ if not already initialized...
-	self initialize.
+        "/ if not already initialized...
+        self initialize.
     ].
     self source:aStringOrStream.
 
@@ -2308,7 +2308,7 @@
      one token too many"
 
     (tokenType == #EOF) ifFalse:[
-	source position:tokenPosition-1
+        source position:tokenPosition-1
     ]
 !
 
@@ -2344,18 +2344,18 @@
 
     firstChar := string at:1.
     (firstChar == $s) ifTrue:[
-	(string = 'self')  ifTrue:[tokenType := #Self. ^true].
-	(string = 'super') ifTrue:[tokenType := #Super. ^true]
+        (string = 'self')  ifTrue:[tokenType := #Self. ^true].
+        (string = 'super') ifTrue:[tokenType := #Super. ^true]
     ].
     (firstChar == $n) ifTrue:[
-	(string = 'nil') ifTrue:[tokenType := #Nil. tokenValue := nil. ^true]
+        (string = 'nil') ifTrue:[tokenType := #Nil. tokenValue := nil. ^true]
     ].
     (firstChar == $t) ifTrue:[
-	(string = 'true') ifTrue:[tokenType := #True. tokenValue := true. ^true].
-	(string = 'thisContext') ifTrue:[tokenType := #ThisContext. ^true]
+        (string = 'true') ifTrue:[tokenType := #True. tokenValue := true. ^true].
+        (string = 'thisContext') ifTrue:[tokenType := #ThisContext. ^true]
     ].
     (firstChar == $f) ifTrue:[
-	(string = 'false') ifTrue:[tokenType := #False. tokenValue := false. ^true]
+        (string = 'false') ifTrue:[tokenType := #False. tokenValue := false. ^true]
     ].
     ^ false
 
@@ -2368,9 +2368,9 @@
 
 eatPeekChar
     peekChar isNil ifTrue:[
-	source next.
+        source next.
     ] ifFalse:[
-	peekChar := nil.
+        peekChar := nil.
     ].
 
     "Created: / 24.10.1998 / 17:25:39 / cg"
@@ -2378,11 +2378,11 @@
 
 endComment:comment
     saveComments ifTrue:[
-	currentComments isNil ifTrue:[
-	    currentComments := OrderedCollection with:comment
-	] ifFalse:[
-	    currentComments add:comment
-	]
+        currentComments isNil ifTrue:[
+            currentComments := OrderedCollection with:comment
+        ] ifFalse:[
+            currentComments add:comment
+        ]
     ].
 !
 
@@ -2396,14 +2396,14 @@
     |comment|
 
     saveComments ifTrue:[
-	comment := Comment new commentString:commentString commentType:commentType.
-	comment startPosition:startPos endPosition:endPos.
-
-	currentComments isNil ifTrue:[
-	    currentComments := OrderedCollection with:comment
-	] ifFalse:[
-	    currentComments add:comment
-	]
+        comment := Comment new commentString:commentString commentType:commentType.
+        comment startPosition:startPos endPosition:endPos.
+
+        currentComments isNil ifTrue:[
+            currentComments := OrderedCollection with:comment
+        ] ifFalse:[
+            currentComments add:comment
+        ]
     ].
 
     "Created: / 17.2.1998 / 14:48:49 / cg"
@@ -2652,11 +2652,11 @@
     source next.
     nextChar := source next.
     nextChar notNil ifTrue:[
-	t := nextChar.
-	tokenType := #Character.
+        t := nextChar.
+        tokenType := #Character.
     ] ifFalse:[
-	t := nil.
-	tokenType := #EOF
+        t := nil.
+        tokenType := #EOF
     ].
     tokenValue := token := t.
     ^ tokenType
@@ -2673,35 +2673,35 @@
     "/ here we needed two characters lookahead after the identifier ...
 
     peekChar == $= ifTrue:[
-	source next.
-	peekChar := nil.
-	tokenType := token := #':='.
-
-	thirdChar := source peek.
-	thirdChar notNil ifTrue:[
-	    (self isSpecialOrExtendedSpecialCharacter:thirdChar) ifTrue:[
-
-	    ]
-	].
-
-	^ tokenType
+        source next.
+        peekChar := nil.
+        tokenType := token := #':='.
+
+        thirdChar := source peek.
+        thirdChar notNil ifTrue:[
+            (self isSpecialOrExtendedSpecialCharacter:thirdChar) ifTrue:[
+
+            ]
+        ].
+
+        ^ tokenType
     ].
 
     "/ special kludge for nameSpace:: (without spaces inbetween)
     "/ here we needed two characters lookahead after the identifier ...
 
     peekChar == $: ifTrue:[
-	source next.
-	peekChar := nil.
-	tokenType := token := #'::'.
-	^ tokenType
+        source next.
+        peekChar := nil.
+        tokenType := token := #'::'.
+        ^ tokenType
     ].
 
     (source nextPeek == $=) ifTrue:[
-	source next.
-	tokenType := token := #':='
+        source next.
+        tokenType := token := #':='
     ] ifFalse:[
-	tokenType := token := $:
+        tokenType := token := $:
     ].
     ^ tokenType
 
@@ -2710,36 +2710,36 @@
 
 nextExcla
     "a !! has been read - return either
-	the !! binarySelector,
-	ExclaLeftParen     (for '!!('),
-	ExclaLeftBrack     (for '!!['),
-	ExclaLeftBrace     (for '!!{')
+        the !! binarySelector,
+        ExclaLeftParen     (for '!!('),
+        ExclaLeftBrack     (for '!!['),
+        ExclaLeftBrace     (for '!!{')
     "
 
     |nextChar|
 
     nextChar := source nextPeek.
     parserFlags allowExtendedSTXSyntax == true ifTrue:[
-	(nextChar == $( ) ifTrue:[
-	    source next.
-	    token := '!!('.
-	    tokenType := #ExclaLeftParen.
-	    ^ tokenType
-	].
-
-	(nextChar == $[ ) ifTrue:[
-	    source next.
-	    token := '!!['.
-	    tokenType := #ExclaLeftBrack.
-	    ^ tokenType
-	].
-
-	(nextChar == ${ ) ifTrue:[
-	    source next.
-	    token := '!!{'.
-	    tokenType := #ExclaLeftBrace.
-	    ^ tokenType
-	].
+        (nextChar == $( ) ifTrue:[
+            source next.
+            token := '!!('.
+            tokenType := #ExclaLeftParen.
+            ^ tokenType
+        ].
+
+        (nextChar == $[ ) ifTrue:[
+            source next.
+            token := '!!['.
+            tokenType := #ExclaLeftBrack.
+            ^ tokenType
+        ].
+
+        (nextChar == ${ ) ifTrue:[
+            source next.
+            token := '!!{'.
+            tokenType := #ExclaLeftBrace.
+            ^ tokenType
+        ].
     ].
 
     "this allows excla to be used as binop -
@@ -2754,7 +2754,7 @@
 
 nextExtendedSpecial:ch
     parserFlags allowExtendedBinarySelectors ifTrue:[
-	^ self nextSpecial
+        ^ self nextSpecial
     ].
     ^ self invalidCharacter:source peek.
 !
@@ -2951,18 +2951,18 @@
     index := 0.
     max := 10.
     [
-	(nextChar notNil and:[nextChar isLetterOrDigit]) ifFalse:[
-	    ^ string copyTo:index
-	].
-	(index == max) ifTrue:[
-	    oldString := string.
-	    string := String basicNew:(max * 2).
-	    string replaceFrom:1 to:max with:oldString.
-	    max := max * 2
-	].
-	index := index + 1.
-	string at:index put:nextChar.
-	nextChar := source nextPeek
+        (nextChar notNil and:[nextChar isLetterOrDigit]) ifFalse:[
+            ^ string copyTo:index
+        ].
+        (index == max) ifTrue:[
+            oldString := string.
+            string := String basicNew:(max * 2).
+            string replaceFrom:1 to:max with:oldString.
+            max := max * 2
+        ].
+        index := index + 1.
+        string at:index put:nextChar.
+        nextChar := source nextPeek
     ] loop.
 
     "Modified: / 5.3.1998 / 02:53:57 / cg"
@@ -3367,28 +3367,28 @@
 
     nextChar := source nextPeek.
     (nextChar == ${) ifFalse:[
-	^ self nextSpecialWith:$%
+        ^ self nextSpecialWith:$%
     ].
 
     stringCollector := CharacterWriteStream new.
     nextChar := source nextPeek.
     inPrimitive := true.
     [inPrimitive] whileTrue:[
-	[nextChar == $%] whileFalse:[
-	    nextChar isNil ifTrue:[
-		self syntaxError:'unterminated primitive'
-			position:tokenPosition to:source position + 1.
-		^ #Error
-	    ].
-	    stringCollector nextPut:nextChar.
-	    nextChar := source next
-	].
-	(source peekOrNil == $}) ifTrue:[
-	    inPrimitive := false
-	] ifFalse:[
-	    stringCollector nextPut:nextChar.
-	    nextChar := source next
-	]
+        [nextChar == $%] whileFalse:[
+            nextChar isNil ifTrue:[
+                self syntaxError:'unterminated primitive'
+                        position:tokenPosition to:source position + 1.
+                ^ #Error
+            ].
+            stringCollector nextPut:nextChar.
+            nextChar := source next
+        ].
+        (source peekOrNil == $}) ifTrue:[
+            inPrimitive := false
+        ] ifFalse:[
+            stringCollector nextPut:nextChar.
+            nextChar := source next
+        ]
     ].
     source next.
     tokenValue := token := stringCollector contents.
@@ -3415,79 +3415,79 @@
 
     secondChar := source peekOrNil.
     ((firstChar == $-) and:[secondChar notNil]) ifTrue:[
-	secondChar isDigit ifTrue:[
-	    self nextNumber.
-	    tokenValue := token := tokenValue negated.
-	    ^ tokenType
-	]
+        secondChar isDigit ifTrue:[
+            self nextNumber.
+            tokenValue := token := tokenValue negated.
+            ^ tokenType
+        ]
     ].
     string := firstChar asString.
 
     "/ changed: do not allow second char to be a hash
     "/ unless the first is also.
     secondChar == $# ifTrue:[
-	(parserFlags allowHashAsBinarySelector
-	and:[firstChar == $#]) ifFalse:[
-	    tokenName := token := string.
-	    tokenType := #BinaryOperator.
-	    ^ tokenType
-	].
+        (parserFlags allowHashAsBinarySelector
+        and:[firstChar == $#]) ifFalse:[
+            tokenName := token := string.
+            tokenType := #BinaryOperator.
+            ^ tokenType
+        ].
     ].
 
     secondChar notNil ifTrue:[
-	(secondChar == $-) ifTrue:[
-	    "special- look if minus belongs to number following"
-	    p := source position.
-	    source next.
-	    thirdChar := source peekOrNil.
-	    source position:p.
-	    (thirdChar notNil and:[thirdChar isDigit]) ifTrue:[
-		tokenName := token := string.
-		tokenType := #BinaryOperator.
-		self
-		    warnPossibleIncompatibility:'add a space before ''-'' for compatibility with stc and other ST systems'
-		    position:p+1
-		    to:p+1.
-		^ tokenType
-	    ]
-	].
-	(self isSpecialOrExtendedSpecialCharacter:secondChar) ifTrue:[
-	    source next.
-	    string := string copyWith:secondChar.
-
-	    thirdChar := source peekOrNil.
-	    thirdChar notNil ifTrue:[
-		(self isSpecialOrExtendedSpecialCharacter:thirdChar) ifTrue:[
-		    p := source position.
-		    source next.
-		    fourthChar := source peekOrNil.
-		    source position:p.
-
-		    (thirdChar == $-) ifTrue:[
-			"special- look if minus belongs to number following"
-			(fourthChar notNil and:[fourthChar isDigit]) ifTrue:[
-			    tokenName := token := string.
-			    tokenType := #BinaryOperator.
-			    self
-				warnPossibleIncompatibility:'add a space before ''-'' for compatibility with stc and other ST systems'
-				position:p+1
-				to:p+1.
-			    ^ tokenType
-			].
-		    ].
-		    thirdChar == $# ifTrue:[
-			(fourthChar notNil and:[fourthChar isSeparator]) ifFalse:[
-			    "/ in sth. like ->#foo, the binop is NOT ->#
-			    tokenName := token := string.
-			    tokenType := #BinaryOperator.
-			    ^ tokenType
-			].
-		    ].
-		    source next.
-		    string := string copyWith:thirdChar.
-		].
-	    ].
-	].
+        (secondChar == $-) ifTrue:[
+            "special- look if minus belongs to number following"
+            p := source position.
+            source next.
+            thirdChar := source peekOrNil.
+            source position:p.
+            (thirdChar notNil and:[thirdChar isDigit]) ifTrue:[
+                tokenName := token := string.
+                tokenType := #BinaryOperator.
+                self
+                    warnPossibleIncompatibility:'add a space before ''-'' for compatibility with stc and other ST systems'
+                    position:p+1
+                    to:p+1.
+                ^ tokenType
+            ]
+        ].
+        (self isSpecialOrExtendedSpecialCharacter:secondChar) ifTrue:[
+            source next.
+            string := string copyWith:secondChar.
+
+            thirdChar := source peekOrNil.
+            thirdChar notNil ifTrue:[
+                (self isSpecialOrExtendedSpecialCharacter:thirdChar) ifTrue:[
+                    p := source position.
+                    source next.
+                    fourthChar := source peekOrNil.
+                    source position:p.
+
+                    (thirdChar == $-) ifTrue:[
+                        "special- look if minus belongs to number following"
+                        (fourthChar notNil and:[fourthChar isDigit]) ifTrue:[
+                            tokenName := token := string.
+                            tokenType := #BinaryOperator.
+                            self
+                                warnPossibleIncompatibility:'add a space before ''-'' for compatibility with stc and other ST systems'
+                                position:p+1
+                                to:p+1.
+                            ^ tokenType
+                        ].
+                    ].
+                    thirdChar == $# ifTrue:[
+                        (fourthChar notNil and:[fourthChar isSeparator]) ifFalse:[
+                            "/ in sth. like ->#foo, the binop is NOT ->#
+                            tokenName := token := string.
+                            tokenType := #BinaryOperator.
+                            ^ tokenType
+                        ].
+                    ].
+                    source next.
+                    string := string copyWith:thirdChar.
+                ].
+            ].
+        ].
     ].
     tokenName := token := string.
     tokenType := #BinaryOperator.
@@ -3587,88 +3587,88 @@
     isNameSpaceSymbol := false.
 
     prefix isEmpty ifTrue:[
-	nextChar isLetter ifFalse:[
-	    ((nextChar == $_) and:[allowUnderscoreInIdentifier]) ifFalse:[
-		((nextChar == $.) and:[allowPeriodInSymbol]) ifFalse:[
-		    (nextChar isDigit and:[parserFlags allowSymbolsStartingWithDigit]) ifFalse:[
-			"/ just for the better error message
-			(nextChar isNationalAlphaNumeric) ifTrue:[
-			    |errMsg|
-
-			    errMsg := 'Invalid character: ''' , nextChar asString , ''' ', '(' , (nextChar codePoint radixPrintStringRadix:16) , ').'.
-			    errMsg := errMsg , '\\Notice:\  Only 7-bit ascii allowed (for compatibility with other Smalltalk dialects).' withCRs.
-			    errMsg := errMsg , '\  If you need symbols with 8-bit characters, use the #''...'' form, or ''...'' asSymbol.' withCRs.
-			    self syntaxError:errMsg position:tokenPosition to:source position+1.
-			].
-			^ nil
-		    ]
-		]
-	    ]
-	].
+        nextChar isLetter ifFalse:[
+            ((nextChar == $_) and:[allowUnderscoreInIdentifier]) ifFalse:[
+                ((nextChar == $.) and:[allowPeriodInSymbol]) ifFalse:[
+                    (nextChar isDigit and:[parserFlags allowSymbolsStartingWithDigit]) ifFalse:[
+                        "/ just for the better error message
+                        (nextChar isNationalAlphaNumeric) ifTrue:[
+                            |errMsg|
+
+                            errMsg := 'Invalid character: ''' , nextChar asString , ''' ', '(' , (nextChar codePoint radixPrintStringRadix:16) , ').'.
+                            errMsg := errMsg , '\\Notice:\  Only 7-bit ascii allowed (for compatibility with other Smalltalk dialects).' withCRs.
+                            errMsg := errMsg , '\  If you need symbols with 8-bit characters, use the #''...'' form, or ''...'' asSymbol.' withCRs.
+                            self syntaxError:errMsg position:tokenPosition to:source position+1.
+                        ].
+                        ^ nil
+                    ]
+                ]
+            ]
+        ].
     ].
 
     string := prefix.
     [
-	nextChar notNil
-	and:[nextChar isLetterOrDigit
-	    or:[(nextChar == $_ and:[allowUnderscoreInIdentifier])
-	    or:[nextChar == $. and:[allowPeriodInSymbol and:[source peek isLetter]]]]
-	 ]
+        nextChar notNil
+        and:[nextChar isLetterOrDigit
+            or:[(nextChar == $_ and:[allowUnderscoreInIdentifier])
+            or:[nextChar == $. and:[allowPeriodInSymbol and:[source peek isLetter]]]]
+         ]
     ] whileTrue:[
-	nextChar == $_ ifTrue:[
-	    part := nil.
-	] ifFalse:[
-	    (allowPeriodInSymbol and:[nextChar == $.]) ifTrue:[
-		part := nil.
-	    ] ifFalse:[
-		part := source nextAlphaNumericWord.
-	    ]
-	].
-	part notNil ifTrue:[
-	    string := string , part.
-	].
-	nextChar := source peek.
-
-	((allowUnderscoreInIdentifier and:[nextChar == $_])
-	or:[ allowPeriodInSymbol and:[nextChar == $.] ]) ifTrue:[
-	    nextChar == $_ ifTrue:[
-		self warnUnderscoreAt:source position + 1.
-	    ] ifFalse:[
-		self warnPeriodAt:source position + 1.
-	    ].
-	    [(nextChar == $_) or:[(allowPeriodInSymbol and:[nextChar == $.])]] whileTrue:[
-		string := string copyWith:nextChar.
-		nextChar := source nextPeek.
-		(nextChar notNil and:[nextChar isLetterOrDigit]) ifTrue:[
-		    string := string , source nextAlphaNumericWord.
-		    nextChar := source peek.
-		] ifFalse:[
-		    (allowPeriodInSymbol and:[string last == $.]) ifTrue:[
-			peekChar := nextChar.
-			nextChar := $..
-			string := string copyButLast:1.
-			tokenValue := token := string asSymbol.
-			tokenType := #Symbol.
-			^ tokenType
-		    ].
-		].
-	    ].
-	].
-	(nextChar == $:) ifFalse:[
-	    self markSymbolFrom:tokenPosition to:(source position).
-	    tokenValue := token := string asSymbol.
-	    tokenType := #Symbol.
-	    ^ tokenType
-	].
-	string := string copyWith:nextChar.
-	nextChar := source nextPeek.
-	parserFlags allowLiteralNameSpaceSymbols ifTrue:[
-	    (nextChar == $:) ifTrue:[
-		string := string copyWith:nextChar.
-		nextChar := source nextPeek.
-		isNameSpaceSymbol := true.
-	    ].
-	].
+        nextChar == $_ ifTrue:[
+            part := nil.
+        ] ifFalse:[
+            (allowPeriodInSymbol and:[nextChar == $.]) ifTrue:[
+                part := nil.
+            ] ifFalse:[
+                part := source nextAlphaNumericWord.
+            ]
+        ].
+        part notNil ifTrue:[
+            string := string , part.
+        ].
+        nextChar := source peek.
+
+        ((allowUnderscoreInIdentifier and:[nextChar == $_])
+        or:[ allowPeriodInSymbol and:[nextChar == $.] ]) ifTrue:[
+            nextChar == $_ ifTrue:[
+                self warnUnderscoreAt:source position + 1.
+            ] ifFalse:[
+                self warnPeriodAt:source position + 1.
+            ].
+            [(nextChar == $_) or:[(allowPeriodInSymbol and:[nextChar == $.])]] whileTrue:[
+                string := string copyWith:nextChar.
+                nextChar := source nextPeek.
+                (nextChar notNil and:[nextChar isLetterOrDigit]) ifTrue:[
+                    string := string , source nextAlphaNumericWord.
+                    nextChar := source peek.
+                ] ifFalse:[
+                    (allowPeriodInSymbol and:[string last == $.]) ifTrue:[
+                        peekChar := nextChar.
+                        nextChar := $..
+                        string := string copyButLast:1.
+                        tokenValue := token := string asSymbol.
+                        tokenType := #Symbol.
+                        ^ tokenType
+                    ].
+                ].
+            ].
+        ].
+        (nextChar == $:) ifFalse:[
+            self markSymbolFrom:tokenPosition to:(source position).
+            tokenValue := token := string asSymbol.
+            tokenType := #Symbol.
+            ^ tokenType
+        ].
+        string := string copyWith:nextChar.
+        nextChar := source nextPeek.
+        parserFlags allowLiteralNameSpaceSymbols ifTrue:[
+            (nextChar == $:) ifTrue:[
+                string := string copyWith:nextChar.
+                nextChar := source nextPeek.
+                isNameSpaceSymbol := true.
+            ].
+        ].
     ].
     tokenValue := token := string asSymbol.
     tokenType := #Symbol.
@@ -3848,7 +3848,7 @@
     "return either an identifier, or an underline (sometimes an assignment)  token"
 
     parserFlags allowUnderscoreInIdentifier ifTrue:[
-	^ self nextIdentifier
+        ^ self nextIdentifier
     ].
     ^ self nextToken:$_
 !
@@ -4036,14 +4036,14 @@
 
 skipToEndOfLineRememberingIn:commentStreamOrNil
     [hereChar notNil and:[hereChar ~~ Character cr]] whileTrue:[
-	commentStreamOrNil notNil ifTrue:[
-	    commentStreamOrNil nextPut:hereChar
-	].
-	outStream notNil ifTrue:[
-	    outStream nextPut:hereChar.
-	    outCol := outCol + 1
-	].
-	hereChar := source nextPeek.
+        commentStreamOrNil notNil ifTrue:[
+            commentStreamOrNil nextPut:hereChar
+        ].
+        outStream notNil ifTrue:[
+            outStream nextPut:hereChar.
+            outCol := outCol + 1
+        ].
+        hereChar := source nextPeek.
     ].
     lineNr := lineNr + 1.
 !