Parser.st
changeset 3267 2ecb618c908e
parent 3244 ecc2c6e3e7c4
child 3271 63e8a42d3dd7
--- a/Parser.st	Sat Aug 10 13:22:26 2013 +0200
+++ b/Parser.st	Sat Aug 10 13:23:29 2013 +0200
@@ -2271,21 +2271,21 @@
     self shouldPerformCodingStyleChecks ifFalse:[^ self ].
 
     aVariableName isUppercaseFirst ifTrue:[
-	msg := ('variable "' , aVariableName , '" should be lowercase (by convention)').
-	self
-	    warning:msg
-	    doNotShowAgainAction:[ ParserFlags warnAboutNonLowercaseLocalVariableNames:false.
-				   parserFlags warnAboutNonLowercaseLocalVariableNames:false.]
-	    position:tokenPosition to:source position1Based - 1.
-
-	Tools::ToDoListBrowser notNil ifTrue:[
-	    self
-		notifyTodo:msg position:tokenPosition
-		className:(self classToCompileFor name) selector:selector
-		severity:#warning priority:#medium
-		equalityParameter:nil
-		checkAction:nil.
-	].
+        msg := ('variable "' , aVariableName , '" should be lowercase (by convention)').
+        self
+            warning:msg
+            doNotShowAgainAction:[ ParserFlags warnAboutNonLowercaseLocalVariableNames:false.
+                                   parserFlags warnAboutNonLowercaseLocalVariableNames:false.]
+            position:tokenPosition to:source position.
+
+        Tools::ToDoListBrowser notNil ifTrue:[
+            self
+                notifyTodo:msg position:tokenPosition
+                className:(self classToCompileFor name) selector:selector
+                severity:#warning priority:#medium
+                equalityParameter:nil
+                checkAction:nil.
+        ].
     ].
 
     "Modified: / 18-10-2006 / 19:38:20 / cg"
