code rewritten to be independent of stream zero-base
authorClaus Gittinger <cg@exept.de>
Tue, 25 Feb 2003 12:47:23 +0100
changeset 1371 de4c37ac12fc
parent 1370 ebed47a4723b
child 1372 3aef25b07d7a
code rewritten to be independent of stream zero-base
MessageNode.st
Parser.st
Scanner.st
SyntaxHighlighter.st
--- a/MessageNode.st	Mon Feb 24 18:17:33 2003 +0100
+++ b/MessageNode.st	Tue Feb 25 12:47:23 2003 +0100
@@ -579,7 +579,7 @@
         theArg codeOn:aStream inBlock:b for:aCompiler
     ].
     aStream nextPut:theByteCode.
-    pos1 := aStream position.   "/ remember branch target of left-fail branch
+    pos1 := aStream position1Based.   "/ remember branch target of left-fail branch
     aStream nextPut:0.
 
     "/ code the right of the and-part
@@ -591,12 +591,12 @@
         jmp := #trueJump
     ].
     aStream nextPut:jmp.
-    pos2 := aStream position.   "/ remember branch target of right-fail branch 
+    pos2 := aStream position1Based.   "/ remember branch target of right-fail branch 
     aStream nextPut:0.
 
     code := aStream contents.
     (selector == #ifFalse:ifTrue:) ifTrue:[
-        code at:pos1 put:(aStream position)
+        code at:pos1 put:(aStream position1Based)
     ].
 
     "/ code the if-block
@@ -618,10 +618,10 @@
     ].
 
     aStream nextPut:#jump.
-    pos3 := aStream position.
+    pos3 := aStream position1Based.
     aStream nextPut:0.
 
-    here := aStream position.
+    here := aStream position1Based.
     (selector == #ifTrue:ifFalse:) ifTrue:[
         code at:pos1 put:here
     ].
@@ -645,7 +645,7 @@
         ]
     ].
 
-    code at:pos3 put:(aStream position)
+    code at:pos3 put:(aStream position1Based)
 
     "Created: 6.9.1996 / 12:56:23 / cg"
 !
@@ -674,7 +674,7 @@
         theArg codeOn:aStream inBlock:b for:aCompiler
     ].
     aStream nextPut:theByteCode.
-    pos1 := aStream position.
+    pos1 := aStream position1Based.
     aStream nextPut:0.
 
     andBlock := receiver arg1. "/ the and:-block
@@ -703,12 +703,12 @@
         andBlock codeInlineOn:aStream inBlock:b for:aCompiler.
     ].
     aStream nextPut:jmp.
-    pos2 := aStream position.
+    pos2 := aStream position1Based.
     aStream nextPut:0.
 
     code := aStream contents.
     (selector == #ifFalse:) ifTrue:[
-        code at:pos1 put:(aStream position)
+        code at:pos1 put:(aStream position1Based)
     ].
     block := argArray at: 1.
     block isBlock ifTrue:[
@@ -729,17 +729,17 @@
 
     valueNeeded ifTrue:[
         aStream nextPut:#jump.
-        pos3 := aStream position.
+        pos3 := aStream position1Based.
         aStream nextPut:0.
-        here := aStream position.
+        here := aStream position1Based.
         (selector == #ifTrue:) ifTrue:[
             code at:pos1 put:here
         ].
         code at:pos2 put:here.
         aStream nextPut:#pushNil.
-        code at:pos3 put:(aStream position)
+        code at:pos3 put:(aStream position1Based)
     ] ifFalse:[
-        here := aStream position.
+        here := aStream position1Based.
         (selector == #ifTrue:) ifTrue:[
             code at:pos1 put:here
         ].
@@ -754,18 +754,18 @@
 
     receiver codeOn:aStream inBlock:b for:aCompiler.
     valueNeeded ifTrue:[
-	aStream nextPut:#dup.
+        aStream nextPut:#dup.
     ].
     aStream nextPut:#falseJump.
-    pos1 := aStream position.
+    pos1 := aStream position1Based.
     aStream nextPut:0.
     valueNeeded ifTrue:[
-	aStream nextPut:#drop.
+        aStream nextPut:#drop.
     ].
     rightExpr := argArray at:1.
     rightExpr codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
 
-    (aStream contents) at:pos1 put:(aStream position)
+    (aStream contents) at:pos1 put:(aStream position1Based)
 
     "Created: 17.6.1996 / 15:46:42 / cg"
     "Modified: 17.6.1996 / 15:47:44 / cg"
@@ -928,7 +928,7 @@
             ] ifFalse:[
                 aStream nextPut:#trueJump.
             ].
-            pos1 := aStream position.
+            pos1 := aStream position1Based.
             aStream nextPut:0.
         
             rightExpr := argArray at:1.
@@ -939,7 +939,7 @@
             ].
             aStream nextPut:#retTop.
         
