*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Thu, 01 Feb 1996 21:21:07 +0100
changeset 177 0008b1a608e2
parent 176 500bf0f1a2ed
child 178 102f75c21a74
*** empty log message ***
TokenizedStream.st
--- a/TokenizedStream.st	Thu Feb 01 19:17:36 1996 +0100
+++ b/TokenizedStream.st	Thu Feb 01 21:21:07 1996 +0100
@@ -26,15 +26,15 @@
 
     operation:
 
-        characters are read from a real input stream
-        and the tokenizer dispatches to a token reading method by the help 
-        of an actionTable, which is indexed by the tokenType.
-        The tokenType itself is aquired via another table via
-        the characters ascii code.
+	characters are read from a real input stream
+	and the tokenizer dispatches to a token reading method by the help 
+	of an actionTable, which is indexed by the tokenType.
+	The tokenType itself is aquired via another table via
+	the characters ascii code.
 
-        By default, the table is setup to only read numbers
-        and identifiers. 
-        Whitespace is ignored, and all other characters return themself.
+	By default, the table is setup to only read numbers
+	and identifiers. 
+	Whitespace is ignored, and all other characters return themself.
 
     The returned tokens are either symbols (#Identifier, #Integer ..) or
     characters ($+ $, etc.)
@@ -54,188 +54,188 @@
 "
     simple example:
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'hello world, how much is 3 + 2'.
-        [s atEnd] whileFalse:[
-            Transcript showCr:(s next).
-        ].
+	s := TokenizedStream on:'hello world, how much is 3 + 2'.
+	[s atEnd] whileFalse:[
+	    Transcript showCr:(s next).
+	].
 
 
     simple example2:
 
-        |s token|
+	|s token|
 
-        s := TokenizedStream on:'foo bar baz  3 + 2'.
-        [s atEnd] whileFalse:[
-            token := s next.
-            token == #Identifier ifTrue:[
-                Transcript showCr:(token , ' name=' , s tokenName).
-            ] ifFalse:[
-                token == #Integer ifTrue:[
-                    Transcript showCr:(token , ' value=' , s tokenValue printString).
-                ] ifFalse:[
-                    Transcript showCr:token.
-                ]
-            ]
-        ].
+	s := TokenizedStream on:'foo bar baz  3 + 2'.
+	[s atEnd] whileFalse:[
+	    token := s next.
+	    token == #Identifier ifTrue:[
+		Transcript showCr:(token , ' name=' , s tokenName).
+	    ] ifFalse:[
+		token == #Integer ifTrue:[
+		    Transcript showCr:(token , ' value=' , s tokenValue printString).
+		] ifFalse:[
+		    Transcript showCr:token.
+		]
+	    ]
+	].
 
 
     reading expressions:
 
-        |s num1 num2|
+	|s num1 num2|
 
-        s := TokenizedStream on:'
+	s := TokenizedStream on:'
 3 + 2
 4 + 6
 1 + 2
 '.
-        [s atEnd] whileFalse:[
-            s next == #Integer ifTrue:[
-                num1 := s tokenValue.
-                s next == $+ ifTrue:[
-                    s next == #Integer ifTrue:[
-                        num2 := s tokenValue.
-                        Transcript showCr:num1 printString 
-                                          , ' + ' 
-                                          , num2 printString 
-                                          , ' => ' 
-                                          , (num1 + num2) printString.
-                    ]
-                ]
-            ]
-        ].
+	[s atEnd] whileFalse:[
+	    s next == #Integer ifTrue:[
+		num1 := s tokenValue.
+		s next == $+ ifTrue:[
+		    s next == #Integer ifTrue:[
+			num2 := s tokenValue.
+			Transcript showCr:num1 printString 
+					  , ' + ' 
+					  , num2 printString 
+					  , ' => ' 
+					  , (num1 + num2) printString.
+		    ]
+		]
+	    ]
+	].
 
 
     with eol-comments:
 
-        |s num1 num2|
+	|s num1 num2|
 
-        s := TokenizedStream on:'
+	s := TokenizedStream on:'
 3 + 2
 ; this is a comment
 4 + 6
 1 + 2
 '.