@@ -2299,107 +2299,107 @@
     self shouldPerformCodingStyleChecks ifFalse:[^ self ].
 
     soundsLikeVowel := [:word |
-	|soundsLikeVowel firstCharacter|
-
-	soundsLikeVowel := false.
-	firstCharacter := word first.
-	('AEIX' includes:firstCharacter) ifTrue:[
-	    soundsLikeVowel := true.
-	] ifFalse:[
-	    firstCharacter := word first.
-	    "/ U and H sound like a vowel, if followed by two more non-vowels
-
-	    ('UH' includes:firstCharacter) ifTrue:[
-		word size > 2 ifTrue:[
-		    (word at:2) isVowel ifFalse:[
-			(word at:3) isVowel ifFalse:[
-			    soundsLikeVowel := true.
-			].
-		    ].
-		].
-	    ].
-	    "/ R sound like a vowel, if followed by a consonant
-	    ('R' includes:firstCharacter) ifTrue:[
-		word size > 2 ifTrue:[
-		    (word at:2) isVowel ifFalse:[
-			soundsLikeVowel := true.
-		    ].
-		].
-	    ].
-	    "/ O sound like a vowel, if not followed by 'ne'
-	    ('O' includes:firstCharacter) ifTrue:[
-		word size > 2 ifTrue:[
-		    (word copyTo:3) asLowercase = 'one' ifFalse:[
-			soundsLikeVowel := true.
-		    ].
-		].
-	    ].
-	    "/ S sounds like a vowel, if followed by UC-consonant followed by vocal
-	    "/ aSBrowser -> anSBrowser
-	    ('S' includes:firstCharacter) ifTrue:[
-		word size > 3 ifTrue:[
-		    ((word at:2) isVowel not
-		    and:[ (word at:2) isUppercase
-		    and:[ (word at:3) isVowel]]) ifTrue:[
-			soundsLikeVowel := true.
-		    ].
-		].
-	    ].
-	    "/ M sounds like a vowel, if followed by UC-consonant followed by consonant
-	    "/ anMC  aMA
-	    ('MN' includes:firstCharacter) ifTrue:[
-		word size > 2 ifTrue:[
-		    ((word at:2) isVowel not
-		    and:[ (word at:2) isUppercase
-		    and:[ (word at:3) isVowel not]]) ifTrue:[
-			soundsLikeVowel := true.
-		    ].
-		].
-	    ].
-	].
-	soundsLikeVowel.
+        |soundsLikeVowel firstCharacter|
+
+        soundsLikeVowel := false.
+        firstCharacter := word first.
+        ('AEIX' includes:firstCharacter) ifTrue:[
+            soundsLikeVowel := true.
+        ] ifFalse:[
+            firstCharacter := word first.
+            "/ U and H sound like a vowel, if followed by two more non-vowels
+
+            ('UH' includes:firstCharacter) ifTrue:[
+                word size > 2 ifTrue:[
+                    (word at:2) isVowel ifFalse:[
+                        (word at:3) isVowel ifFalse:[
+                            soundsLikeVowel := true.
+                        ].
+                    ].
+                ].
+            ].
+            "/ R sound like a vowel, if followed by a consonant
+            ('R' includes:firstCharacter) ifTrue:[
+                word size > 2 ifTrue:[
+                    (word at:2) isVowel ifFalse:[
+                        soundsLikeVowel := true.
+                    ].
+                ].
+            ].
+            "/ O sound like a vowel, if not followed by 'ne'
+            ('O' includes:firstCharacter) ifTrue:[
+                word size > 2 ifTrue:[
+                    (word copyTo:3) asLowercase = 'one' ifFalse:[
+                        soundsLikeVowel := true.
+                    ].
+                ].
+            ].
+            "/ S sounds like a vowel, if followed by UC-consonant followed by vocal
+            "/ aSBrowser -> anSBrowser
+            ('S' includes:firstCharacter) ifTrue:[
+                word size > 3 ifTrue:[
+                    ((word at:2) isVowel not
+                    and:[ (word at:2) isUppercase
+                    and:[ (word at:3) isVowel]]) ifTrue:[
+                        soundsLikeVowel := true.
+                    ].
+                ].
+            ].
+            "/ M sounds like a vowel, if followed by UC-consonant followed by consonant
+            "/ anMC  aMA
+            ('MN' includes:firstCharacter) ifTrue:[
+                word size > 2 ifTrue:[
+                    ((word at:2) isVowel not
+                    and:[ (word at:2) isUppercase
+                    and:[ (word at:3) isVowel not]]) ifTrue:[
+                        soundsLikeVowel := true.
+                    ].
+                ].
+            ].
+        ].
+        soundsLikeVowel.
     ].
 
     aVariableName size > 4 ifTrue:[
-	(aVariableName startsWith:'an') ifTrue:[
-	    firstCharacterAfterArticle := aVariableName at:3.
-	    firstCharacterAfterArticle isUppercase ifTrue:[
-		rest := aVariableName copyFrom:3.
-		(soundsLikeVowel value:rest) ifFalse:[
-		    whatShouldItBeNamed := 'a' , rest.
-		]
-	    ].
-	] ifFalse:[
-	    (aVariableName startsWith:'a') ifTrue:[
-		firstCharacterAfterArticle := aVariableName at:2.
-		firstCharacterAfterArticle isUppercase ifTrue:[
-		    rest := aVariableName copyFrom:2.
-		    (soundsLikeVowel value:rest) ifTrue:[
-			whatShouldItBeNamed := 'an' , rest.
-		    ].
-		].
-	    ].
-	].
-	whatShouldItBeNamed notNil ifTrue:[
+        (aVariableName startsWith:'an') ifTrue:[
+            firstCharacterAfterArticle := aVariableName at:3.
+            firstCharacterAfterArticle isUppercase ifTrue:[
+                rest := aVariableName copyFrom:3.
+                (soundsLikeVowel value:rest) ifFalse:[
+                    whatShouldItBeNamed := 'a' , rest.
+                ]
+            ].
+        ] ifFalse:[
+            (aVariableName startsWith:'a') ifTrue:[
+                firstCharacterAfterArticle := aVariableName at:2.
+                firstCharacterAfterArticle isUppercase ifTrue:[
+                    rest := aVariableName copyFrom:2.
+                    (soundsLikeVowel value:rest) ifTrue:[
+                        whatShouldItBeNamed := 'an' , rest.
+                    ].
+                ].
+            ].
+        ].
+        whatShouldItBeNamed notNil ifTrue:[
 "/            self
 "/                warnCommonMistake:('variable "',aVariableName,'" should be named "',whatShouldItBeNamed,'" (by english language rules)')
 "/                position:tokenPosition to:source position1Based - 1.
-	    msg := ('variable "',aVariableName,'" should be named "',whatShouldItBeNamed,'" (by english language rules)').
-	    self
-		warning:msg
-		doNotShowAgainAction:[ parserFlags warnAboutWrongVariableNames:false. ParserFlags warnAboutWrongVariableNames:false ]
-		doNotShowAgainForThisMethodAction: [ self disableWarningsOnCurrentMethodFor: #warnAboutWrongVariableNames ]
-		position:tokenPosition to:source position1Based - 1.
-
-	    Tools::ToDoListBrowser notNil ifTrue:[
-		self
-		    notifyTodo:msg position:tokenPosition
-		    className:(self classToCompileFor name) selector:selector
-		    severity:#warning priority:#low
-		    equalityParameter:nil
-		    checkAction:nil.
-	    ].
-	].
+            msg := ('variable "',aVariableName,'" should be named "',whatShouldItBeNamed,'" (by english language rules)').
+            self
+                warning:msg
+                doNotShowAgainAction:[ parserFlags warnAboutWrongVariableNames:false. ParserFlags warnAboutWrongVariableNames:false ]
+                doNotShowAgainForThisMethodAction: [ self disableWarningsOnCurrentMethodFor: #warnAboutWrongVariableNames ]
+                position:tokenPosition to:source position.
+
+            Tools::ToDoListBrowser notNil ifTrue:[
+                self
+                    notifyTodo:msg position:tokenPosition
+                    className:(self classToCompileFor name) selector:selector
+                    severity:#warning priority:#low
+                    equalityParameter:nil
+                    checkAction:nil.
+            ].
+        ].
     ].
 
     "Modified: / 16-03-2012 / 18:36:43 / cg"
@@ -2411,37 +2411,37 @@
     self shouldPerformCodingStyleChecks ifFalse:[^ self ].
 
     parserFlags warnAboutVariableNameConventions == true ifTrue:[
-	parserFlags warnAboutNonLowercaseLocalVariableNames == true ifTrue:[
-	    self checkForLowercaseVariableName:aVariableName.
-	].
-	parserFlags warnAboutShortLocalVariableNames == true ifTrue:[
-	    aVariableName size <= 2 ifTrue:[
-		(#(
-		    'x' 'y'
-		) includes:aVariableName)
-		ifFalse:[
-		    msg := ('short variable name: "' , aVariableName , '"').
-		    self
-			warning:('short variable name: "' , aVariableName , '"')
-			doNotShowAgainAction:[ ParserFlags warnAboutShortLocalVariableNames:false]
-			position:tokenPosition to:source position1Based - 1.
-
-		    Tools::ToDoListBrowser notNil ifTrue:[
-			self
-			    notifyTodo:msg position:tokenPosition
-			    className:(self classToCompileFor name) selector:selector
-			    severity:#warning priority:#medium
-			    equalityParameter:nil
-			    checkAction:nil.
-		    ].
-		].
-	    ].
-	].
+        parserFlags warnAboutNonLowercaseLocalVariableNames == true ifTrue:[
+            self checkForLowercaseVariableName:aVariableName.
+        ].
+        parserFlags warnAboutShortLocalVariableNames == true ifTrue:[
+            aVariableName size <= 2 ifTrue:[
+                (#(
+                    'x' 'y'
+                ) includes:aVariableName)
+                ifFalse:[
+                    msg := ('short variable name: "' , aVariableName , '"').
+                    self
+                        warning:('short variable name: "' , aVariableName , '"')
+                        doNotShowAgainAction:[ ParserFlags warnAboutShortLocalVariableNames:false]
+                        position:tokenPosition to:source position.
+
+                    Tools::ToDoListBrowser notNil ifTrue:[
+                        self
+                            notifyTodo:msg position:tokenPosition
+                            className:(self classToCompileFor name) selector:selector
+                            severity:#warning priority:#medium
+                            equalityParameter:nil
+                            checkAction:nil.
+                    ].
+                ].
+            ].
+        ].
     ].
     parserFlags warnAboutWrongVariableNames == true ifTrue:[
-	(ParserFlags isFlag:#warnAboutWrongVariableNames enabledForClass:classToCompileFor selector:selector) ifTrue:[
-	    self checkForProperUseOfArticleInVariableName:aVariableName.
-	].
+        (ParserFlags isFlag:#warnAboutWrongVariableNames enabledForClass:classToCompileFor selector:selector) ifTrue:[
+            self checkForProperUseOfArticleInVariableName:aVariableName.
+        ].
     ].
 
     "Modified: / 16-03-2012 / 18:42:56 / cg"
