#REFACTORING by cg
authorClaus Gittinger <cg@exept.de>
Fri, 21 Feb 2020 15:17:26 +0100
changeset 4637 1f1869c7b7ad
parent 4636 dc08f5bcc04d
child 4638 b5606754bec4
#REFACTORING by cg class: Scanner changed: #nextNumber
Scanner.st
--- a/Scanner.st	Fri Feb 21 15:16:30 2020 +0100
+++ b/Scanner.st	Fri Feb 21 15:17:26 2020 +0100
@@ -3154,24 +3154,24 @@
 nextNumber
     "scan a number; handles radix prefix, mantissa and exponent.
      Allows for
-	e, d or q to be used as exponent limiter (for float or long float),
-	s for scaled fixpoint numbers,
-	f for single precision floats (controlled by parserFlags).
+        e, d or q to be used as exponent limiter (for float or long float),
+        s for scaled fixpoint numbers,
+        f for single precision floats (controlled by parserFlags).
 
      i.e. 1e5 -> float (technically a double precision IEEE)
-	  1d5 -> float (also, a double precision IEEE)
-	  1q5 -> long float (a c-long double / extended or quad precision IEEE, dep. on CPU)
-	  1Q5 -> quad float (quad precision IEEE)
-	  1QD5 -> qDouble float (4*double precision)
-	  1QL5 -> large float (arbitrary precision)
-	  1s  -> a fixed point with precision from number of digits given.
-	  1s5 -> a fixed point with 5 digits precision.
-	  1d  -> float (technically a double precision IEEE float).
-	  1q  -> long float (technically a c-long double / extended or quad precision IEEE float, dep. on CPU).
-	  1Q  -> quad float (quad precision IEEE)
-
-	  1f5 -> shortFloat (technically a single precision IEEE float) or float, dep on parserFlags.
-	  1f  -> shortFloat (technically a single precision IEEE float) or float, dep on parserFlags.
+          1d5 -> float (also, a double precision IEEE)
+          1q5 -> long float (a c-long double / extended or quad precision IEEE, dep. on CPU)
+          1Q5 -> quad float (quad precision IEEE)
+          1QD5 -> qDouble float (4*double precision)
+          1QL5 -> large float (arbitrary precision)
+          1s  -> a fixed point with precision from number of digits given.
+          1s5 -> a fixed point with 5 digits precision.
+          1d  -> float (technically a double precision IEEE float).
+          1q  -> long float (technically a c-long double / extended or quad precision IEEE float, dep. on CPU).
+          1Q  -> quad float (quad precision IEEE)
+
+          1f5 -> shortFloat (technically a single precision IEEE float) or float, dep on parserFlags.
+          1f  -> shortFloat (technically a single precision IEEE float) or float, dep on parserFlags.
      support for scaled decimals can be disabled, if code needs to be read,
      which does not know about them (very unlikely).
      support for single prec. floats with f/F is controlled by a parser flag"
