Scanner.st
changeset 45 e8331ba8ad5d
parent 41 62214c6ca833
child 49 02660b790c3e
--- a/Scanner.st	Sun Oct 02 23:01:25 1994 +0100
+++ b/Scanner.st	Mon Oct 10 01:58:23 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -12,25 +12,25 @@
 
 Object subclass:#Scanner
        instanceVariableNames:'source 
-                              token tokenType tokenPosition tokenValue
-                              tokenName tokenLineNr tokenRadix
-                              thisChar peekChar
-                              requestor exitBlock
-                              errorFlag 
-                              ignoreErrors ignoreWarnings
-                              saveComments currentComments
-                              warnSTXSpecialComment
-                              outStream outCol'
-          classVariableNames:'TypeArray ActionArray Warnings WarnSTXSpecials'
-            poolDictionaries:''
-                    category:'System-Compiler'
+			      token tokenType tokenPosition tokenValue
+			      tokenName tokenLineNr tokenRadix
+			      thisChar peekChar
+			      requestor exitBlock
+			      errorFlag 
+			      ignoreErrors ignoreWarnings
+			      saveComments currentComments
+			      warnSTXSpecialComment
+			      outStream outCol'
+	  classVariableNames:'TypeArray ActionArray Warnings WarnSTXSpecials'
+	    poolDictionaries:''
+		    category:'System-Compiler'
 !
 
 Scanner comment:'
 COPYRIGHT (c) 1989 by Claus Gittinger
-             All Rights Reserved
+	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.12 1994-08-23 23:05:01 claus Exp $
+$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.13 1994-10-10 00:57:45 claus Exp $
 '!
 
 !Scanner class methodsFor:'documentation'!
@@ -38,7 +38,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -51,7 +51,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.12 1994-08-23 23:05:01 claus Exp $
+$Header: /cvs/stx/stx/libcomp/Scanner.st,v 1.13 1994-10-10 00:57:45 claus Exp $
 "
 !
 
@@ -74,7 +74,7 @@
 warnings:aBoolean
     "this allows turning on/off warnings; the default is on.
      You can turn off warnings in your 'private.rc' file with
-         Compiler warnings:false
+	 Compiler warnings:false
     "
 
     Warnings := aBoolean
@@ -84,7 +84,7 @@
     "this allows turning on/off warnings about stx specials.
      If you get bored by those warnings, turn them off by adding
      a line as:
-        Compiler warnSTXSpecials:false
+	Compiler warnSTXSpecials:false
      in your 'private.rc' file"
 
     WarnSTXSpecials := aBoolean
@@ -100,26 +100,26 @@
 
     block := [:s :char | s nextNumber].
     ($0 asciiValue) to:($9 asciiValue) do:[:index |
-        ActionArray at:index put:block
+	ActionArray at:index put:block
     ].
 
     block := [:s :char | s nextIdentifier].
     ($a asciiValue) to:($z asciiValue) do:[:index |
-        ActionArray at:index put:block
+	ActionArray at:index put:block
     ].
     ($A asciiValue) to:($Z asciiValue) do:[:index |
-        ActionArray at:index put:block
+	ActionArray at:index put:block
     ].
 
     block := [:s :char | s nextSpecial].
     #( $& $- $+ $= $* $/ $\ $< $> $~ $@ $, $? ) do:[:binop |
-        TypeArray at:(binop asciiValue) put:#special.
-        ActionArray at:(binop asciiValue) put:block
+	TypeArray at:(binop asciiValue) put:#special.
+	ActionArray at:(binop asciiValue) put:block
     ].
 
     block := [:s :char | s nextToken:char].
     #( $; $. $( $) $[ $] $!! $^ $| $_ ) do:[:ch |
-        ActionArray at:(ch asciiValue) put:block
+	ActionArray at:(ch asciiValue) put:block
     ].
 
     "kludge: action is characterToken, but type is special"
@@ -145,9 +145,9 @@
     errorFlag := false.
     tokenLineNr := 1.
     aStringOrStream isStream ifFalse:[
-        source := ReadStream on:aStringOrStream
+	source := ReadStream on:aStringOrStream
     ] ifTrue:[
-        source := aStringOrStream.
+	source := aStringOrStream.
     ].
     currentComments := nil.
     saveComments := false.
@@ -156,7 +156,7 @@
     warnSTXSpecialComment := WarnSTXSpecials.
 
     ActionArray isNil ifTrue:[
-        self class setupActions
+	self class setupActions
     ]
 !
 