-            (aStream contents) at:pos1 put:(aStream position).
+            (aStream contents) at:pos1 put:(aStream position1Based).
             selector == #and: ifTrue:[
                 aStream nextPut:#retFalse.
             ] ifFalse:[
@@ -954,9 +954,6 @@
         inBlock:b 
         lineNumber:lineNrOrNil 
         for:aCompiler
-
-
-
 !
 
 codeIfElseOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
@@ -1019,7 +1016,7 @@
     ].
 
     aStream nextPut:theByteCode.
-    pos := aStream position.
+    pos := aStream position1Based.
     aStream nextPut:0.
     needJump := true.
     block1 := argArray at:1.
@@ -1043,11 +1040,11 @@
     ].
     needJump ifTrue:[
         aStream nextPut:#jump.
-        pos2 := aStream position.
+        pos2 := aStream position1Based.
         aStream nextPut:0.
     ].
     code := aStream contents.
-    code at:pos put:(aStream position).
+    code at:pos put:(aStream position1Based).
     block2 := (argArray at:2).
     block2 isBlock ifTrue:[
         block2 codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
@@ -1065,7 +1062,7 @@
         ].
     ].
     needJump ifTrue:[
-        code at:pos2 put:(aStream position)
+        code at:pos2 put:(aStream position1Based)
     ]
 
     "Modified: 9.11.1996 / 19:53:52 / cg"
@@ -1075,7 +1072,7 @@
     "generate code for x ifNil:[ ... ] ifNotNil:[...]
      or: x ifNil:const1 ifNotNil:const2"
 
-    |pos pos2 theReceiver theArg theByteCode optByteCode subsel code
+    |pos pos2 theReceiver theArg theByteCode code
      needLineNr block1 block2|
 
     theReceiver := receiver.
@@ -1106,7 +1103,7 @@
     ].
 
     aStream nextPut:theByteCode.
-    pos := aStream position.
+    pos := aStream position1Based.
     aStream nextPut:0.
     block1 := argArray at: 1.
     block1 isBlock ifTrue:[
@@ -1125,11 +1122,11 @@
         ].
     ].
     aStream nextPut:#jump.
-    pos2 := aStream position.
+    pos2 := aStream position1Based.
     aStream nextPut:0.
 
     code := aStream contents.
-    code at:pos put:(aStream position).
+    code at:pos put:(aStream position1Based).
     block2 := argArray at: 2.
     block2 isBlock ifTrue:[
         block2 codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
@@ -1148,7 +1145,7 @@
     ].
 
     code := aStream contents.
-    code at:pos2 put:(aStream position)
+    code at:pos2 put:(aStream position1Based)
 
     "Modified: / 11.2.2000 / 12:50:36 / cg"
 !
@@ -1156,7 +1153,7 @@
 codeIfNilOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler
     "generate code for x ifNil:[ ... ]"
 
-    |pos pos2 theReceiver arg theByteCode optByteCode subsel code
+    |pos theReceiver arg theByteCode code
      needLineNr|
 
     theReceiver := receiver.
@@ -1189,7 +1186,7 @@
         aStream nextPut:#dup.
     ].
     aStream nextPut:theByteCode.
-    pos := aStream position.
+    pos := aStream position1Based.
     aStream nextPut:0.
     valueNeeded ifTrue:[
         aStream nextPut:#drop.
@@ -1213,7 +1210,7 @@
     ].
 
     code := aStream contents.
-    code at:pos put:(aStream position)
+    code at:pos put:(aStream position1Based)
 
     "Modified: / 28.10.1997 / 18:33:42 / cg"
 !
@@ -1285,7 +1282,7 @@
     ].
 
     aStream nextPut:theByteCode.
-    pos := aStream position.
+    pos := aStream position1Based.
     aStream nextPut:0.
     block := (argArray at:1).
     block isBlock ifTrue:[
@@ -1307,13 +1304,13 @@
     code := aStream contents.
     valueNeeded ifTrue:[
         aStream nextPut:#jump.
-        pos2 := aStream position.
+        pos2 := aStream position1Based.
         aStream nextPut:0.
-        code at:pos put:(aStream position).
+        code at:pos put:(aStream position1Based).
         aStream nextPut:#pushNil.
-        code at:pos2 put:(aStream position)
+        code at:pos2 put:(aStream position1Based)
     ] ifFalse:[
-        code at:pos put:(aStream position)
+        code at:pos put:(aStream position1Based)
     ]
 
     "Modified: / 28.10.1997 / 18:33:42 / cg"
@@ -1706,7 +1703,7 @@
         theArg codeOn:aStream inBlock:b for:aCompiler
     ].
     aStream nextPut:theByteCode.
-    pos1 := aStream position.   "/ remember branch target of left-ok branch
+    pos1 := aStream position1Based.   "/ remember branch target of left-ok branch
     aStream nextPut:0.
 
     "/ code the right of the or-part
@@ -1742,13 +1739,13 @@
         theReceiver codeInlineOn:aStream inBlock:b for:aCompiler.
     ].
     aStream nextPut:jmp.