@@ -2878,7 +2878,7 @@
     correctedSource := requestor currentSourceCode.
     "/ update the current source position
     source := (ReadStream on:correctedSource)
-		  position:(source position1Based - selectionSize).
+                  position:(source position + 1 - selectionSize).
 
     ^ nil
 
@@ -3030,19 +3030,19 @@
 
     "/ update the current source position
     source atEnd ifTrue:[
-	newPos := correctedSource size.
+        newPos := correctedSource size.
     ] ifFalse:[
-	source position1Based >= stop ifTrue:[
-	    newPos := source position1Based - deleteSize
-	] ifFalse:[
-	    source position1Based < start ifTrue:[
-		newPos := source position1Based
-	    ] ifFalse:[
-		newPos := start
-	    ].
-	]
-    ].
-    source := (ReadStream on:correctedSource) position1Based:newPos.
+        source position + 1 >= stop ifTrue:[
+            newPos := source position - deleteSize.
+        ] ifFalse:[
+            source position + 1 < start ifTrue:[
+                newPos := source position.
+            ] ifFalse:[
+                newPos := start-1.
+            ].
+        ]
+    ].
+    source := (ReadStream on:correctedSource) position:newPos.
 
     localDefsStart := localVarDefPosition at:1.
     localDefsStop := localVarDefPosition at:2.