@@ -195,7 +195,7 @@
      one token too many"
 
     (tokenType == #EOF) ifFalse:[
-        source position:tokenPosition
+	source position:tokenPosition
     ]
 !
 
@@ -205,11 +205,11 @@
 
 endComment:comment
     saveComments ifTrue:[
-        currentComments isNil ifTrue:[
-            currentComments := OrderedCollection with:comment
-        ] ifFalse:[
-            currentComments add:comment
-        ]
+	currentComments isNil ifTrue:[
+	    currentComments := OrderedCollection with:comment
+	] ifFalse:[
+	    currentComments add:comment
+	]
     ].
 ! !
 
@@ -219,9 +219,9 @@
     "show an errormessage on the Transcript"
 
     ignoreErrors ifFalse:[
-        Smalltalk silentLoading == true ifFalse:[
-            Transcript showCr:(pos printString , ' ' , aMessage)
-        ]
+	Smalltalk silentLoading == true ifFalse:[
+	    Transcript showCr:(pos printString , ' ' , aMessage)
+	]
     ]
 !
 
@@ -231,8 +231,8 @@
      Return the result passed back by the requestor."
 
     requestor isNil ifTrue:[
-        self showErrorMessage:aMessage position:position.
-        ^ false
+	self showErrorMessage:aMessage position:position.
+	^ false
     ].
 
     ^ requestor error:aMessage position:position to:endPos
@@ -244,10 +244,10 @@
      Return the result passed back by the requestor."
 
     requestor isNil ifTrue:[
-        ignoreWarnings ifFalse:[
-            self showErrorMessage:aMessage position:position.
-        ].
-        ^ false
+	ignoreWarnings ifFalse:[
+	    self showErrorMessage:aMessage position:position.
+	].
+	^ false
     ].
     ^ requestor warning:aMessage position:position to:endPos
 !
@@ -315,13 +315,13 @@
     positions := OrderedCollection new.
 
     [(t := self nextToken) ~~ #EOF] whileTrue:[
-        searchType == t ifTrue:[
-            (searchName isNil or:[tokenName = searchName]) ifTrue:[
-                (searchValue isNil or:[tokenValue = searchValue]) ifTrue:[
-                    positions add:tokenPosition.
-                ]
-            ]
-        ]
+	searchType == t ifTrue:[
+	    (searchName isNil or:[tokenName = searchName]) ifTrue:[
+		(searchValue isNil or:[tokenValue = searchValue]) ifTrue:[
+		    positions add:tokenPosition.
+		]
+	    ]
+	]
     ].
 
     ^ positions
@@ -342,8 +342,8 @@
 
     self beginComment.
     outStream notNil ifTrue:[
-        outStream nextPut:Character doubleQuote.
-        outCol := outCol + 1
+	outStream nextPut:Character doubleQuote.
+	outCol := outCol + 1
     ].
 
     startPos := source position.
