Parser.st
changeset 883 e595802b4853
parent 879 7066d5d6c064
child 887 e42ea977b85d
--- a/Parser.st	Tue Jun 29 12:04:19 1999 +0200
+++ b/Parser.st	Tue Jun 29 20:37:22 1999 +0200
@@ -1756,6 +1756,12 @@
     "Created: / 31.3.1998 / 13:22:15 / cg"
 !
 
+markBadIdentifierFrom:pos1 to:pos2
+
+    "Modified: / 31.3.1998 / 19:16:26 / cg"
+    "Created: / 31.3.1998 / 19:35:53 / cg"
+!
+
 markBooleanConstantFrom:pos1 to:pos2
 
     "Created: / 31.3.1998 / 18:06:22 / cg"
@@ -2630,7 +2636,7 @@
 block
     "parse a block; return a node-tree, nil or #Error"
 
-    |node args argNames arg pos lno|
+    |node args argNames arg pos pos2 lno|
 
     lno := tokenLineNr.
     self nextToken.
@@ -2638,19 +2644,26 @@
         [tokenType == $:] whileTrue:[
             pos := tokenPosition.
             self nextToken.
-            (tokenType == #Identifier) ifFalse:[
+            (tokenType ~~ #Identifier) ifTrue:[
                 ^ self identifierExpectedIn:'block-arg declaration'
             ].
-            self markArgumentIdentifierFrom:tokenPosition to:(tokenPosition + tokenName size - 1).
+
+            pos2 := tokenPosition + tokenName size - 1.
+            self markArgumentIdentifierFrom:tokenPosition to:pos2.
             arg := Variable name:tokenName.
             args isNil ifTrue:[
                 args := Array with:arg.
                 argNames := Array with:tokenName.
             ] ifFalse:[
                 (argNames includes:tokenName) ifTrue:[
-                    self syntaxError:'redefinition of ''' , tokenName , ''' in argument list.'
-                            position:tokenPosition 
-                                   to:(tokenPosition + tokenName size - 1)
+                    "/ argname reuse
+                    self isSyntaxHighlighter ifTrue:[
+                        self markBadIdentifierFrom:tokenPosition to:pos2.
+                    ] ifFalse:[
+                        self 
+                            syntaxError:'redefinition of ''' , tokenName , ''' in argument list.'
+                            position:tokenPosition to:pos2
+                    ]
                 ].
                 args := args copyWith:arg.
                 argNames := argNames copyWith:tokenName.
@@ -2681,7 +2694,7 @@
 blockBody:args
     "parse a blocks body; return a node-tree, nil or #Error"
 
-    |stats node var vars lno names|
+    |stats node var vars lno names pos2|
 
     lno := tokenLineNr.
     (tokenType == $| ) ifTrue:[
@@ -2690,15 +2703,22 @@
             (tokenType == #Identifier) ifFalse:[
                 ^ self identifierExpectedIn:'block-var declaration'
             ].
-            self markLocalIdentifierFrom:tokenPosition to:(tokenPosition + tokenName size - 1).
+            pos2 := tokenPosition + tokenName size - 1.
+            self markLocalIdentifierFrom:tokenPosition to:pos2.
             var := Variable name:tokenName.
             vars isNil ifTrue:[
                 vars := Array with:var.
                 names := Array with:tokenName
             ] ifFalse:[
                 (names includes:tokenName) ifTrue:[
-                    self parseError:'redefinition of ''' , tokenName , ''' in local variables'
-                           position:tokenPosition to:tokenPosition + tokenName size -1.
+                    "/ varname reuse
+                    self isSyntaxHighlighter ifTrue:[
+                        self markBadIdentifierFrom:tokenPosition to:pos2.
+                    ] ifFalse:[
+                        self 
+                            parseError:'redefinition of ''' , tokenName , ''' in local variables'
+                            position:tokenPosition to:pos2.
+                    ]
                 ] ifFalse:[
                     vars := vars copyWith:var.
                     names := names copyWith:tokenName
@@ -2805,28 +2825,28 @@
      Return a node-tree, or #Error
 
      methodBody ::= '<' st80Primitive '>' #EOF
-		    | '<' st80Primitive '>' methodBodyVarSpec statementList #EOF
+                    | '<' st80Primitive '>' methodBodyVarSpec statementList #EOF
 
     "
     |stats|
 
-    classToCompileFor notNil ifTrue:[
-	stats := self parseMethodBodyOrEmpty.
-    ] ifFalse:[
-	stats := self parseMethodBodyOrEmpty.
-    ].
+"/    classToCompileFor notNil ifTrue:[
+"/        stats := self parseMethodBodyOrEmpty.
+"/    ] ifFalse:[
+        stats := self parseMethodBodyOrEmpty.
+"/    ].
     (stats == #Error) ifFalse:[
-	(tokenType ~~ #EOF) ifTrue:[
-	    "/ just for the nicer error message
-	    (#(Self Nil True False Super Here) includes:tokenType) ifTrue:[
-		self parseError:tokenName , ' unexpected (missing ''.'' before ' , tokenName , ' ?)' 
-		       position:tokenPosition to:(tokenPosition + tokenName size - 1)
-	    ] ifFalse:[
-		self parseError:(tokenType printString , ' unexpected (missing ''.'' or selector before it ?)') 
-		     position:tokenPosition to:source position-1.
-	    ].
-	    ^#Error
-	]
+        (tokenType ~~ #EOF) ifTrue:[
+            "/ just for the nicer error message
+            (#(Self Nil True False Super Here) includes:tokenType) ifTrue:[
+                self parseError:tokenName , ' unexpected (missing ''.'' before ' , tokenName , ' ?)' 
+                       position:tokenPosition to:(tokenPosition + tokenName size - 1)
+            ] ifFalse:[
+                self parseError:(tokenType printString , ' unexpected (missing ''.'' or selector before it ?)') 
+                     position:tokenPosition to:source position-1.
+            ].
+            ^#Error
+        ]
     ].
     ^ stats
 
@@ -2866,7 +2886,7 @@
                             | <empty>
     "
 
-    |var pos msg|
+    |var pos pos2 msg|
 
     ((tokenType == #BinaryOperator) and:[tokenName = '<']) ifTrue:[
         self parsePrimitiveOrResourceSpecOrEmpty.
@@ -2874,41 +2894,55 @@
 
     (tokenType == $|) ifTrue:[
         "memorize position for declaration in correction"
+
         localVarDefPosition := tokenPosition.
         self nextToken.
         pos := tokenPosition.
         [tokenType == #Identifier] whileTrue:[
-            self markLocalIdentifierFrom:tokenPosition to:(tokenPosition + tokenName size - 1).
+            pos2 := tokenPosition + tokenName size - 1.
+            self markLocalIdentifierFrom:tokenPosition to:pos2.
             var := Variable name:tokenName.
+
             methodVars isNil ifTrue:[
                 methodVars := OrderedCollection with:var.
                 methodVarNames := OrderedCollection with:tokenName
             ] ifFalse:[
                 (methodVarNames includes:tokenName) ifTrue:[
-                    self parseError:'redefinition of ''' , tokenName , ''' in local variables'
-                           position:tokenPosition to:tokenPosition + tokenName size -1.
+                    "/ 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
                 ]
             ].
+
             methodArgNames notNil ifTrue:[
                 (methodArgNames includes:tokenName) ifTrue:[
-                    self warning:'local variable ''' , tokenName , ''' hides argument.'
-                        position:tokenPosition 
-                              to:(tokenPosition + tokenName size - 1)
+                    self 
+                        warning:'local variable ''' , tokenName , ''' hides argument.'
+                        position:tokenPosition to:pos2
                 ]
             ].
             self nextToken.
             pos := tokenPosition
         ].
+
         (tokenType ~~ $|) ifTrue:[
             (#(True False Self Nil Super ThisContext) includes:tokenType) ifTrue:[
-                msg := 'Reserved keyword in local var declaration' 
+                msg := 'Reserved keyword in local var declaration'. 
+                pos2 := tokenPosition + tokenName size - 1.
+                self markBadIdentifierFrom:tokenPosition to:pos2.
             ] ifFalse:[
+                pos2 := source position-1.
                 msg := 'Identifier or | expected in local var declaration' 
             ].
-            self syntaxError:msg position:tokenPosition to:source position-1.
+            self syntaxError:msg position:tokenPosition to:pos2.
             ^ #Error
         ].
         localVarDefPosition := Array with:localVarDefPosition with:tokenPosition.
@@ -2929,7 +2963,7 @@
                     | IDENTIFIER
     "
 
-    |var|
+    |var pos2|
 
     tokenType isNil ifTrue:[
         self nextToken.
@@ -2941,17 +2975,24 @@
             self markMethodSelectorFrom:tokenPosition to:(tokenPosition+tokenName size-1).
             selector := selector , tokenName.
             self nextToken.
+
             (tokenType ~~ #Identifier) ifTrue:[^ #Error].
-            self markArgumentIdentifierFrom:tokenPosition to:(tokenPosition+tokenName size-1).
+            pos2 := tokenPosition+tokenName size-1.
+            self markArgumentIdentifierFrom:tokenPosition to:pos2.
             var := Variable name:tokenName.
             methodArgs isNil ifTrue:[
                 methodArgs := Array with:var.
                 methodArgNames := Array with:tokenName
             ] ifFalse:[
                 (methodArgNames includes:tokenName) ifTrue:[
-                    self syntaxError:'redefinition of ''' , tokenName , ''' in argument list.'
-                            position:tokenPosition 
-                                  to:(tokenPosition + tokenName size - 1)
+                    "/ argname reuse
+                    self isSyntaxHighlighter ifTrue:[
+                        self markBadIdentifierFrom:tokenPosition to:pos2.
+                    ] ifFalse:[
+                        self 
+                            syntaxError:'redefinition of ''' , tokenName , ''' in argument list.'
+                            position:tokenPosition to:pos2
+                    ]
                 ].
                 methodArgs := methodArgs copyWith:var.
                 methodArgNames := methodArgNames copyWith:tokenName
@@ -4683,6 +4724,10 @@
     ^ hasPrimitiveCode
 !
 
+isSyntaxHighlighter
+    ^ false
+!
+
 lineNumberInfo
     ^ lineNumberInfo
 
@@ -4897,6 +4942,6 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.205 1999-06-26 16:29:19 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.206 1999-06-29 18:37:22 cg Exp $'
 ! !
 Parser initialize!