-    pos2 := aStream position.   "/ remember branch target of right-fail branch 
+    pos2 := aStream position1Based.   "/ remember branch target of right-fail branch 
     aStream nextPut:0.
 
 
     code := aStream contents.
     (selector == #ifTrue:ifFalse:) ifTrue:[
-        code at:pos1 put:(aStream position)
+        code at:pos1 put:(aStream position1Based)
     ].
 
     "/ code the if-block
@@ -1770,10 +1767,10 @@
     ].
 
     aStream nextPut:#jump.
-    pos3 := aStream position.
+    pos3 := aStream position1Based.
     aStream nextPut:0.
 
-    here := aStream position.
+    here := aStream position1Based.
     (selector == #ifFalse:ifTrue:) ifTrue:[
         code at:pos1 put:here
     ].
@@ -1796,7 +1793,7 @@
             aStream nextPut:#drop
         ]
     ].
-    code at:pos3 put:(aStream position)
+    code at:pos3 put:(aStream position1Based)
 
     "Created: 6.9.1996 / 13:08:52 / cg"
 !
@@ -1823,7 +1820,7 @@
         theArg codeOn:aStream inBlock:b for:aCompiler
     ].
     aStream nextPut:theByteCode.
-    pos1 := aStream position.
+    pos1 := aStream position1Based.
     aStream nextPut:0.
 
 
@@ -1863,10 +1860,10 @@
         ].
         aStream nextPut:jmp
     ].