@@ -358,61 +358,61 @@
       change it without notice)"
 
     thisChar == $/ ifTrue:[
-        [thisChar notNil and:[thisChar ~~ Character cr]] whileTrue:[
-            saveComments ifTrue:[
-                comment := comment copyWith:thisChar
-            ].
-            outStream notNil ifTrue:[
-                outStream nextPut:thisChar.
-                outCol := outCol + 1
-            ].
-            thisChar := source nextPeek.
-        ].
-        tokenLineNr := tokenLineNr + 1.
-        ignoreWarnings ifFalse:[
-            warnSTXSpecialComment ifTrue:[
-                self warning:'end-of-line comments are a nonstandard feature of ST/X' 
-                     position:startPos to:(source position).
-                "
-                 only warn once
-                "
-                warnSTXSpecialComment := false
-            ]
-        ].
-        outStream notNil ifTrue:[
-            outStream cr.
-            outCol := 1
-        ].
+	[thisChar notNil and:[thisChar ~~ Character cr]] whileTrue:[
+	    saveComments ifTrue:[
+		comment := comment copyWith:thisChar
+	    ].
+	    outStream notNil ifTrue:[
+		outStream nextPut:thisChar.
+		outCol := outCol + 1
+	    ].
+	    thisChar := source nextPeek.
+	].
+	tokenLineNr := tokenLineNr + 1.
+	ignoreWarnings ifFalse:[
+	    warnSTXSpecialComment ifTrue:[
+		self warning:'end-of-line comments are a nonstandard feature of ST/X' 
+		     position:startPos to:(source position).
+		"
+		 only warn once
+		"
+		warnSTXSpecialComment := false
+	    ]
+	].
+	outStream notNil ifTrue:[
+	    outStream cr.
+	    outCol := 1
+	].
     ] ifFalse:[
-        [thisChar notNil and:[thisChar ~~ (Character doubleQuote)]] whileTrue:[
-            thisChar == (Character cr) ifTrue:[
-                tokenLineNr := tokenLineNr + 1.
-            ].
-            saveComments ifTrue:[
-                comment := comment copyWith:thisChar
-            ].
-            outStream notNil ifTrue:[
-                outStream nextPut:thisChar.
-                outCol := outCol + 1
-            ].
-            thisChar := source nextPeek
-        ].
-        thisChar isNil ifTrue:[
-            self warning:'unclosed comment' position:startPos to:(source position)
-        ] ifFalse:[
-            outStream notNil ifTrue:[
-                outStream nextPut:(Character doubleQuote).
-                outCol := outCol + 1
-            ].
-        ]
+	[thisChar notNil and:[thisChar ~~ (Character doubleQuote)]] whileTrue:[
+	    thisChar == (Character cr) ifTrue:[
+		tokenLineNr := tokenLineNr + 1.
+	    ].
+	    saveComments ifTrue:[
+		comment := comment copyWith:thisChar
+	    ].
+	    outStream notNil ifTrue:[
+		outStream nextPut:thisChar.
+		outCol := outCol + 1
+	    ].
+	    thisChar := source nextPeek
+	].
+	thisChar isNil ifTrue:[
+	    self warning:'unclosed comment' position:startPos to:(source position)
+	] ifFalse:[
+	    outStream notNil ifTrue:[
+		outStream nextPut:(Character doubleQuote).
+		outCol := outCol + 1
+	    ].
+	]
     ].
 
     saveComments ifTrue:[
-        currentComments isNil ifTrue:[
-            currentComments := OrderedCollection with:comment
-        ] ifFalse:[
-            currentComments add:comment
-        ]
+	currentComments isNil ifTrue:[
+	    currentComments := OrderedCollection with:comment
+	] ifFalse:[
+	    currentComments add:comment
+	]
     ].
 
     "skip final dQuote or cr"