-        s eolCommentCharacter:$;.
+	s eolCommentCharacter:$;.
 
-        [s atEnd] whileFalse:[
-            s next == #Integer ifTrue:[
-                num1 := s tokenValue.
-                s next == $+ ifTrue:[
-                    s next == #Integer ifTrue:[
-                        num2 := s tokenValue.
-                        Transcript showCr:num1 printString 
-                                          , ' + ' 
-                                          , num2 printString 
-                                          , ' => ' 
-                                          , (num1 + num2) printString.
-                    ]
-                ]
-            ]
-        ].
+	[s atEnd] whileFalse:[
+	    s next == #Integer ifTrue:[
+		num1 := s tokenValue.
+		s next == $+ ifTrue:[
+		    s next == #Integer ifTrue:[
+			num2 := s tokenValue.
+			Transcript showCr:num1 printString 
+					  , ' + ' 
+					  , num2 printString 
+					  , ' => ' 
+					  , (num1 + num2) printString.
+		    ]
+		]
+	    ]
+	].
 
     allowing float & negative numbers (the default):
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'1.23 4.56 7 8 9 -5 5 -5.0 5.0'.
-        [s atEnd] whileFalse:[
-            s next.
-            Transcript showCr:(s tokenType displayString, ' value=' , s tokenValue printString).
-        ].
+	s := TokenizedStream on:'1.23 4.56 7 8 9 -5 5 -5.0 5.0'.
+	[s atEnd] whileFalse:[
+	    s next.
+	    Transcript showCr:(s tokenType displayString, ' value=' , s tokenValue printString).
+	].
 
 
     not allowing float numbers :
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'1.23 4.56 7 8 9 -5 5 -5.0 5.0 '.
-        s allowFloatNumbers:false.
+	s := TokenizedStream on:'1.23 4.56 7 8 9 -5 5 -5.0 5.0 '.
+	s allowFloatNumbers:false.
 
-        [s atEnd] whileFalse:[
-            s next.
-            Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString).
-        ].
+	[s atEnd] whileFalse:[
+	    s next.
+	    Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString).
+	].
 
 
     not allowing negative numbers :
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'1.23 4.56 7 8 9 -5 5 -5.0 5.0'.
-        s numbersAreSigned:false.
+	s := TokenizedStream on:'1.23 4.56 7 8 9 -5 5 -5.0 5.0'.
+	s numbersAreSigned:false.
 
-        [s atEnd] whileFalse:[
-            s next.
-            Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString).
-        ].
+	[s atEnd] whileFalse:[
+	    s next.
+	    Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString).
+	].
 
 
     no radix numbers (the default):
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'0x1234 16r1234'.
+	s := TokenizedStream on:'0x1234 16r1234'.
 
-        [s atEnd] whileFalse:[
-            s next.
-            Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString , ' name=' , s tokenName displayString).
-        ].
+	[s atEnd] whileFalse:[
+	    s next.
+	    Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString , ' name=' , s tokenName displayString).
+	].
 
 
     C-style radix numbers:
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'0x1234 16r1234'.
-        s actionTable at:#digit put:[:s :char | s nextCNumber].
+	s := TokenizedStream on:'0x1234 16r1234'.
+	s actionTable at:#digit put:[:s :char | s nextCNumber].
 
-        [s atEnd] whileFalse:[
-            s next.
-            Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString , ' name=' , s tokenName displayString).
-        ].
+	[s atEnd] whileFalse:[
+	    s next.
+	    Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString , ' name=' , s tokenName displayString).
+	].
 
 
     smalltalk-style radix numbers:
 
-        |s|
+	|s|
 
-        s := TokenizedStream on:'0x1234 16r1234'.
-        s actionTable at:#digit put:[:s :char | s nextSmalltalkNumber].
+	s := TokenizedStream on:'0x1234 16r1234'.
+	s actionTable at:#digit put:[:s :char | s nextSmalltalkNumber].
 
-        [s atEnd] whileFalse:[
-            s next.
-            Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString , ' name=' , s tokenName displayString).
-        ].
+	[s atEnd] whileFalse:[
+	    s next.
+	    Transcript showCr:(s tokenType displayString , ' value= ' , s tokenValue printString , ' name=' , s tokenName displayString).
+	].
 
 
     scan the '/etc/services' file:
 