-    pos2 := aStream position.
+    pos2 := aStream position1Based.
     aStream nextPut:0.
     (selector == #ifTrue:) ifTrue:[
-        (aStream contents) at:pos1 put:(aStream position)
+        (aStream contents) at:pos1 put:(aStream position1Based)
     ].
     block := argArray at: 1.
     block isBlock ifTrue:[
@@ -1888,17 +1885,17 @@
     code := aStream contents.
     valueNeeded ifTrue:[
         aStream nextPut:#jump.
-        pos3 := aStream position.
+        pos3 := aStream position1Based.
         aStream nextPut:0.
-        here := aStream position.
+        here := aStream position1Based.
         (selector == #ifFalse:) ifTrue:[
             code at:pos1 put:here
         ].
         code at:pos2 put:here.
         aStream nextPut:#pushNil.
-        code at:pos3 put:(aStream position)
+        code at:pos3 put:(aStream position1Based)
     ] ifFalse:[
-        here := aStream position.
+        here := aStream position1Based.
         (selector == #ifFalse:) ifTrue:[
             code at:pos1 put:here
         ].
@@ -1915,18 +1912,18 @@
 
     receiver codeOn:aStream inBlock:b for:aCompiler.
     valueNeeded ifTrue:[
-	aStream nextPut:#dup.
+        aStream nextPut:#dup.
     ].
     aStream nextPut:#trueJump.
-    pos1 := aStream position.
+    pos1 := aStream position1Based.
     aStream nextPut:0.
     valueNeeded ifTrue:[
-	aStream nextPut:#drop.
+        aStream nextPut:#drop.
     ].
     rightExpr := argArray at:1.
     rightExpr codeInlineOn:aStream inBlock:b valueNeeded:valueNeeded for:aCompiler.
 
-    (aStream contents) at:pos1 put:(aStream position)
+    (aStream contents) at:pos1 put:(aStream position1Based)
 
     "Created: 17.6.1996 / 15:40:22 / cg"
     "Modified: 17.6.1996 / 15:47:22 / cg"
@@ -1941,14 +1938,14 @@
     receiver codeOn:aStream inBlock:b for:aCompiler.
     aStream nextPut:#dup.
     aStream nextPut:#notNilJump.
-    pos := aStream position.
+    pos := aStream position1Based.
     aStream nextPut:0.
 
     aStream nextPut:#drop.
     (argArray at: 1) codeOn:aStream inBlock:b for:aCompiler.
 
     code := aStream contents.
-    code at:pos put:(aStream position).
+    code at:pos put:(aStream position1Based).
 
     valueNeeded ifFalse:[
         aStream nextPut:#drop.
@@ -1963,7 +1960,7 @@
 
     |pos|
 
-    pos := aStream position.
+    pos := aStream position1Based.
     receiver codeInlineOn:aStream inBlock:b valueNeeded:false for:aCompiler.
     aStream nextPut:#jump; nextPut:pos.
 
@@ -2137,18 +2134,18 @@
 
     loopCount isNil ifTrue:[
         aStream nextPut:#pushgt0; nextPut:lineNr; nextPut:#falseJump.
-        pos2 := aStream position.
+        pos2 := aStream position1Based.
         aStream nextPut:0.
     ].
 
-    pos1 := aStream position.
+    pos1 := aStream position1Based.
     (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:false for:aCompiler.
     aStream nextPut:#minus1; nextPut:lineNr.
     aStream nextPut:#pushgt0; nextPut:lineNr.
     aStream nextPut:#trueJump; nextPut:pos1.
 
     pos2 notNil ifTrue:[
-        (aStream contents) at:pos2 put:(aStream position).
+        (aStream contents) at:pos2 put:(aStream position1Based).
     ].
     aStream nextPut:#drop.  "/ drop run variable
 
@@ -2215,7 +2212,7 @@
         ]
     ].
 
-    pos := aStream position.
+    pos := aStream position1Based.
 
     aStream nextPut:#dup.
     stopVarIndex notNil ifTrue:[
@@ -2236,7 +2233,7 @@
         aStream nextPut:lineNr.
     ].
     aStream nextPut:#trueJump.
-    pos2 := aStream position.
+    pos2 := aStream position1Based.
     aStream nextPut:0.
 
     theBlock := argArray at:3.
@@ -2274,7 +2271,7 @@
 
     aStream nextPut:#jump; nextPut:pos.
 
-    (aStream contents) at:pos2 put:(aStream position).
+    (aStream contents) at:pos2 put:(aStream position1Based).
     aStream nextPut:#drop.  "/ drop run variable
     lateEval ifTrue:[
         start codeOn:aStream inBlock:b for:aCompiler.
@@ -2322,55 +2319,55 @@
     lateEval := false.
 
     valueNeeded ifTrue:[
-	"/ easily reconstructable - no need to keep on stack
-	start isConstant ifTrue:[
-	    (start evaluate isMemberOf:SmallInteger) ifTrue:[
-		lateEval := true.
-	    ]
-	].
-	lateEval ifFalse:[
-	    aStream nextPut:#dup
-	].
+        "/ easily reconstructable - no need to keep on stack
+        start isConstant ifTrue:[
+            (start evaluate isMemberOf:SmallInteger) ifTrue:[
+                lateEval := true.
+            ]
+        ].
+        lateEval ifFalse:[
+            aStream nextPut:#dup
+        ].
     ].
 
     "/ if stop is not constant, and not an argVar,
     "/  evaluate it into a temp slot ...
 
     (stop isConstant and:[stop type == #Integer]) ifFalse:[
-	"/ a method/blockArg is constant as well ...
-	(stop isVariable and:[stop isArgument]) ifFalse:[
-	    stop codeOn:aStream inBlock:b for:aCompiler.
-
-	    b isNil ifTrue:[
-		stopVarIndex := aCompiler addTempVar.
-		aStream nextPut:#storeMethodVar; nextPut:stopVarIndex.
-	    ] ifFalse:[
-		stopVarIndex := b addTempVar.
-		aStream nextPut:#storeBlockVar; nextPut:stopVarIndex.
-	    ].
-	]
+        "/ a method/blockArg is constant as well ...
+        (stop isVariable and:[stop isArgument]) ifFalse:[
+            stop codeOn:aStream inBlock:b for:aCompiler.
+
+            b isNil ifTrue:[
+                stopVarIndex := aCompiler addTempVar.
+                aStream nextPut:#storeMethodVar; nextPut:stopVarIndex.
+            ] ifFalse:[
+                stopVarIndex := b addTempVar.
+                aStream nextPut:#storeBlockVar; nextPut:stopVarIndex.
+            ].
+        ]
     ].
 
-    pos := aStream position.
+    pos := aStream position1Based.
 
     aStream nextPut:#lineno; nextPut:lineNr.
 
     aStream nextPut:#dup.
     stopVarIndex notNil ifTrue:[
-	b isNil ifTrue:[
-	    aStream nextPut:#pushMethodVar; nextPut:stopVarIndex.
-	] ifFalse:[
-	    aStream nextPut:#pushBlockVar; nextPut:stopVarIndex.
-	]
+        b isNil ifTrue:[
+            aStream nextPut:#pushMethodVar; nextPut:stopVarIndex.
+        ] ifFalse:[
+            aStream nextPut:#pushBlockVar; nextPut:stopVarIndex.
+        ]
     ] ifFalse:[
-	stop codeOn:aStream inBlock:b for:aCompiler.
+        stop codeOn:aStream inBlock:b for:aCompiler.
     ].
     aStream nextPut:#>.
     (aCompiler hasLineNumber:selector) ifTrue:[
-	aStream nextPut:lineNr.
+        aStream nextPut:lineNr.
     ].
     aStream nextPut:#trueJump.
-    pos2 := aStream position.
+    pos2 := aStream position1Based.
     aStream nextPut:0.
 
     theBlock := argArray at:2.
@@ -2378,13 +2375,13 @@
     "/ need a temporary in the outer context for
     "/ the loop ...
     b isNil ifTrue:[
-	loopVarIndex := aCompiler addTempVar.
-	aStream nextPut:#dup.
-	aStream nextPut:#storeMethodVar; nextPut:loopVarIndex.
+        loopVarIndex := aCompiler addTempVar.
+        aStream nextPut:#dup.
+        aStream nextPut:#storeMethodVar; nextPut:loopVarIndex.
     ] ifFalse:[
-	loopVarIndex := b addTempVar.
-	aStream nextPut:#dup.
-	aStream nextPut:#storeBlockVar; nextPut:loopVarIndex.
+        loopVarIndex := b addTempVar.
+        aStream nextPut:#dup.
+        aStream nextPut:#storeBlockVar; nextPut:loopVarIndex.
     ].
     theBlock indexOfFirstTemp:loopVarIndex.
 
@@ -2394,27 +2391,27 @@
 
     aStream nextPut:#plus1; nextPut:lineNr; nextPut:#jump; nextPut:pos.
 
-    (aStream contents) at:pos2 put:(aStream position).
+    (aStream contents) at:pos2 put:(aStream position1Based).
     aStream nextPut:#drop.  "/ drop run variable
     lateEval ifTrue:[
-	start codeOn:aStream inBlock:b for:aCompiler.
+        start codeOn:aStream inBlock:b for:aCompiler.
     ].
 
     "/ no need to nil-out loop-tempVar to help GC
     "/ (its integer, anyway).
 
     b isNil ifTrue:[
-	aCompiler removeTempVar
+        aCompiler removeTempVar
     ] ifFalse:[
-	b removeTempVar
+        b removeTempVar
     ].
 
     stopVarIndex notNil ifTrue:[
-	b isNil ifTrue:[
-	    aCompiler removeTempVar
-	] ifFalse:[
-	    b removeTempVar
-	]
+        b isNil ifTrue:[
+            aCompiler removeTempVar
+        ] ifFalse:[
+            b removeTempVar
+        ]
     ].
 
     "Created: 26.6.1997 / 10:58:47 / cg"
@@ -2473,7 +2470,7 @@
 "/
     needLineNr := true.
 
-    pos := aStream position.
+    pos := aStream position1Based.
 
 "/    aCompiler lineNumberInfo == #full ifTrue:[
         self codeLineNumber:lineNr on:aStream for:aCompiler.
@@ -2549,14 +2546,14 @@
 
     theByteCode ~~ #never ifTrue:[
         aStream nextPut:theByteCode.
-        pos2 := aStream position.
+        pos2 := aStream position1Based.
         aStream nextPut:0.
     ].
 
     (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:false for:aCompiler.
     aStream nextPut:#jump; nextPut:pos.
     theByteCode ~~ #never ifTrue:[
-        (aStream contents) at:pos2 put:(aStream position).
+        (aStream contents) at:pos2 put:(aStream position1Based).
     ].
 
     valueNeeded ifTrue:[aStream nextPut:#pushNil].
@@ -2621,16 +2618,16 @@
     hasLoopBlock ifTrue:[
         (argArray at:1) isEmptyBlock ifFalse:[
             aStream nextPut:#jump.
-            pos0 := aStream position.
+            pos0 := aStream position1Based.
             aStream nextPut:0.
 
-            pos := aStream position.
+            pos := aStream position1Based.
             (argArray at:1) codeInlineOn:aStream inBlock:b valueNeeded:false for:aCompiler.
 
-            (aStream contents) at:pos0 put:(aStream position).
+            (aStream contents) at:pos0 put:(aStream position1Based).
         ]
     ] ifFalse:[
-        pos := aStream position.
+        pos := aStream position1Based.
     ].
 
     optByteCode isNil ifTrue:[
@@ -3075,5 +3072,5 @@
 !MessageNode class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/MessageNode.st,v 1.124 2002-06-19 12:08:34 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/MessageNode.st,v 1.125 2003-02-25 11:47:23 cg Exp $'
 ! !
--- a/Parser.st	Mon Feb 24 18:17:33 2003 +0100
+++ b/Parser.st	Tue Feb 25 12:47:23 2003 +0100
@@ -2182,7 +2182,7 @@
                     ].
                     correctedSource := requestor currentSourceCode.
                     source := (ReadStream on:correctedSource)
-                                  position:(source position + ins size).
+                                  position:(source position1Based + ins size).
 
                     varIndex := methodVarNames size.
                     var used:true.
@@ -2263,7 +2263,7 @@
     correctedSource := requestor currentSourceCode.
     "/ update the current source position
     source := (ReadStream on:correctedSource)
-                  position:(source position - selectionSize).
+                  position:(source position1Based - selectionSize).
 
     ^ nil
 
@@ -2355,7 +2355,7 @@
     "
     correctedSource := requestor currentSourceCode.
     source := (ReadStream on:correctedSource)
-                  position:(source position + 1 + (newSelector size - aSelectorString size)).
+                  position:(source position1Based + 1 + (newSelector size - aSelectorString size)).
 "/ Parser murks.
     ^ newSelector
 
@@ -2385,7 +2385,7 @@
     correctedSource := requestor currentSourceCode.
     "/ update the current source position
     source := (ReadStream on:correctedSource)
-                  position:(source position - deleteSize).
+                  position:(source position1Based - deleteSize).
     ^ nil
 !
 
@@ -2457,7 +2457,7 @@
     "
     correctedSource := requestor currentSourceCode.
     source := (ReadStream on:correctedSource)
-                  position:(source position + newName size - tokenName size).
+                  position:(source position1Based + newName size - tokenName size).
 
     "redo parse with new value"
     token := tokenName := newName.
@@ -3021,7 +3021,7 @@
         msg := 'Identifier expected in ' 
     ].
     self syntaxError:(msg , what , ' (got ''' , tokenType printString, ''')')
-         position:tokenPosition to:source position - 1.
+         position:tokenPosition to:source position1Based - 1.
     ^ #Error
 !
 
@@ -3527,7 +3527,7 @@
     [tokenType == $] ] whileFalse:[
         (tokenType == $.) ifFalse:[
             (tokenType == #EOF) ifTrue:[
-                self syntaxError:'missing '']'' in block' position:(source position) to:(source position).
+                self syntaxError:'missing '']'' in block' position:(source position1Based) to:(source position1Based).
                 ^ #Error.
             ].
 
@@ -3572,7 +3572,7 @@
                    position:tokenPosition to:(tokenPosition + tokenName size - 1)
         ] ifFalse:[
             self parseError:(tokenType printString , ' unexpected (missing ''.'' or selector before it ?)') 
-                 position:tokenPosition to:source position-1.
+                 position:tokenPosition to:source position1Based-1.
         ].
         ^#Error
     ]
@@ -3865,7 +3865,7 @@
                 pos2 := tokenPosition + tokenName size - 1.
                 self markBadIdentifierFrom:tokenPosition to:pos2.
             ] ifFalse:[
-                pos2 := source position-1.
+                pos2 := source position1Based-1.
                 msg := 'Identifier or | expected in local var declaration' 
             ].
             self syntaxError:msg position:tokenPosition to:pos2.
@@ -4423,7 +4423,7 @@
 "/            ^ #Error
 "/        ].
         elem isSymbol ifTrue:[
-            self markSymbolFrom:tokenPosition to:(source position-1).
+            self markSymbolFrom:tokenPosition to:(source position1Based-1).
         ].
         elements add:elem.
         self nextToken
@@ -4774,7 +4774,7 @@
                     ] ifFalse:[
                         (tokenType == #Error) ifTrue:[^ #Error].
                         self syntaxError:('invalid cascade; ' , tokenType printString , ' unexpected')
-                                position:tokenPosition to:source position - 1.
+                                position:tokenPosition to:source position1Based - 1.
                         ^ #Error
                     ]
                 ]
@@ -4800,7 +4800,7 @@
          or:[(tokenType == #BinaryOperator)
              or:[tokenType == #Keyword]]) ifTrue:[
             self syntaxError:'ambigous cascade - please group using (...)'
-                    position:tokenPosition to:source position - 1.
+                    position:tokenPosition to:source position1Based - 1.
             ^ #Error
 "/            self warning: "syntaxError:" 'possibly ambigous cascade - please group using (...)'
 "/                    position:tokenPosition to:source position - 1.
@@ -5321,7 +5321,7 @@
                      , (token ? '') , ' (', tokenType printString ,
                      ') unexpected') 
         ].
-        self syntaxError:eMsg position:tokenPosition to:source position
+        self syntaxError:eMsg position:tokenPosition to:source position1Based - 1
     ].
     ^ #Error
 
@@ -5520,7 +5520,7 @@
                 ignoreWarnings ifFalse:[
                     warnSTXNameSpaceUse ifTrue:[
                         self warning:'nameSpaces are a nonstandard feature of ST/X' 
-                             position:pos1 to:(source position).
+                             position:pos1 to:(source position1Based).
                         "
                          only warn once
                         "
@@ -7053,7 +7053,7 @@
 !Parser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.370 2003-02-24 16:59:39 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Parser.st,v 1.371 2003-02-25 11:47:07 cg Exp $'
 ! !
 
 Parser initialize!
--- a/Scanner.st	Mon Feb 24 18:17:33 2003 +0100
+++ b/Scanner.st	Tue Feb 25 12:47:23 2003 +0100
@@ -561,7 +561,7 @@
      This method was required by some PD program.
      It is not maintained and may be removed without notice."
 
-    ^ source position
+    ^ source position1Based
 
     "Modified: 23.5.1997 / 12:14:27 / cg"
 !
@@ -647,8 +647,7 @@
 !
 
 sourcePosition
-    ^ source position
-
+    ^ source position1Based
 !
 
 sourceStream
@@ -1199,7 +1198,7 @@
     |oldPos|
 
     self initializeFor:aStringOrStream.
-    oldPos := source position.
+    oldPos := source position1Based.
     self nextToken.
     tokenValue isNumber ifTrue:[
         "/ must keep stream positioned correctly
@@ -1213,7 +1212,7 @@
         ^ tokenValue
     ].
     "/ backup in case of error; return nil
-    source position:oldPos.
+    source position1Based:oldPos.
     ^ nil.
 
     "Created: / 18.6.1998 / 23:05:22 / cg"
@@ -1375,7 +1374,7 @@
      one token too many"
 
     (tokenType == #EOF) ifFalse:[
-	source position:tokenPosition
+        source position1Based:tokenPosition
     ]
 !
 
@@ -1719,7 +1718,7 @@
                 nextChar := source peek.
                 allowUnderscoreInIdentifier == true ifTrue:[
                     nextChar == $_ ifTrue:[
-                        self warnUnderscoreAt:source position.
+                        self warnUnderscoreAt:source position1Based.
                     ].
                     [nextChar == $_] whileTrue:[
                         string := string copyWith:nextChar.
@@ -1731,7 +1730,7 @@
                     ].
                 ].
                 (nextChar == $:) ifFalse:[
-                    self markSymbolFrom:tokenPosition to:(source position-1).
+                    self markSymbolFrom:tokenPosition to:(source position1Based-1).
                     tokenValue := token := string asSymbol.
                     tokenType := #Symbol.
                     ^ tokenType
@@ -1773,7 +1772,7 @@
         (nextChar == $' ) ifTrue:[
             "ST-80 and ST/X support arbitrary symbols as #'...'"
             self nextString.
-            self markSymbolFrom:tokenPosition to:(source position-1).
+            self markSymbolFrom:tokenPosition to:(source position1Based-1).
             tokenValue := token := tokenValue asSymbol.
             tokenType := #Symbol.
             ^ tokenType
@@ -1811,7 +1810,7 @@
                     string := string copyWith:nextChar
                 ]
             ].
-            self markSymbolFrom:tokenPosition to:(source position-1).
+            self markSymbolFrom:tokenPosition to:(source position1Based-1).
             tokenValue := token := string asSymbol.
             tokenType := #Symbol.
             ^ tokenType
@@ -1898,7 +1897,7 @@
     or:[nextChar == $$]) ifTrue:[
         ok := (nextChar == $_) ifTrue:[allowUnderscoreInIdentifier] ifFalse:[allowDollarInIdentifier].
         ok ifTrue:[
-            pos := source position.
+            pos := source position1Based.
             nextChar == $_ ifTrue:[
                 self warnUnderscoreAt:pos.
             ] ifFalse:[
@@ -1944,7 +1943,7 @@
                         tokenName := token := (string copyWith:nextChar) , token.   
                         tokenType ~~ #Keyword ifTrue:[
                             self syntaxError:'invalid keyword symbol in array constant'
-                                    position:tokenPosition to:(source position - 1).
+                                    position:tokenPosition to:(source position1Based - 1).
                         ].
                         tokenType := #Keyword.
                     ].
@@ -1973,7 +1972,7 @@
     ].
 
     nextChar == $- ifTrue:[
-        pos := source position.
+        pos := source position1Based.
         self
             warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other systems'
             position:pos to:pos.
@@ -2032,7 +2031,7 @@
 
     tokenRadix := 10.
     type := #Integer.
-    pos1 := source position.
+    pos1 := source position1Based.
 
     value := Integer readFrom:source radix:tokenRadix.
     nextChar := source peekOrNil.
@@ -2042,7 +2041,7 @@
 
         (tokenRadix between:2 and:36) ifFalse:[
             self syntaxError:'bad radix (must be 2 .. 36)'
-                    position:tokenPosition to:(source position - 1).
+                    position:tokenPosition to:(source position1Based - 1).
         ].
         s := 1.
         source peekOrNil == $- ifTrue:[
@@ -2059,7 +2058,7 @@
         (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
             (tokenRadix > 14 and:[nextChar == $e or:[nextChar == $E]]) ifTrue:[
                 self warning:'float with radix > 14 - (e/E are valid digits; not exponent-leaders)'
-                    position:tokenPosition to:(source position - 1).
+                    position:tokenPosition to:(source position1Based - 1).
             ].
             mantissaAndScaledPart := self nextMantissaAndScaledPartWithRadix:tokenRadix.
             integerPart := value.
@@ -2120,7 +2119,7 @@
                 type := #FixedPoint.
                 self
                     warnPossibleIncompatibility:'fixedPoint literal might be incompatibile with other systems'
-                    position:pos1 to:source position.
+                    position:pos1 to:source position1Based.
             ].
         ].
     ].
@@ -2128,7 +2127,7 @@
     nextChar == $- ifTrue:[
         self
             warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other systems'
-            position:(source position) to:source position.
+            position:(source position1Based) to:(source position1Based).
     ].
 
     tokenValue := token := value.
@@ -2162,7 +2161,7 @@
         [nextChar == $%] whileFalse:[
             nextChar isNil ifTrue:[
                 self syntaxError:'unterminated primitive'
-                        position:tokenPosition to:source position.
+                        position:tokenPosition to:source position1Based.
                 ^ #Error
             ].
             string at:index put:nextChar.
@@ -2221,16 +2220,16 @@
         ((typeArray at:(secondChar asciiValue)) == #special) ifTrue:[
             (secondChar == $-) ifTrue:[
                 "special- look if minus belongs to number following"
-                p := source position.
+                p := source position1Based.
                 source next.
                 thirdChar := source peekOrNil.
-                source position:p.
+                source position1Based:p.
                 (thirdChar notNil and:[thirdChar isDigit]) ifTrue:[
                     tokenName := token := string.
                     tokenType := #BinaryOperator.
                     self 
                         warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other ST systems' 
-                        position:p-(PositionableStream zeroPosition) 
+                        position:p 
                         to:p.
                     ^ tokenType
                 ]
@@ -2243,16 +2242,16 @@
                 ((typeArray at:(thirdChar asciiValue)) == #special) ifTrue:[
                     (thirdChar == $-) ifTrue:[
                         "special- look if minus belongs to number following"
-                        p := source position.
+                        p := source position1Based.
                         source next.
                         fourthChar := source peekOrNil.
-                        source position:p.
+                        source position1Based:p.
                         fourthChar isDigit ifTrue:[
                             tokenName := token := string.
                             tokenType := #BinaryOperator.
                             self 
                                 warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other ST systems' 
-                                position:p-(PositionableStream zeroPosition) 
+                                position:p 
                                 to:p.
                             ^ tokenType
                         ]
@@ -2281,7 +2280,7 @@
     string := String basicNew:20.
     len := 20.
     index := 1.
-    pos := source position.
+    pos := source position1Based.
     source next.
     nextChar := source next.
     inString := true.
@@ -2289,8 +2288,8 @@
     [inString] whileTrue:[
         nextChar isNil ifTrue:[
             self syntaxError:'unexpected end-of-input in String'
-                    position:pos to:(source position - 1).
-            self markStringFrom:pos to:source position-1.
+                    position:pos to:(source position1Based - 1).
+            self markStringFrom:pos to:source position1Based-1.
             token := nil.
             tokenType := #EOF.
             ^ tokenType
@@ -2328,7 +2327,7 @@
             nextChar := source next
         ]
     ].
-    self markStringFrom:pos to:source position-1.
+    self markStringFrom:pos to:source position1Based-1.
 
     tokenValue := token := string copyTo:(index - 1).
     tokenType := #String.
@@ -2417,7 +2416,7 @@
             ].
             ch := hereChar
         ].
-        tokenPosition := source position.
+        tokenPosition := source position1Based.
         tokenLineNr := lineNr.
 
         (v := ch asciiValue) == 0 ifTrue:[
@@ -2469,7 +2468,7 @@
         outCol := outCol + 1
     ].
 
-    startPos := source position.
+    startPos := source position1Based.
     source next.
     hereChar := source peekOrNil.
 
@@ -2495,12 +2494,12 @@
             ].
             hereChar := source nextPeek.
         ].
-        self markCommentFrom:startPos to:(source position).
+        self markCommentFrom:startPos to:(source position1Based).
         lineNr := lineNr + 1.
         ignoreWarnings ifFalse:[
             warnSTXSpecialComment ifTrue:[
                 self warning:'end-of-line comments are a nonstandard feature of ST/X' 
-                     position:startPos to:(source position).
+                     position:startPos to:(source position1Based).
                 "
                  only warn once
                 "
@@ -2544,9 +2543,9 @@
 
             hereChar isNil ifTrue:[
                 self markCommentFrom:startPos to:(source size).
-                self warning:'unclosed comment' position:startPos to:(source position)
+                self warning:'unclosed comment' position:startPos to:(source position1Based)
             ] ifFalse:[
-                self markCommentFrom:startPos to:(source position).
+                self markCommentFrom:startPos to:(source position1Based).
                 outStream notNil ifTrue:[
                     outStream nextPut:(Character doubleQuote).
                     outCol := outCol + 1
@@ -2612,7 +2611,7 @@
 !Scanner class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.162 2003-02-24 17:17:33 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.163 2003-02-25 11:46:10 cg Exp $'
 ! !
 
 Scanner initialize!
--- a/SyntaxHighlighter.st	Mon Feb 24 18:17:33 2003 +0100
+++ b/SyntaxHighlighter.st	Tue Feb 25 12:47:23 2003 +0100
@@ -97,7 +97,7 @@
 
         "/ alternative2: take original emphasis for rest
 
-        endPos := parser sourceStream position.
+        endPos := parser sourceStream position1Based.
         endPos >= text size ifTrue:[
             ^ text
         ].
@@ -149,13 +149,13 @@
                 "/ mhmh - which is better ...
                 "/ alternative1: color rest after error in red
                 text 
-                    emphasizeFrom:(parser sourceStream position) 
+                    emphasizeFrom:(parser sourceStream position1Based) 
                     to:text size 
                     with:(#color->eColor).
             ] ifFalse:[
                 "/ alternative2: take original emphasis for rest
 
-                endPos := parser sourceStream position.
+                endPos := parser sourceStream position1Based.
                 endPos >= text size ifTrue:[
                     ^ text
                 ].
@@ -656,5 +656,5 @@
 !SyntaxHighlighter class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.40 2003-01-31 15:24:25 penk Exp $'
+    ^ '$Header: /cvs/stx/stx/libcomp/SyntaxHighlighter.st,v 1.41 2003-02-25 11:45:48 cg Exp $'
 ! !