@@ -3051,14 +3051,14 @@
     localDefsStart >= stop ifTrue:[^ self].
 
     (localDefsStart >= start and:[localDefsStop <= stop]) ifTrue:[
-	localVarDefPosition := nil.
-	^ self
+        localVarDefPosition := nil.
+        ^ self
     ].
 
     "/ must update
     (start > localDefsStart and:[stop < localDefsStop]) ifTrue:[
-	localVarDefPosition at:2 put:(localDefsStop - (stop-start+1)).
-	^ self.
+        localVarDefPosition at:2 put:(localDefsStop - (stop-start+1)).
+        ^ self.
     ].
     ^ self
 !
@@ -3167,7 +3167,7 @@
     "
     correctedSource := requestor currentSourceCode.
     source := (ReadStream on:correctedSource)
-                  position:(source position1Based + newName size - tokenName size).
+                  position:(source position + 1 + newName size - tokenName size).
 
     "redo parse with new value"
     token := tokenName := newName.
@@ -3293,7 +3293,7 @@
             ].
             correctedSource := requestor currentSourceCode asString string.
             source := (ReadStream on:correctedSource)
-                          position:(source position1Based + ins size).
+                          position:(source position + 1 + ins size).
 
             varIndex := methodVarNames size.
             var used:true.