-        |s t service port protocol|
+	|s t service port protocol|
 
-        s := TokenizedStream on:'/etc/services' asFilename readStream.
-        s eolCommentCharacter:$#.
-        s typeTable at:($- asciiValue) put:#letter.
+	s := TokenizedStream on:'/etc/services' asFilename readStream.
+	s eolCommentCharacter:$#.
+	s typeTable at:($- asciiValue) put:#letter.
 
-        [s atEnd] whileFalse:[
-            t := s next.
-            t == #Identifier ifTrue:[
-                service := s tokenName.
-                t := s next.
-                t == #Integer ifTrue:[
-                    port := s tokenValue.
-                    s next == $/ ifTrue:[
-                        t := s next.
-                        t == #Identifier ifTrue:[
-                            protocol := s tokenName.
-                            Transcript showCr:(service , ' is ' , protocol , ' port=' , port printString).
-                        ]
-                    ]
-                ]
-            ].
-            s skipToEol
-        ]
+	[s atEnd] whileFalse:[
+	    t := s next.
+	    t == #Identifier ifTrue:[
+		service := s tokenName.
+		t := s next.
+		t == #Integer ifTrue:[
+		    port := s tokenValue.
+		    s next == $/ ifTrue:[
+			t := s next.
+			t == #Identifier ifTrue:[
+			    protocol := s tokenName.
+			    Transcript showCr:(service , ' is ' , protocol , ' port=' , port printString).
+			]
+		    ]
+		]
+	    ].
+	    s skipToEol
+	]
 "
 ! !
 
@@ -247,23 +247,23 @@
 
     "kludge: action is nextColonOrAssign, but type is special"
     2 to:255 do:[:code |
-        DefaultTypes at:code put:(Character value:code).
+	DefaultTypes at:code put:(Character value:code).
     ].
 
     ($0 asciiValue) to:($9 asciiValue) do:[:index |
-        DefaultTypes at:index put:#digit.
+	DefaultTypes at:index put:#digit.
     ].
 
     ($a asciiValue) to:($z asciiValue) do:[:index |
-        DefaultTypes at:index put:#letter.
+	DefaultTypes at:index put:#letter.
     ].
     ($A asciiValue) to:($Z asciiValue) do:[:index |
-        DefaultTypes at:index put:#letter.
+	DefaultTypes at:index put:#letter.
     ].
 
     DefaultActions at:#letter put:[:s :char | s nextIdentifier].
     DefaultActions at:#digit  put:[:s :char | s nextNumber].
-    DefaultActions at:$-  put:[:s :char | s checkForNumberAfterSign].
+    DefaultActions at:$-  put:[:s :char | s nextSignedNumber].
 
     "
      TokenizedStream initialize
@@ -378,9 +378,9 @@
     self initialize.
 
     aStringOrStream isStream ifFalse:[
-        source := ReadStream on:aStringOrStream
+	source := ReadStream on:aStringOrStream
     ] ifTrue:[
-        source := aStringOrStream.
+	source := aStringOrStream.
     ].
 
     "Created: 1.2.1996 / 16:18:34 / cg"
@@ -389,17 +389,18 @@
 
 !TokenizedStream methodsFor:'reading'!
 