@@ -427,53 +427,53 @@
     |skipping actionBlock|
 
     peekChar notNil ifTrue:[
-        thisChar := peekChar.
-        peekChar := nil
+	thisChar := peekChar.
+	peekChar := nil
     ] ifFalse:[
-        skipping := true.
-        [skipping] whileTrue:[
-            outStream notNil ifTrue:[
-                [(thisChar := source peek) == Character space] whileTrue:[
-                    source next.
-                    outStream space. 
-                    outCol := outCol + 1.
-                ]
-            ] ifFalse:[
-                thisChar := source skipSeparatorsExceptCR.
-            ].
-            thisChar == (Character cr) ifTrue:[
-                tokenLineNr := tokenLineNr + 1.
-                source next.
-                outStream notNil ifTrue:[
-                    outStream cr.
-                    outCol := 1
-                ]
-            ] ifFalse:[
-                thisChar == (Character doubleQuote) ifTrue:[
-                    "start of a comment"
+	skipping := true.
+	[skipping] whileTrue:[
+	    outStream notNil ifTrue:[
+		[(thisChar := source peek) == Character space] whileTrue:[
+		    source next.
+		    outStream space. 
+		    outCol := outCol + 1.
+		]
+	    ] ifFalse:[
+		thisChar := source skipSeparatorsExceptCR.
+	    ].
+	    thisChar == (Character cr) ifTrue:[
+		tokenLineNr := tokenLineNr + 1.
+		source next.
+		outStream notNil ifTrue:[
+		    outStream cr.
+		    outCol := 1
+		]
+	    ] ifFalse:[
+		thisChar == (Character doubleQuote) ifTrue:[
+		    "start of a comment"
 
-                    self skipComment.
-                    thisChar := source peek.
-                ] ifFalse:[
-                    skipping := false
-                ]
-            ]
-        ].
-        thisChar isNil ifTrue:[
-            tokenType := #EOF.
-            ^ tokenType
-        ]
+		    self skipComment.
+		    thisChar := source peek.
+		] ifFalse:[
+		    skipping := false
+		]
+	    ]
+	].
+	thisChar isNil ifTrue:[
+	    tokenType := #EOF.
+	    ^ tokenType
+	]
     ].
     tokenPosition := source position.
 
     actionBlock := ActionArray at:(thisChar asciiValue).
     actionBlock notNil ifTrue:[
-        ^ actionBlock value:self value:thisChar
+	^ actionBlock value:self value:thisChar
     ].
 
     self syntaxError:('invalid character: ''' , thisChar asString , ''' ',
-                      '(' , thisChar asciiValue printString , ')')
-            position:tokenPosition to:tokenPosition.
+		      '(' , thisChar asciiValue printString , ')')
+	    position:tokenPosition to:tokenPosition.
     tokenType := #Error.
     ^ #Error
 !
@@ -488,10 +488,10 @@
     "colon has been read - look for = to make it an assign"
 
     (source nextPeek == $=) ifTrue:[
-        source next.
-        tokenType := $_
+	source next.
+	tokenType := $_
     ] ifFalse:[
-        tokenType := $:
+	tokenType := $:
     ].
     ^ tokenType
 !
@@ -505,30 +505,30 @@
     firstChar := source next.
     secondChar := source peek.
     (firstChar == $-) ifTrue:[
-        secondChar isDigit ifTrue:[
-            self nextNumber.
-            tokenValue := tokenValue negated.
-            ^ tokenType
-        ]
+	secondChar isDigit ifTrue:[
+	    self nextNumber.
+	    tokenValue := tokenValue negated.
+	    ^ tokenType
+	]
     ].
     string := firstChar asString.
     secondChar notNil ifTrue:[
-        ((TypeArray at:(secondChar asciiValue)) == #special) ifTrue:[
-            (secondChar == $-) ifTrue:[
-                "special- look if minus belongs to number following"
-                p := source position.
-                source next.
-                thirdChar := source peek.
-                source position:p.
-                thirdChar isDigit ifTrue:[
-                    tokenName := string.
-                    tokenType := #BinaryOperator.
-                    ^ tokenType
-                ]
-            ].
-            source next.
-            string := string copyWith:secondChar
-        ].
+	((TypeArray at:(secondChar asciiValue)) == #special) ifTrue:[
+	    (secondChar == $-) ifTrue:[
+		"special- look if minus belongs to number following"
+		p := source position.
+		source next.
+		thirdChar := source peek.
+		source position:p.
+		thirdChar isDigit ifTrue:[
+		    tokenName := string.
+		    tokenType := #BinaryOperator.
+		    ^ tokenType
+		]
+	    ].
+	    source next.
+	    string := string copyWith:secondChar
+	].
     ].
     tokenName := string.
     tokenType := #BinaryOperator.
@@ -543,10 +543,10 @@
     source next.
     nextChar := source next.
     nextChar notNil ifTrue:[
-        tokenValue := nextChar.
-        tokenType := #Character
+	tokenValue := nextChar.
+	tokenType := #Character
     ] ifFalse:[
-        tokenType := #EOF
+	tokenType := #EOF
     ].
     ^ tokenType
 !
@@ -558,9 +558,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
 !
@@ -572,50 +572,50 @@
     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
     ].
     (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 := 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 := 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
 !
@@ -630,18 +630,18 @@
     index := 0.
     max := 10.
     [true] whileTrue:[
-        (nextChar notNil and:[nextChar isAlphaNumeric]) ifFalse:[
-            ^ string copyTo:index
-        ].
-        (index == max) ifTrue:[
-            oldString := string.
-            string := String new:(max * 2).
-            string replaceFrom:1 to:max with:oldString.
-            max := max * 2
-        ].
-        index := index + 1.
-        string at:index put:nextChar.
-        nextChar := source nextPeek
+	(nextChar notNil and:[nextChar isLetterOrDigit]) ifFalse:[
+	    ^ string copyTo:index
+	].
+	(index == max) ifTrue:[
+	    oldString := string.
+	    string := String new:(max * 2).
+	    string replaceFrom:1 to:max with:oldString.
+	    max := max * 2
+	].
+	index := index + 1.
+	string at:index put:nextChar.
+	nextChar := source nextPeek
     ]
 !
 
@@ -651,29 +651,29 @@
     string := source nextWord "self nextId".
     nextChar := source peek.
     (nextChar == $:) ifTrue:[
-        source next.
-        (source peek == $=) ifFalse:[
-            tokenName := string copyWith:nextChar.
-            tokenType := #Keyword.
-            ^ self
-        ].
-        peekChar := $_
+	source next.
+	(source peek == $=) ifFalse:[
+	    tokenName := string copyWith:nextChar.
+	    tokenType := #Keyword.
+	    ^ self
+	].
+	peekChar := $_
     ].
     tokenName := string.
     firstChar := string at:1.
     (firstChar == $s) ifTrue:[
-        (string = 'self') ifTrue:[tokenType := #Self. ^self].
-        (string = 'super') ifTrue:[tokenType := #Super. ^self]
+	(string = 'self') ifTrue:[tokenType := #Self. ^self].
+	(string = 'super') ifTrue:[tokenType := #Super. ^self]
     ].
     (firstChar == $n) ifTrue:[
-        (string = 'nil') ifTrue:[tokenType := #Nil. ^self]
+	(string = 'nil') ifTrue:[tokenType := #Nil. ^self]
     ].
     (firstChar == $t) ifTrue:[
-        (string = 'true') ifTrue:[tokenType := #True. ^self].
-        (string = 'thisContext') ifTrue:[tokenType := #ThisContext. ^self]
+	(string = 'true') ifTrue:[tokenType := #True. ^self].
+	(string = 'thisContext') ifTrue:[tokenType := #ThisContext. ^self]
     ].
     (firstChar == $f) ifTrue:[
-        (string = 'false') ifTrue:[tokenType := #False. ^self]
+	(string = 'false') ifTrue:[tokenType := #False. ^self]
     ].
     tokenType := #Identifier.
     ^ tokenType
@@ -689,35 +689,35 @@
     len := 500.
     index := 1.
     (nextChar == ${) ifTrue:[
-        nextChar := source nextPeek.
-        inPrimitive := true.
-        [inPrimitive] whileTrue:[
-            [nextChar == $%] whileFalse:[
-                string at:index put:nextChar.
-                (index == len) ifTrue:[
-                    string := string , (String new:len).
-                    len := len * 2
-                ].
-                index := index + 1.
-                nextChar := source next
-            ].
-            (source peek == $}) ifTrue:[
-                inPrimitive := false
-            ] ifFalse:[
-                string at:index put:nextChar.
-                (index == len) ifTrue:[
-                    string := string , (String new:len).
-                    len := len * 2
-                ].
-                index := index + 1.
-                nextChar := source next
-            ]
-        ].
-        source next.
-        tokenValue := string copyTo:(index - 1).
-        tokenType := #Primitive.
-        tokenLineNr := tokenLineNr + (tokenValue occurrencesOf:(Character cr)).
-        ^ tokenType
+	nextChar := source nextPeek.
+	inPrimitive := true.
+	[inPrimitive] whileTrue:[
+	    [nextChar == $%] whileFalse:[
+		string at:index put:nextChar.
+		(index == len) ifTrue:[
+		    string := string , (String new:len).
+		    len := len * 2
+		].
+		index := index + 1.
+		nextChar := source next
+	    ].
+	    (source peek == $}) ifTrue:[
+		inPrimitive := false
+	    ] ifFalse:[
+		string at:index put:nextChar.
+		(index == len) ifTrue:[
+		    string := string , (String new:len).
+		    len := len * 2
+		].
+		index := index + 1.
+		nextChar := source next
+	    ]
+	].
+	source next.
+	tokenValue := string copyTo:(index - 1).
+	tokenType := #Primitive.
+	tokenLineNr := tokenLineNr + (tokenValue occurrencesOf:(Character cr)).
+	^ tokenType
     ].
 
     "a % alone is a binary operator"
@@ -726,7 +726,7 @@
     ^ tokenType.
 "
     self syntaxError:('invalid character: ''' , nextChar asString , '''')
-            position:tokenPosition to:(tokenPosition + 1).
+	    position:tokenPosition to:(tokenPosition + 1).
     ^ #Error
 "
 !
@@ -736,66 +736,66 @@
 
     nextChar := source nextPeek.
     nextChar notNil ifTrue:[
-        nextChar isAlphaNumeric ifTrue:[
-            string := ''.
-            [nextChar notNil and:[nextChar isAlphaNumeric]] whileTrue:[
-                string := string , (source nextWord "self nextId").
-                nextChar := source peek.
-                (nextChar == $:) ifFalse:[
-                    tokenValue := string asSymbol.
-                    tokenType := #Symbol.
-                    ^ tokenType
-                ].
-                string := string copyWith:nextChar.
-                nextChar := source nextPeek
-            ].
-            tokenValue := string asSymbol.
-            tokenType := #Symbol.
-            ^ tokenType
-        ].
-        (nextChar == $( ) ifTrue:[
-            source next.
-            tokenType := #HashLeftParen.
-            ^ tokenType
-        ].
-        (nextChar == $[ ) ifTrue:[
-            "it seems that ST-80 supports Constant ByteArrays as #[...]
-             (seen in a PD program)"
-            source next.
-            tokenType := #HashLeftBrack.
-            ^ tokenType
-        ].
-        (nextChar == $' ) ifTrue:[
-            "it seems that ST-80 supports arbitrary symbols as #'...'
-             (seen in a PD program)"
-            self nextString.
-            tokenValue := tokenValue asSymbol.
-            tokenType := #Symbol.
-            ^ tokenType
-        ].
-        ((TypeArray at:(nextChar asciiValue)) == #special) ifTrue:[
-            string := source next asString.
-            nextChar := source peek.
-            nextChar notNil ifTrue:[
-                ((TypeArray at:(nextChar asciiValue)) == #special) ifTrue:[
-                    source next.
-                    string := string copyWith:nextChar
-                ]
-            ].
-            tokenValue := string asSymbol.
-            tokenType := #Symbol.
-            ^ tokenType
-        ]
+	nextChar isLetterOrDigit ifTrue:[
+	    string := ''.
+	    [nextChar notNil and:[nextChar isLetterOrDigit]] whileTrue:[
+		string := string , (source nextWord "self nextId").
+		nextChar := source peek.
+		(nextChar == $:) ifFalse:[
+		    tokenValue := string asSymbol.
+		    tokenType := #Symbol.
+		    ^ tokenType
+		].
+		string := string copyWith:nextChar.
+		nextChar := source nextPeek
+	    ].
+	    tokenValue := string asSymbol.
+	    tokenType := #Symbol.
+	    ^ tokenType
+	].
+	(nextChar == $( ) ifTrue:[
+	    source next.
+	    tokenType := #HashLeftParen.
+	    ^ tokenType
+	].
+	(nextChar == $[ ) ifTrue:[
+	    "it seems that ST-80 supports Constant ByteArrays as #[...]
+	     (seen in a PD program)"
+	    source next.
+	    tokenType := #HashLeftBrack.
+	    ^ tokenType
+	].
+	(nextChar == $' ) ifTrue:[
+	    "it seems that ST-80 supports arbitrary symbols as #'...'
+	     (seen in a PD program)"
+	    self nextString.
+	    tokenValue := tokenValue asSymbol.
+	    tokenType := #Symbol.
+	    ^ tokenType
+	].
+	((TypeArray at:(nextChar asciiValue)) == #special) ifTrue:[
+	    string := source next asString.
+	    nextChar := source peek.
+	    nextChar notNil ifTrue:[
+		((TypeArray at:(nextChar asciiValue)) == #special) ifTrue:[
+		    source next.
+		    string := string copyWith:nextChar
+		]
+	    ].
+	    tokenValue := string asSymbol.
+	    tokenType := #Symbol.
+	    ^ tokenType
+	]
     ].
     "this allows hash to be used as binop -
      I dont know, if this is correct ..."
 
     tokenName := '#'.
-    tokenType := BinaryOperator.
+    tokenType := #BinaryOperator.
     ^ tokenType
 "
     self syntaxError:'unexpected end-of-input in Symbol'
-            position:tokenPosition to:(tokenPosition + 1).
+	    position:tokenPosition to:(tokenPosition + 1).
     ^ #Error
 "
 !
@@ -815,31 +815,31 @@
     inString := true.
 
     [inString] whileTrue:[
-        nextChar isNil ifTrue:[
-            self syntaxError:'unexpected end-of-input in String'
-                    position:pos to:(source position - 1).
-            tokenType := #EOF.
-            ^ tokenType
-        ].
-        (nextChar == Character cr) ifTrue:[
-            tokenLineNr := tokenLineNr + 1
-        ].
-        (nextChar == Character quote) ifTrue:[
-            (source peek == Character quote) 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 syntaxError:'unexpected end-of-input in String'
+		    position:pos to:(source position - 1).
+	    tokenType := #EOF.
+	    ^ tokenType
+	].
+	(nextChar == Character cr) ifTrue:[
+	    tokenLineNr := tokenLineNr + 1
+	].
+	(nextChar == Character quote) ifTrue:[
+	    (source peek == Character quote) 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.