@@ -4107,12 +4107,12 @@
     |msg|
 
     (#(True False Self Nil Super ThisContext) includes:tokenType) ifTrue:[
-	msg := 'Reserved keyword in '
+        msg := 'Reserved keyword in '
     ] ifFalse:[
-	msg := 'Identifier expected in '
+        msg := 'Identifier expected in '
     ].
     self syntaxError:(msg , what , ' (got ''' , tokenType printString, ''')')
-	 position:tokenPosition to:source position1Based - 1.
+         position:tokenPosition to:source position.
     ^ #Error
 !
 
@@ -4285,17 +4285,17 @@
 
 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
-	    ]
-	]
+        didWarnAboutSTXNameSpaceUse ifFalse:[
+            parserFlags warnSTXNameSpaceUse ifTrue:[
+                self warning:'NameSpaces are a nonstandard feature of ST/X'
+                     doNotShowAgainAction:[ ParserFlags warnSTXSpecials:false ]
+                     position:position to:(source position + 1).
+                "
+                 only warn once
+                "
+                didWarnAboutSTXNameSpaceUse := false
+            ]
+        ]
     ].
 !
 
@@ -5043,7 +5043,7 @@
     [tokenType == $] ] whileFalse:[
         (tokenType == $.) ifFalse:[
             (tokenType == #EOF) ifTrue:[
-                self syntaxError:'missing '']'' in block' position:blockStart to:(source position1Based).
+                self syntaxError:'missing '']'' in block' position:blockStart to:(source position + 1).
                 ^ #Error.
             ].
 
@@ -5091,21 +5091,21 @@
     |what msg endPos|
 
     (tokenType ~~ #EOF) ifTrue:[
-	"/ just for the nicer error message
-	(#(Self Nil True False Super Here) includes:tokenType) ifTrue:[
-	    msg := '"',tokenName allBold,'" unexpected (missing "." or ":" before ' , tokenName , ' ?)'.
-	    endPos := tokenPosition + tokenName size - 1.
-	] ifFalse:[
-	    tokenType isCharacter ifTrue:[
-		what := '"' , tokenType asString allBold, '"'.
-	    ] ifFalse:[
-		what := tokenType printString allBold.
-	    ].
-	    msg := what , ' unexpected. (missing ".", ":" or selector before it ?)'.
-	    endPos := source position1Based-1.
-	].
-	self parseError:msg position:tokenPosition to:endPos.
-	^#Error
+        "/ just for the nicer error message
+        (#(Self Nil True False Super Here) includes:tokenType) ifTrue:[
+            msg := '"',tokenName allBold,'" unexpected (missing "." or ":" before ' , tokenName , ' ?)'.
+            endPos := tokenPosition + tokenName size - 1.
+        ] ifFalse:[
+            tokenType isCharacter ifTrue:[
+                what := '"' , tokenType asString allBold, '"'.
+            ] ifFalse:[
+                what := tokenType printString allBold.
+            ].
+            msg := what , ' unexpected. (missing ".", ":" or selector before it ?)'.
+            endPos := source position.
+        ].
+        self parseError:msg position:tokenPosition to:endPos.
+        ^#Error
     ]
 
     "Modified: / 22-08-2006 / 14:22:45 / cg"
@@ -5331,124 +5331,124 @@
      Return #Error or self.
 
      methodBodyVarSpec ::= '|' { IDENTIFIER } '|'
-			    | <empty>
+                            | <empty>
     "
 
     |var pos pos2 msg classHint whatIsHidden|
 
     ((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
-	self parsePrimitiveOrResourceSpecOrEmpty.
+        self parsePrimitiveOrResourceSpecOrEmpty.
     ].
 
     (tokenType == $|) ifTrue:[
-	"memorize position for declaration in correction"
-
-	localVarDefPosition := Array with:tokenPosition with:nil.
-	self nextToken.
-	pos := tokenPosition.
-	[tokenType == #Identifier] whileTrue:[
-	    pos2 := tokenPosition + tokenName size - 1.
-	    self markLocalIdentifierFrom:tokenPosition to:pos2.
-	    self checkMethodVariableNameConventionsFor:tokenName.
-	    var := Variable name:tokenName.
-
-	    methodVars isNil ifTrue:[
-		methodVars := OrderedCollection with:var.
-		methodVarNames := OrderedCollection with:tokenName
-	    ] ifFalse:[
-		(methodVarNames includes:tokenName) ifTrue:[
-		    "/ redefinition
-		    self isSyntaxHighlighter ifTrue:[
-			self markBadIdentifierFrom:tokenPosition to:pos2.
-		    ] ifFalse:[
-			self
-			    parseError:'redefinition of ''' , tokenName , ''' in local variables.'
-			    position:tokenPosition to:pos2.
-		    ]
-		] ifFalse:[
-		    methodVars add:var.
-		    methodVarNames add:tokenName
-		]
-	    ].
-
-	    (self isDoIt not
-		    and:[ parserFlags warnHiddenVariables
-		    and:[(ParserFlags isFlag:#warnHiddenVariables enabledForClass:classToCompileFor selector:selector)
-	    ]]) ifTrue:[
-		whatIsHidden := nil.
-		methodArgNames notNil ifTrue:[
-		    (methodArgNames includes:tokenName) ifTrue:[
-			whatIsHidden := 'method argument'
-		    ]
-		].
-		classToCompileFor notNil ifTrue:[
-		    (self classesInstVarNames includes:tokenName) ifTrue:[
-			classToCompileFor isMeta ifTrue:[
-			    whatIsHidden := 'class instance variable'.
-			] ifFalse:[
-			    whatIsHidden := 'instance variable'.
-			]
-		    ]
-		].
-		whatIsHidden notNil ifTrue:[
-		    self
-			warning:(('local variable "%1" hides ',whatIsHidden,'.') bindWith:tokenName allBold)
-			doNotShowAgainAction:[ parserFlags warnHiddenVariables:false. ParserFlags warnHiddenVariables:false ]
-			doNotShowAgainForThisMethodAction: [ self disableWarningsOnCurrentMethodFor: #warnHiddenVariables ]
-			position:tokenPosition to:pos2
-		]
-	    ].
-
-	    self nextToken.
-
-	    classHint := nil.
-	    lastDirective notNil ifTrue:[
-		lastDirective isClassHintDirective ifTrue:[
-		    var classHint:lastDirective className.
-		].
-		lastDirective := nil.
-	    ].
-
-	    parserFlags allowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
-		((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
-		    self nextToken.
-		    "/ Q: should we allow literals only, or arbitrary expressions ?
-		    self shouldImplement.
-		]
-	    ].
-	    parserFlags allowDomainVariables == true ifTrue:[
-		(tokenType == $() ifTrue:[
-		    self variableTypeDeclarationFor:var.
-		].
-	    ].
-	    pos := tokenPosition
-	].
-
-	(tokenType ~~ $|) ifTrue:[
-	    (#(True False Self Nil Super ThisContext) includes:tokenType) ifTrue:[
-		msg := 'reserved keyword "',tokenName allBold,'" in local var declaration'.
-		pos2 := tokenPosition + tokenName size - 1.
-		self markBadIdentifierFrom:tokenPosition to:pos2.
-	    ] ifFalse:[
-		pos2 := source position1Based-1.
-		msg := 'Identifier or | expected in local var declaration'
-	    ].
-	    self syntaxError:msg position:tokenPosition to:pos2.
-	    ^ #Error
-	].
-	localVarDefPosition at:2 put:tokenPosition.
-	self nextToken
+        "memorize position for declaration in correction"
+
+        localVarDefPosition := Array with:tokenPosition with:nil.
+        self nextToken.
+        pos := tokenPosition.
+        [tokenType == #Identifier] whileTrue:[
+            pos2 := tokenPosition + tokenName size - 1.
+            self markLocalIdentifierFrom:tokenPosition to:pos2.
+            self checkMethodVariableNameConventionsFor:tokenName.
+            var := Variable name:tokenName.
+
+            methodVars isNil ifTrue:[
+                methodVars := OrderedCollection with:var.
+                methodVarNames := OrderedCollection with:tokenName
+            ] ifFalse:[
+                (methodVarNames includes:tokenName) ifTrue:[
+                    "/ redefinition
+                    self isSyntaxHighlighter ifTrue:[
+                        self markBadIdentifierFrom:tokenPosition to:pos2.
+                    ] ifFalse:[
+                        self
+                            parseError:'redefinition of ''' , tokenName , ''' in local variables.'
+                            position:tokenPosition to:pos2.
+                    ]
+                ] ifFalse:[
+                    methodVars add:var.
+                    methodVarNames add:tokenName
+                ]
+            ].
+
+            (self isDoIt not
+                    and:[ parserFlags warnHiddenVariables
+                    and:[(ParserFlags isFlag:#warnHiddenVariables enabledForClass:classToCompileFor selector:selector)
+            ]]) ifTrue:[
+                whatIsHidden := nil.
+                methodArgNames notNil ifTrue:[
+                    (methodArgNames includes:tokenName) ifTrue:[
+                        whatIsHidden := 'method argument'
+                    ]
+                ].
+                classToCompileFor notNil ifTrue:[
+                    (self classesInstVarNames includes:tokenName) ifTrue:[
+                        classToCompileFor isMeta ifTrue:[
+                            whatIsHidden := 'class instance variable'.
+                        ] ifFalse:[
+                            whatIsHidden := 'instance variable'.
+                        ]
+                    ]
+                ].
+                whatIsHidden notNil ifTrue:[
+                    self
+                        warning:(('local variable "%1" hides ',whatIsHidden,'.') bindWith:tokenName allBold)
+                        doNotShowAgainAction:[ parserFlags warnHiddenVariables:false. ParserFlags warnHiddenVariables:false ]
+                        doNotShowAgainForThisMethodAction: [ self disableWarningsOnCurrentMethodFor: #warnHiddenVariables ]
+                        position:tokenPosition to:pos2
+                ]
+            ].
+
+            self nextToken.
+
+            classHint := nil.
+            lastDirective notNil ifTrue:[
+                lastDirective isClassHintDirective ifTrue:[
+                    var classHint:lastDirective className.
+                ].
+                lastDirective := nil.
+            ].
+
+            parserFlags allowLocalVariableDeclarationWithInitializerExpression == true ifTrue:[
+                ((tokenType == $_) or:[tokenType == #':=']) ifTrue:[
+                    self nextToken.
+                    "/ Q: should we allow literals only, or arbitrary expressions ?
+                    self shouldImplement.
+                ]
+            ].
+            parserFlags allowDomainVariables == true ifTrue:[
+                (tokenType == $() ifTrue:[
+                    self variableTypeDeclarationFor:var.
+                ].
+            ].
+            pos := tokenPosition
+        ].
+
+        (tokenType ~~ $|) ifTrue:[
+            (#(True False Self Nil Super ThisContext) includes:tokenType) ifTrue:[
+                msg := 'reserved keyword "',tokenName allBold,'" in local var declaration'.
+                pos2 := tokenPosition + tokenName size - 1.
+                self markBadIdentifierFrom:tokenPosition to:pos2.
+            ] ifFalse:[
+                pos2 := source position.
+                msg := 'Identifier or | expected in local var declaration'
+            ].
+            self syntaxError:msg position:tokenPosition to:pos2.
+            ^ #Error
+        ].
+        localVarDefPosition at:2 put:tokenPosition.
+        self nextToken
     ].
 
     (parserFlags allowSqueakPrimitives
     or:[ parserFlags allowSqueakExtensions
     or:[ parserFlags allowVisualAgePrimitives
     or:[ parserFlags allowSTVPrimitives ]]]) ifTrue:[
-	"/ allow for primitiveSpec after local-var decl.
-
-	((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
-	    self parsePrimitiveOrResourceSpecOrEmpty.
-	]
+        "/ allow for primitiveSpec after local-var decl.
+
+        ((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
+            self parsePrimitiveOrResourceSpecOrEmpty.
+        ]
     ].
 
     ^ self
@@ -5633,7 +5633,7 @@
     (tokenType == #Primitive) ifTrue:[
         code := tokenValue.
         node := PrimitiveNode code:code.
-        node startPosition: tokenPosition endPosition: source position1Based.
+        node startPosition: tokenPosition endPosition: source position + 1.
         self nextToken.
         node isOptional ifFalse:[
             hasNonOptionalPrimitiveCode := true
@@ -5847,7 +5847,7 @@
 "/            ^ #Error
 "/        ].
         elem isSymbol ifTrue:[
-            self markSymbolFrom:tokenPosition to:(source position1Based-1).
+            self markSymbolFrom:tokenPosition to:(source position).
         ].
         elements add:elem.
         self nextToken.
@@ -6334,7 +6334,7 @@
                     ] ifFalse:[
                         (tokenType == #Error) ifTrue:[^ #Error].
                         self syntaxError:('invalid cascade; ' , tokenType printString , ' unexpected')
-                                position:tokenPosition to:source position1Based - 1.
+                                position:tokenPosition to:source position.
                         ^ #Error
                     ]
                 ]
@@ -6360,7 +6360,7 @@
          or:[(tokenType == #BinaryOperator)
              or:[tokenType == #Keyword]]) ifTrue:[
             self syntaxError:'ambigous cascade - please group using (...)'
-                    position:tokenPosition to:source position1Based - 1.
+                    position:tokenPosition to:source position.
             ^ #Error
 "/            self warning: "syntaxError:" 'possibly ambigous cascade - please group using (...)'
 "/                    position:tokenPosition to:source position - 1.
@@ -6856,7 +6856,7 @@
 
     (tokenType == #Primitive) ifTrue:[
         node := PrimitiveNode code:tokenValue.
-        node startPosition: tokenPosition endPosition: source position1Based.
+        node startPosition: tokenPosition endPosition: source position + 1.
         self nextToken.
         hasNonOptionalPrimitiveCode := true.
         hasPrimitiveCode := true.
@@ -6946,7 +6946,7 @@
                 eMsg := '"',(token ? ''),'" (',tokenType printString,') unexpected in primary.'
             ]
         ].
-        endPos :=source position1Based - 1.
+        endPos :=source position.
     ].
     self syntaxError:eMsg position:tokenPosition to:endPos.
     ^ #Error
@@ -7540,37 +7540,37 @@
     |pos pos2 val|
 
     pos := tokenPosition.
-    pos2 := source position1Based - 1.
+    pos2 := source position.
 
     "/
     "/ ImmutableStrings are experimental
     "/
     ((tokenType == #String)
     and:[(parserFlags stringsAreImmutable)]) ifTrue:[
-	token := tokenValue := self makeImmutableString:tokenValue.
+        token := tokenValue := self makeImmutableString:tokenValue.
     ].
 
     ((tokenType == #Symbol) or:[tokenType == #ESSymbol]) ifTrue:[
-	parseForCode ifFalse:[
-	    self rememberSymbolUsed:tokenValue
-	].
+        parseForCode ifFalse:[
+            self rememberSymbolUsed:tokenValue
+        ].
     ].
     val := ConstantNode type: tokenType value:tokenValue
-			from: pos to: pos2.
+                        from: pos to: pos2.
 
     ((tokenType == #Symbol) or:[tokenType == #ESSymbol]) ifTrue:[
-	self markSymbolFrom:tokenPosition to:tokenPosition+tokenValue size-1.
+        self markSymbolFrom:tokenPosition to:tokenPosition+tokenValue size-1.
     ] ifFalse:[
-	tokenType == #String ifTrue:[
-	    self markStringFrom:pos to:source position1Based-1.
-	] ifFalse:[
-	    self markConstantFrom:pos to:source position1Based-1.
-	].
+        tokenType == #String ifTrue:[
+            self markStringFrom:pos to:source position.
+        ] ifFalse:[
+            self markConstantFrom:pos to:source position.
+        ].
     ].
 
     self nextToken.
     (self noAssignmentAllowed:'Assignment to a constant' at:pos) ifFalse:[
-	^ #Error
+        ^ #Error
     ].
     ^ val
 
@@ -10894,11 +10894,11 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.771 2013-07-30 19:17:43 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.772 2013-08-10 11:23:29 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.771 2013-07-30 19:17:43 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.772 2013-08-10 11:23:29 stefan Exp $'
 !
 
 version_SVN