-checkForNumberAfterSign
+nextSignedNumber
     |next|
 
     source next.
     numbersAreSigned ifTrue:[
-        next := source peek .
-        (next notNil and:[(types at:next asciiValue) == #digit]) ifTrue:[
-            (actions at:#digit) value:self value:next.
-            tokenValue := tokenValue negated.
-        ]
-    ]
+	next := source peek .
+	(next notNil and:[(types at:next asciiValue) == #digit]) ifTrue:[
+	    (actions at:#digit) value:self value:next.
+	    tokenValue := tokenValue negated.
+	]
+    ].
+    ^ tokenType
 
     "Modified: 1.2.1996 / 19:02:46 / cg"
 !
@@ -415,53 +416,53 @@
 
     tokenRadix := 10.
     source peek == $0 ifTrue:[
-        source next.
-        source peek == $x ifTrue:[
-            source next.
-            tokenRadix := 16.
-        ] ifFalse:[
-            tokenRadix := 8
-        ]
+	source next.
+	source peek == $x ifTrue:[
+	    source next.
+	    tokenRadix := 16.
+	] ifFalse:[
+	    tokenRadix := 8
+	]
     ].
 
     value := Integer readFrom:source radix:tokenRadix.
     nextChar := source peek.
 
     (allowFloatNumbers and:[tokenRadix == 10]) ifTrue:[
-        (nextChar == $.) ifTrue:[
-            nextChar := source nextPeek.
-            (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
-                value := value asFloat + (self nextMantissa:tokenRadix).
-                nextChar := source peek
-            ] ifFalse:[
-                nextChar == (Character cr) ifTrue:[
-                    tokenLineNr := tokenLineNr + 1.
-                ].
-                peekChar := $.
-            ]
-        ].
-        ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
-            nextChar := source nextPeek.
-            (nextChar notNil and:[(nextChar isDigitRadix:tokenRadix) or:['+-' includes:nextChar]]) ifTrue:[
-                s := 1.
-                (nextChar == $+) ifTrue:[
-                    nextChar := source nextPeek
-                ] ifFalse:[
-                    (nextChar == $-) ifTrue:[
-                        nextChar := source nextPeek.
-                        s := s negated
-                    ]
-                ].
-                value := value asFloat
-                         * (10.0 raisedToInteger:((Integer readFrom:source radix:tokenRadix) * s))
-            ]
-        ].
+	(nextChar == $.) ifTrue:[
+	    nextChar := source nextPeek.
+	    (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
+		value := value asFloat + (self nextMantissa:tokenRadix).
+		nextChar := source peek
+	    ] ifFalse:[
+		nextChar == (Character cr) ifTrue:[
+		    tokenLineNr := tokenLineNr + 1.
+		].
+		peekChar := $.
+	    ]
+	].
+	((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+	    nextChar := source nextPeek.
+	    (nextChar notNil and:[(nextChar isDigitRadix:tokenRadix) or:['+-' includes:nextChar]]) ifTrue:[
+		s := 1.
+		(nextChar == $+) ifTrue:[
+		    nextChar := source nextPeek
+		] ifFalse:[
+		    (nextChar == $-) ifTrue:[
+			nextChar := source nextPeek.
+			s := s negated
+		    ]
+		].
+		value := value asFloat
+			 * (10.0 raisedToInteger:((Integer readFrom:source radix:tokenRadix) * s))
+	    ]
+	].
     ].
     tokenValue := value.
     (value isMemberOf:Float) ifTrue:[
-        tokenType := #Float
+	tokenType := #Float
     ] ifFalse:[
-        tokenType := #Integer
+	tokenType := #Integer
     ].
     ^ tokenType
 
@@ -481,23 +482,23 @@
 
     done := false.
     [done] whileFalse:[
-        nextChar isNil ifTrue:[
-            done := true
-        ] ifFalse:[
-            t := types at:(nextChar asciiValue).
-            done := (t ~~ #letter and:[t ~~ #digit]).
-        ].
-        done ifFalse:[
-            (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 isNil ifTrue:[
+	    done := true
+	] ifFalse:[
+	    t := types at:(nextChar asciiValue).
+	    done := (t ~~ #letter and:[t ~~ #digit]).
+	].
+	done ifFalse:[
+	    (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
+	]
     ].
     tokenType := #Identifier.
     tokenName := string copyTo:index.
@@ -524,9 +525,9 @@
     factor := 1.0 / radix.
     nextChar := source peek.
     [(nextChar notNil and:[nextChar isDigitRadix:radix])] whileTrue:[
-        value := value + (nextChar digitValue * factor).
-        factor := factor / radix.
-        nextChar := source nextPeek
+	value := value + (nextChar digitValue * factor).
+	factor := factor / radix.
+	nextChar := source nextPeek
     ].
     ^ value
 
@@ -540,40 +541,40 @@
     value := Integer readFrom:source radix:tokenRadix.
     nextChar := source peek.
     allowFloatNumbers ifTrue:[
-        (nextChar == $.) ifTrue:[
-            nextChar := source nextPeek.
-            (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
-                value := value asFloat + (self nextMantissa:tokenRadix).
-                nextChar := source peek
-            ] ifFalse:[
-                nextChar == (Character cr) ifTrue:[
-                    tokenLineNr := tokenLineNr + 1.
-                ].
-                peekChar := $.
-            ]
-        ].
-        ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
-            nextChar := source nextPeek.
-            (nextChar notNil and:[(nextChar isDigitRadix:tokenRadix) or:['+-' includes:nextChar]]) ifTrue:[
-                s := 1.
-                (nextChar == $+) ifTrue:[
-                    nextChar := source nextPeek
-                ] ifFalse:[
-                    (nextChar == $-) ifTrue:[
-                        nextChar := source nextPeek.
-                        s := s negated
-                    ]
-                ].
-                value := value asFloat
-                         * (10.0 raisedToInteger:((Integer readFrom:source radix:tokenRadix) * s))
-            ]
-        ].
+	(nextChar == $.) ifTrue:[
+	    nextChar := source nextPeek.
+	    (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
+		value := value asFloat + (self nextMantissa:tokenRadix).
+		nextChar := source peek
+	    ] ifFalse:[
+		nextChar == (Character cr) ifTrue:[
+		    tokenLineNr := tokenLineNr + 1.
+		].
+		peekChar := $.
+	    ]
+	].
+	((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+	    nextChar := source nextPeek.
+	    (nextChar notNil and:[(nextChar isDigitRadix:tokenRadix) or:['+-' includes:nextChar]]) ifTrue:[
+		s := 1.
+		(nextChar == $+) ifTrue:[
+		    nextChar := source nextPeek
+		] ifFalse:[
+		    (nextChar == $-) ifTrue:[
+			nextChar := source nextPeek.
+			s := s negated
+		    ]
+		].
+		value := value asFloat
+			 * (10.0 raisedToInteger:((Integer readFrom:source radix:tokenRadix) * s))
+	    ]
+	].
     ].
     tokenValue := value.
     (value isMemberOf:Float) ifTrue:[
-        tokenType := #Float
+	tokenType := #Float
     ] ifFalse:[
-        tokenType := #Integer
+	tokenType := #Integer
     ].
     ^ tokenType
 
@@ -588,52 +589,52 @@
     value := Integer readFrom:source radix:tokenRadix.
     nextChar := source peek.
     (nextChar == $r) ifTrue:[
-        tokenRadix := value.
-        source next.
-        s := 1.
-        source peek == $- ifTrue:[
-            source next.
-            s := -1
-        ].
-        value := Integer readFrom:source radix:tokenRadix.
-        value := value * s.
-        nextChar := source peek
+	tokenRadix := value.
+	source next.
+	s := 1.
+	source peek == $- ifTrue:[
+	    source next.
+	    s := -1
+	].
+	value := Integer readFrom:source radix:tokenRadix.
+	value := value * s.
+	nextChar := source peek
     ].
     allowFloatNumbers ifTrue:[
-        (nextChar == $.) ifTrue:[
-            nextChar := source nextPeek.
-            (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
-                value := value asFloat + (self nextMantissa:tokenRadix).
-                nextChar := source peek
-            ] ifFalse:[
-                nextChar == (Character cr) ifTrue:[
-                    tokenLineNr := tokenLineNr + 1.
-                ].
-                peekChar := $.
-            ]
-        ].
-        ((nextChar == $e) or:[nextChar == $E]) ifTrue:[
-            nextChar := source nextPeek.
-            (nextChar notNil and:[(nextChar isDigitRadix:tokenRadix) or:['+-' includes:nextChar]]) ifTrue:[
-                s := 1.
-                (nextChar == $+) ifTrue:[
-                    nextChar := source nextPeek
-                ] ifFalse:[
-                    (nextChar == $-) ifTrue:[
-                        nextChar := source nextPeek.
-                        s := s negated
-                    ]
-                ].
-                value := value asFloat
-                         * (10.0 raisedToInteger:((Integer readFrom:source radix:tokenRadix) * s))
-            ]
-        ].
+	(nextChar == $.) ifTrue:[
+	    nextChar := source nextPeek.
+	    (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
+		value := value asFloat + (self nextMantissa:tokenRadix).
+		nextChar := source peek
+	    ] ifFalse:[
+		nextChar == (Character cr) ifTrue:[
+		    tokenLineNr := tokenLineNr + 1.
+		].
+		peekChar := $.
+	    ]
+	].
+	((nextChar == $e) or:[nextChar == $E]) ifTrue:[
+	    nextChar := source nextPeek.
+	    (nextChar notNil and:[(nextChar isDigitRadix:tokenRadix) or:['+-' includes:nextChar]]) ifTrue:[
+		s := 1.
+		(nextChar == $+) ifTrue:[
+		    nextChar := source nextPeek
+		] ifFalse:[
+		    (nextChar == $-) ifTrue:[
+			nextChar := source nextPeek.
+			s := s negated
+		    ]
+		].
+		value := value asFloat
+			 * (10.0 raisedToInteger:((Integer readFrom:source radix:tokenRadix) * s))
+	    ]
+	].
     ].
     tokenValue := value.
     (value isMemberOf:Float) ifTrue:[
-        tokenType := #Float
+	tokenType := #Float
     ] ifFalse:[
-        tokenType := #Integer
+	tokenType := #Integer
     ].
     ^ tokenType
 
@@ -656,30 +657,30 @@
     inString := true.
 
     [inString] whileTrue:[
-        nextChar isNil ifTrue:[
-            self error:'unexpected end-of-input in String'.
-            tokenType := #EOF.
-            ^ tokenType
-        ].
-        (nextChar == Character cr) ifTrue:[
-            tokenLineNr := tokenLineNr + 1
-        ].
-        (nextChar == separator) ifTrue:[
-            (source peek == separator) ifTrue:[
-                source next
-            ] ifFalse:[
-                inString := false
-            ]
-        ].
-        inString ifTrue:[
-            string at:index put:nextChar.
-            (index == len) ifTrue:[
-                string := string , (String new:len).
-                len := len * 2
-            ].
-            index := index + 1.
-            nextChar := source next
-        ]
+	nextChar isNil ifTrue:[
+	    self error:'unexpected end-of-input in String'.
+	    tokenType := #EOF.
+	    ^ tokenType
+	].
+	(nextChar == Character cr) ifTrue:[
+	    tokenLineNr := tokenLineNr + 1
+	].
+	(nextChar == separator) ifTrue:[
+	    (source peek == separator) ifTrue:[
+		source next
+	    ] ifFalse:[
+		inString := false
+	    ]
+	].
+	inString ifTrue:[
+	    string at:index put:nextChar.
+	    (index == len) ifTrue:[
+		string := string , (String new:len).
+		len := len * 2
+	    ].
+	    index := index + 1.
+	    nextChar := source next
+	]
     ].
     tokenValue := string copyTo:(index - 1).
     tokenType := #String.
@@ -696,75 +697,75 @@
     tokenValue := tokenName := nil.
 
     peekChar notNil ifTrue:[
-        hereChar := peekChar.
-        peekChar := peekChar2.
-        peekChar2 := nil
+	hereChar := peekChar.
+	peekChar := peekChar2.
+	peekChar2 := nil
     ] ifFalse:[
-        skipping := true.
-        [skipping] whileTrue:[
-            outStream notNil ifTrue:[
-                [(hereChar := source peek) == Character space] whileTrue:[
-                    source next.
-                    outStream space. 
-                    outCol := outCol + 1.
-                ]
-            ] ifFalse:[
-                hereChar := source skipSeparatorsExceptCR.
-            ].
-            hereChar isNil ifTrue:[
-                tokenType := #EOF.
-                ^ tokenType
-            ].
-            hereChar == eolCharacter ifTrue:[
-                tokenLineNr := tokenLineNr + 1.
-                source next.
-                outStream notNil ifTrue:[
-                    outStream cr.
-                    outCol := 1
-                ].
-                eolIsSignificant ifTrue:[
-                    tokenType := #EOL.
-                    ^ tokenType
-                ]
-            ] ifFalse:[
-                hereChar == beginCommentCharacter ifTrue:[
-                    "start of a comment"
+	skipping := true.
+	[skipping] whileTrue:[
+	    outStream notNil ifTrue:[
+		[(hereChar := source peek) == Character space] whileTrue:[
+		    source next.
+		    outStream space. 
+		    outCol := outCol + 1.
+		]
+	    ] ifFalse:[
+		hereChar := source skipSeparatorsExceptCR.
+	    ].
+	    hereChar isNil ifTrue:[
+		tokenType := #EOF.
+		^ tokenType
+	    ].
+	    hereChar == eolCharacter ifTrue:[
+		tokenLineNr := tokenLineNr + 1.
+		source next.
+		outStream notNil ifTrue:[
+		    outStream cr.
+		    outCol := 1
+		].
+		eolIsSignificant ifTrue:[
+		    tokenType := #EOL.
+		    ^ tokenType
+		]
+	    ] ifFalse:[
+		hereChar == beginCommentCharacter ifTrue:[
+		    "start of a comment"
 
-                    self skipComment.
-                    hereChar := source peek.
-                ] ifFalse:[
-                    hereChar == eolCommentCharacter ifTrue:[
-                        "start of an eol comment"
+		    self skipComment.
+		    hereChar := source peek.
+		] ifFalse:[
+		    hereChar == eolCommentCharacter ifTrue:[
+			"start of an eol comment"
 
-                        self skipEolComment.
-                        hereChar := source peek.
-                    ] ifFalse:[
-                        skipping := false
-                    ]
-                ]
-            ]
-        ].
-        hereChar isNil ifTrue:[
-            tokenType := #EOF.
-            ^ tokenType
-        ]
+			self skipEolComment.
+			hereChar := source peek.
+		    ] ifFalse:[
+			skipping := false
+		    ]
+		]
+	    ]
+	].
+	hereChar isNil ifTrue:[
+	    tokenType := #EOF.
+	    ^ tokenType
+	]
     ].
     tokenPosition := source position.
 
     types notNil ifTrue:[
-        tokenType := types at:(hereChar asciiValue).
+	tokenType := types at:(hereChar asciiValue).
     ].
 
     actions notNil ifTrue:[
-        actionBlock := actions at:tokenType ifAbsent:nil.
-        actionBlock notNil ifTrue:[
-            ^ actionBlock value:self value:hereChar
-        ]
+	actionBlock := actions at:tokenType ifAbsent:nil.
+	actionBlock notNil ifTrue:[
+	    ^ actionBlock value:self value:hereChar
+	]
     ].
 
     source next.
     tokenType isNil ifTrue:[
-        tokenType := #Error.
+	tokenType := #Error.
     ].
     ^ tokenType
 
@@ -776,14 +777,14 @@
     hereChar := source peek.
 
     [hereChar notNil and:[hereChar ~~ endCommentCharacter]] whileTrue:[
-        hereChar == eolCharacter ifTrue:[
-            tokenLineNr := tokenLineNr + 1.
-        ].
-        outStream notNil ifTrue:[
-            outStream nextPut:hereChar.
-            outCol := outCol + 1
-        ].
-        hereChar := source nextPeek
+	hereChar == eolCharacter ifTrue:[
+	    tokenLineNr := tokenLineNr + 1.
+	].
+	outStream notNil ifTrue:[
+	    outStream nextPut:hereChar.
+	    outCol := outCol + 1
+	].
+	hereChar := source nextPeek
     ].
 
     "Created: 1.2.1996 / 17:35:24 / cg"
@@ -802,11 +803,11 @@
     hereChar := source peek.
 
     [hereChar notNil and:[hereChar ~~ eolCharacter]] whileTrue:[
-        outStream notNil ifTrue:[
-            outStream nextPut:hereChar.
-            outCol := outCol + 1
-        ].
-        hereChar := source nextPeek.
+	outStream notNil ifTrue:[
+	    outStream nextPut:hereChar.
+	    outCol := outCol + 1
+	].
+	hereChar := source nextPeek.
     ].
     tokenLineNr := tokenLineNr + 1.
 
@@ -826,6 +827,6 @@
 !TokenizedStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/TokenizedStream.st,v 1.6 1996-02-01 18:17:36 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/TokenizedStream.st,v 1.7 1996-02-01 20:21:07 cg Exp $'
 ! !
 TokenizedStream initialize!