@@ -3186,229 +3186,229 @@
     pos1 := source position + 1.
 
     parserFlags allowCIntegers ifTrue:[
-	source peek == $0 ifTrue:[
-	    nextChar := source nextPeek.
-	    nextChar == $x ifTrue:[
-		source next.
-		((source peek ? $.) isDigitRadix:16) ifFalse:[
-		    self syntaxError:'invalid cStyle integer (hex digit expected)'
-			 position:tokenPosition to:(source position).
-		].
-		value := Integer readFrom:source radix:16.
-		sign < 0 ifTrue:[ value := value negated ].
-		tokenValue := token := value.
-		tokenType := type.
-		^ tokenType
-	    ].
-	    nextChar == $o ifTrue:[
-		source next.
-		((source peek ? $.) isDigitRadix:8) ifFalse:[
-		    self syntaxError:'invalid cStyle integer (octal digit expected)'
-			 position:tokenPosition to:(source position).
-		].
-		value := Integer readFrom:source radix:8.
-		sign < 0 ifTrue:[ value := value negated ].
-		tokenValue := token := value.
-		tokenType := type.
-		^ tokenType
-	    ].
-	    nextChar == $b ifTrue:[
-		source next.
-		((source peek ? $.) isDigitRadix:2) ifFalse:[
-		    self syntaxError:'invalid cStyle integer (binary digit expected)'
-			 position:tokenPosition to:(source position).
-		].
-		value := Integer readFrom:source radix:2.
-		sign < 0 ifTrue:[ value := value negated ].
-		tokenValue := token := value.
-		tokenType := type.
-		^ tokenType
-	    ].
-	    (nextChar notNil
-	    and:[ nextChar isDigit or:[nextChar == $.]]) ifFalse:[
-		tokenValue := token := 0.
-		tokenType := type.
-		^ tokenType
-	    ].
-	    value := 0.
-	].
+        source peek == $0 ifTrue:[
+            nextChar := source nextPeek.
+            nextChar == $x ifTrue:[
+                source next.
+                ((source peek ? $.) isDigitRadix:16) ifFalse:[
+                    self syntaxError:'invalid cStyle integer (hex digit expected)'
+                         position:tokenPosition to:(source position).
+                ].
+                value := Integer readFrom:source radix:16.
+                sign < 0 ifTrue:[ value := value negated ].
+                tokenValue := token := value.
+                tokenType := type.
+                ^ tokenType
+            ].
+            nextChar == $o ifTrue:[
+                source next.
+                ((source peek ? $.) isDigitRadix:8) ifFalse:[
+                    self syntaxError:'invalid cStyle integer (octal digit expected)'
+                         position:tokenPosition to:(source position).
+                ].
+                value := Integer readFrom:source radix:8.
+                sign < 0 ifTrue:[ value := value negated ].
+                tokenValue := token := value.
+                tokenType := type.
+                ^ tokenType
+            ].
+            nextChar == $b ifTrue:[
+                source next.
+                ((source peek ? $.) isDigitRadix:2) ifFalse:[
+                    self syntaxError:'invalid cStyle integer (binary digit expected)'
+                         position:tokenPosition to:(source position).
+                ].
+                value := Integer readFrom:source radix:2.
+                sign < 0 ifTrue:[ value := value negated ].
+                tokenValue := token := value.
+                tokenType := type.
+                ^ tokenType
+            ].
+            (nextChar notNil
+            and:[ nextChar isDigit or:[nextChar == $.]]) ifFalse:[
+                tokenValue := token := 0.
+                tokenType := type.
+                ^ tokenType
+            ].
+            value := 0.
+        ].
     ].
     nextChar == $. ifFalse:[
-	value := Integer readFrom:source radix:tokenRadix.
-	nextChar := source peekOrNil.
-	(nextChar == $r) ifTrue:[
-	    tokenRadix := value.
-	    source next.
-	    (tokenRadix between:2 and:36) ifFalse:[
-		self syntaxError:'bad radix (must be 2 .. 36)'
-			position:tokenPosition to:(source position).
-	    ].
-	    source peekOrNil == $- ifTrue:[
-		source next.
-		sign := -1
-	    ].
-	    pos1 := source position + 1.
-	    value := Integer readFrom:source radix:tokenRadix.
-	    nextChar := source peekOrNil.
-	].
+        value := Integer readFrom:source radix:tokenRadix.
+        nextChar := source peekOrNil.
+        (nextChar == $r) ifTrue:[
+            tokenRadix := value.
+            source next.
+            (tokenRadix between:2 and:36) ifFalse:[
+                self syntaxError:'bad radix (must be 2 .. 36)'
+                        position:tokenPosition to:(source position).
+            ].
+            source peekOrNil == $- ifTrue:[
+                source next.
+                sign := -1
+            ].
+            pos1 := source position + 1.
+            value := Integer readFrom:source radix:tokenRadix.
+            nextChar := source peekOrNil.
+        ].
     ].
 
     (nextChar == $.) ifTrue:[
-	nextChar := source nextPeek.
-	(nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
-	    (tokenRadix > 13) ifTrue:[
-		(nextChar == $d or:[nextChar == $D]) ifTrue:[
-		    self warning:'float with radix > 13 - (d/D are valid digits; not exponent-leaders)'
-			 position:tokenPosition to:(source position).
-		].
-		(tokenRadix > 14) ifTrue:[
-		    (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).
-		    ].
-		    (tokenRadix > 15) ifTrue:[
-			(nextChar == $f or:[nextChar == $F]) ifTrue:[
-			    self warning:'float with radix > 15 - (f/F are valid digits; not exponent-leaders)'
-				 position:tokenPosition to:(source position).
-			]
-		    ]
-		]
-	    ].
-	    mantissaAndScaledPart := self nextMantissaAndScaledPartWithRadix:tokenRadix.
-	    integerPart := value.
-	    value := integerPart + (mantissaAndScaledPart first).  "could be a longFloat now"
-	    type := #Float.
-	    nextChar := source peekOrNil
-	] ifFalse:[
-	    ('eEdDqQfF' includes:nextChar) ifTrue:[
-		"/ allow 5.e-3 - is this standard ?
-
-	    ] ifFalse:[
+        nextChar := source nextPeek.
+        (nextChar notNil and:[nextChar isDigitRadix:tokenRadix]) ifTrue:[
+            (tokenRadix > 13) ifTrue:[
+                (nextChar == $d or:[nextChar == $D]) ifTrue:[
+                    self warning:'float with radix > 13 - (d/D are valid digits; not exponent-leaders)'
+                         position:tokenPosition to:(source position).
+                ].
+                (tokenRadix > 14) ifTrue:[
+                    (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).
+                    ].
+                    (tokenRadix > 15) ifTrue:[
+                        (nextChar == $f or:[nextChar == $F]) ifTrue:[
+                            self warning:'float with radix > 15 - (f/F are valid digits; not exponent-leaders)'
+                                 position:tokenPosition to:(source position).
+                        ]
+                    ]
+                ]
+            ].
+            mantissaAndScaledPart := self nextMantissaAndScaledPartWithRadix:tokenRadix.
+            integerPart := value.
+            value := integerPart + (mantissaAndScaledPart first).  "could be a longFloat now"
+            type := #Float.
+            nextChar := source peekOrNil
+        ] ifFalse:[
+            ('eEdDqQfF' includes:nextChar) ifTrue:[
+                "/ allow 5.e-3 - is this standard ?
+
+            ] ifFalse:[
 "/                nextChar == (Character cr) ifTrue:[
 "/                    lineNr := lineNr + 1.
 "/                ].
-		nextChar := peekChar := $..
-	    ]
-	]
+                nextChar := peekChar := $..
+            ]
+        ]
     ].
 
     ('eEdDqQfF' includes:nextChar) ifTrue:[
-	kindClass := Float.
-	kindChar := nextChar.
-	nextChar := source nextPeek.
-	(kindChar == $q or:[kindChar == $Q]) ifTrue:[
-	    (kindChar == $Q) ifTrue:[
-		nextChar == $D ifTrue:[
-		    kindClass := QDouble.
-		    value := value asQDouble.
-		    nextChar := source nextPeek.
-		] ifFalse:[
-		    nextChar == $L ifTrue:[
-			kindClass := LargeFloat.
-			value := value asLargeFloat.
-			nextChar := source nextPeek.
-		    ] ifFalse:[
-			kindClass := QuadFloat.
-			value := value asQuadFloat
-		    ].
-		].
-	    ] ifFalse:[
-		kindClass := LongFloat.
-		value := value asLongFloat
-	    ].
-	] ifFalse:[
-	    ((kindChar == $f or:[kindChar == $F]) and:[parserFlags singlePrecisionFloatF]) ifTrue:[
-		kindClass := ShortFloat.
-		value := value asShortFloat
-	    ] ifFalse:[
-		value := value asFloat.
-	    ].
-	].
-	type := #Float.
-	(nextChar notNil and:[(nextChar isDigit"Radix:tokenRadix") or:['+-' includes:nextChar]]) ifTrue:[
-	    expSign := 1.
-	    (nextChar == $+) ifTrue:[
-		nextChar := source nextPeek
-	    ] ifFalse:[
-		(nextChar == $-) ifTrue:[
-		    nextChar := source nextPeek.
-		    expSign := -1
-		]
-	    ].
-	    exp := (Integer readFrom:source) * expSign.
-	    value := value * ((value class unity * tokenRadix) raisedToInteger:exp).
-
-	    nextChar := source peek.
-
-	    "/ due to a strange overflow, we might get a Nan, although we
-	    "/ are actually still in the float range.
-	    "/ happens eg. for 1.7976931348623157e+308
-
-	    "/ Also, the above raisedToInteger generates an additional error,
-	    "/ which is not present, if we use the strtox functions from the C-library.
-	    "/ Therefore, always use the low level fastFromString: converter.
-
-	    "/ However: it only accepts decimal radix
-	    tokenRadix = 10 ifTrue:[
-		Error handle:[:ex |
-		    "/ self halt.
-		] do:[
-		    chars := (source collection copyFrom:pos1 to:source position) string asSingleByteStringIfPossible.
-		    value := kindClass fastFromString:chars at:1.
-		].
-	    ].
-	].
+        kindClass := Float.
+        kindChar := nextChar.
+        nextChar := source nextPeek.
+        (kindChar == $q or:[kindChar == $Q]) ifTrue:[
+            (kindChar == $Q) ifTrue:[
+                nextChar == $D ifTrue:[
+                    kindClass := QDouble.
+                    value := value asQDouble.
+                    nextChar := source nextPeek.
+                ] ifFalse:[
+                    nextChar == $L ifTrue:[
+                        kindClass := LargeFloat.
+                        value := value asLargeFloat.
+                        nextChar := source nextPeek.
+                    ] ifFalse:[
+                        kindClass := QuadFloat.
+                        value := value asQuadFloat
+                    ].
+                ].
+            ] ifFalse:[
+                kindClass := LongFloat.
+                value := value asLongFloat
+            ].
+        ] ifFalse:[
+            ((kindChar == $f or:[kindChar == $F]) and:[parserFlags singlePrecisionFloatF]) ifTrue:[
+                kindClass := ShortFloat.
+                value := value asShortFloat
+            ] ifFalse:[
+                value := value asFloat.
+            ].
+        ].
+        type := #Float.
+        (nextChar notNil and:[(nextChar isDigit"Radix:tokenRadix") or:['+-' includes:nextChar]]) ifTrue:[
+            expSign := 1.
+            (nextChar == $+) ifTrue:[
+                nextChar := source nextPeek
+            ] ifFalse:[
+                (nextChar == $-) ifTrue:[
+                    nextChar := source nextPeek.
+                    expSign := -1
+                ]
+            ].
+            exp := (Integer readFrom:source) * expSign.
+            value := value * ((value class unity * tokenRadix) raisedToInteger:exp).
+
+            nextChar := source peek.
+
+            "/ due to a strange overflow, we might get a Nan, although we
+            "/ are actually still in the float range.
+            "/ happens eg. for 1.7976931348623157e+308
+
+            "/ Also, the above raisedToInteger generates an additional error,
+            "/ which is not present, if we use the strtox functions from the C-library.
+            "/ Therefore, always use the low level fastFromString: converter.
+
+            "/ However: it only accepts decimal radix
+            tokenRadix = 10 ifTrue:[
+                Error handle:[:ex |
+                    "/ self halt.
+                ] do:[
+                    chars := (source collection copyFrom:pos1 to:source position) string asSingleByteStringIfPossible.
+                    value := kindClass fastFromString:chars at:1.
+                ].
+            ].
+        ].
     ] ifFalse:[
-	value isLimitedPrecisionReal ifTrue:[
-	    "/ fastFromString only accepts decimal radix
-	    tokenRadix = 10 ifTrue:[
-		"/ no type specified - makes it a float
-		"/ value := value asFloat.
-		Error handle:[:ex |
-		    value := value asFloat
-		] do:[
-		    chars := (source collection copyFrom:pos1 to:source position) asSingleByteStringIfPossible.
-		    value := Float fastFromString:chars at:1.
-		].
-	    ].
-	].
-
-	parserFlags allowFixedPointLiterals == true ifTrue:[
-	    "/ ScaledDecimal numbers
-	    ('s' includes:nextChar) ifTrue:[
-		nextChar := source nextPeek.
-
-		(nextChar notNil and:[(nextChar isDigit)]) ifTrue:[
-		    scale := (Integer readFrom:source).
-		].
-
-		mantissaAndScaledPart isNil ifTrue:[
-		    value := value asFixedPoint:(scale ? 0)
-		] ifFalse:[
-		    d := 10 raisedTo:(mantissaAndScaledPart last).
-		    value := FixedPoint
-			numerator:((integerPart * d) + mantissaAndScaledPart second)
-			denominator:d
-			scale:(scale ? mantissaAndScaledPart last).
-		].
-		type := #FixedPoint.
-		self
-		    warnPossibleIncompatibility:'fixedPoint literal might be incompatibile with other systems'
-		    position:pos1 to:source position + 1.
-	    ].
-	].
+        value isLimitedPrecisionReal ifTrue:[
+            "/ fastFromString only accepts decimal radix
+            tokenRadix = 10 ifTrue:[
+                "/ no type specified - makes it a float
+                "/ value := value asFloat.
+                Error handle:[:ex |
+                    value := value asFloat
+                ] do:[
+                    chars := (source collection copyFrom:pos1 to:source position) asSingleByteStringIfPossible.
+                    value := Float fastFromString:chars at:1.
+                ].
+            ].
+        ].
+
+        parserFlags allowFixedPointLiterals ifTrue:[
+            "/ ScaledDecimal numbers
+            ('s' includes:nextChar) ifTrue:[
+                nextChar := source nextPeek.
+
+                (nextChar notNil and:[(nextChar isDigit)]) ifTrue:[
+                    scale := (Integer readFrom:source).
+                ].
+
+                mantissaAndScaledPart isNil ifTrue:[
+                    value := value asFixedPoint:(scale ? 0)
+                ] ifFalse:[
+                    d := 10 raisedTo:(mantissaAndScaledPart last).
+                    value := FixedPoint
+                        numerator:((integerPart * d) + mantissaAndScaledPart second)
+                        denominator:d
+                        scale:(scale ? mantissaAndScaledPart last).
+                ].
+                type := #FixedPoint.
+                self
+                    warnPossibleIncompatibility:'fixedPoint literal might be incompatibile with other systems'
+                    position:pos1 to:source position + 1.
+            ].
+        ].
     ].
 
     nextChar == $- ifTrue:[
-	self
-	    warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other systems'
-	    position:(source position + 1) to:(source position + 1).
+        self
+            warnPossibleIncompatibility:'add a space before ''-'' for compatibility with other systems'
+            position:(source position + 1) to:(source position + 1).
     ].
 
     tokenValue := token := (sign < 0) ifTrue:[value negated] ifFalse:[value].
     tokenType := type.
     (tokenValue isLimitedPrecisionReal) ~~ (tokenType == #Float) ifTrue:[
-	self shouldImplement.
+        self shouldImplement.
     ].
 
 "/    self markConstantFrom:tokenPosition to:(source position - 1).