[squeak-dev] The Trunk: Kernel-ct.1419.mcz

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Thu Dec 2 00:41:53 UTC 2021


Hi Christoph,
yes sorry for the noise, old behavior is indeed unchanged.

My understanding was that defaultBase utility would have been to avoid
using an explicit radix
For example for reinterpreting numbers printed via printStringBase:,
because printStringBase: also omits the explicit radix.
However, I would not expect the defaultBase to change the interpretation of
radix, nor of exponent, because I'm not used to it, and that's not how
Smalltalk reads Numbers traditionally.

Example:
(20 exp printStringBase: 8)
-> '3.47260421332164004e9'

((ExtendedNumberParser on: (20 exp printStringBase: 8))
defaultBase: 8;
nextNumber)
->  3.614762391222941

does not feel completely right IMO.

But you seem to have over plans for defaultBase.
What is its utility exactly ?

Le jeu. 2 déc. 2021 à 01:07, Thiede, Christoph <
Christoph.Thiede at student.hpi.uni-potsdam.de> a écrit :

> Hi Nicolas,
>
>
> could you please elaborate what breaking change you are referring to? :-)
> After installing this update, 2r1e53 still evaluates to the same value
> for me.
>
>
> The old behavior seems to have been: The radix of the string, if any, is
> parsed to base 10. The significand is parsed based to that radix, if any,
> otherwise, to 10. The exponent, if any, is parsed to 10.
>
> The new behavior is: The radix of the string, if any parsed to the new
> default base in the number parsed, which defaults to 10. The significand
> is parsed based to that radix, if any, otherwise, to the default base.
> The exponent, if any, is parsed to the default base.
>
>
> Here is another example:
>
>
> (ExtendedNumberParser on: '11r1e10')
> defaultBase: 2;
> nextNumber. "9"
>
>
> The only questionable hick-up I could find is this:
>
>
> (ExtendedNumberParser on: '1e3')
> defaultBase: 2;
> nextNumber. "1"
>
> (One might expect a NumberParserError instead.)
>
>
> But this is not something new; in an older image, the following has the
> same result:
>
>
> (ExtendedNumberParser on: '1ea') nextNumber. "1"
>
>
> Best,
>
> Christoph
> ------------------------------
> *Von:* Squeak-dev <squeak-dev-bounces at lists.squeakfoundation.org> im
> Auftrag von Nicolas Cellier <nicolas.cellier.aka.nice at gmail.com>
> *Gesendet:* Donnerstag, 2. Dezember 2021 00:37:34
> *An:* The general-purpose Squeak developers list
> *Betreff:* Re: [squeak-dev] The Trunk: Kernel-ct.1419.mcz
>
> Reminder: until now, the exponent has always been read in base 10,
> whatever the radix of the significand.
>
> For example:
>     1 << 53 = 2r1e53
>
> This commit is changing the interpretation of such numbers...
>
> Le mer. 1 déc. 2021 à 16:34, <commits at source.squeak.org> a écrit :
>
>> Marcel Taeumel uploaded a new version of Kernel to project The Trunk:
>> http://source.squeak.org/trunk/Kernel-ct.1419.mcz
>>
>> ==================== Summary ====================
>>
>> Name: Kernel-ct.1419
>> Author: ct
>> Time: 27 October 2021, 10:21:05.275233 pm
>> UUID: ecfac90e-ea85-774f-b13d-0ecad50c894a
>> Ancestors: Kernel-eem.1418
>>
>> Makes it possible to specify a different default base in number parsers.
>> There is no need to hard-code the 10 and I am actually building something
>> with a different default number system. Clients can still change the base
>> via the radix notation.
>>
>>         (ExtendedNumberParser on: '10')
>>                 defaultBase: 16;
>>                 nextNumber. "16"
>>         (ExtendedNumberParser on: '2r10')
>>                 defaultBase: 16;
>>                 nextNumber. "2"
>>         (ExtendedNumberParser on: 'ar10')
>>                 defaultBase: 16;
>>                 nextNumber. "10".
>>
>> Also adds Integer class >> #readFrom:base:ifFail: for convenience.
>> Removes redundant class-side overrides on SqNumberParser.
>>
>> =============== Diff against Kernel-eem.1418 ===============
>>
>> Item was changed:
>>   ----- Method: ExtendedNumberParser>>nextFraction (in category
>> 'parsing-public') -----
>>   nextFraction
>>         | numerator denominator numberOfTrailingZeroInIntegerPart |
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := self peekSignIsMinus.
>>         (integerPart := self nextUnsignedIntegerOrNilBase: base)
>>                 ifNil: [numberOfTrailingZeroInIntegerPart := 0]
>>                 ifNotNil: [
>>                         numberOfTrailingZeroInIntegerPart := nDigits -
>> lastNonZero.
>>                         (sourceStream peekFor: $r)
>>                                 ifTrue: ["<base>r<integer>"
>>                                         (base := integerPart) < 2
>>                                                 ifTrue: [
>>                                                         sourceStream
>> skip: -1.
>>                                                         ^ self expected:
>> 'an integer greater than 1 as valid radix'].
>>                                         self peekSignIsMinus
>>                                                 ifTrue: [neg := neg not].
>>                                         integerPart := self
>> nextUnsignedIntegerBase: base.
>>                                         numberOfTrailingZeroInIntegerPart
>> := nDigits - lastNonZero]].
>>         (sourceStream peekFor: $.)
>>                 ifTrue:
>>                         [^self
>> readFractionPartNumberOfTrailingZeroInIntegerPart:
>> numberOfTrailingZeroInIntegerPart].
>>         integerPart
>>                 ifNil:
>>                         ["No integerPart, raise an error"
>>                         ^ self expected: 'a digit'].
>>         numerator := neg
>>                 ifTrue: [integerPart negated]
>>                 ifFalse: [integerPart].
>>         self readExponent ifTrue: [numerator := numerator * (base
>> raisedToInteger: exponent)].
>>         (sourceStream peekFor: $/) ifFalse: [^numerator].
>>         base := 10.
>> +       base := self defaultBase.
>>         (denominator := self nextUnsignedIntegerOrNilBase: base)
>>                 ifNil:
>>                         [sourceStream skip: -1. "Not a valid denominator,
>> ungobble / and return numerator"
>>                         ^numerator].
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         (base := denominator) < 2
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.
>>                                         ^ self expected: 'an integer
>> greater than 1 as valid radix'].
>>                         denominator := self nextUnsignedIntegerBase:
>> base].
>>         self readExponent ifTrue: [denominator := denominator * (base
>> raisedToInteger: exponent)].
>>         ^numerator / denominator!
>>
>> Item was changed:
>>   ----- Method: ExtendedNumberParser>>nextNumber (in category
>> 'parsing-public') -----
>>   nextNumber
>>         "main method for reading a number.
>>         This one can read Float Integer and ScaledDecimal"
>>
>>         | numberOfTrailingZeroInIntegerPart |
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := self peekSignIsMinus.
>>         integerPart := self nextUnsignedIntegerOrNilBase: base.
>>         integerPart ifNil: [(sourceStream peekFor: $.)
>>                 ifTrue: [
>>                         "Try .1 syntax"
>>                         ^self readNumberWithoutIntegerPart]
>>                 ifFalse: [
>>                         "This is not a regular number beginning with a
>> digit
>>                         It is time to check for exceptional condition NaN
>> and Infinity"
>>                         ^self readNamedFloatOrFail]].
>>         numberOfTrailingZeroInIntegerPart := nDigits - lastNonZero.
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         | oldNeg pos |
>>                         pos := sourceStream position - 1.
>>                         (base := integerPart) < 2
>>                                 ifTrue: ["A radix currently need to be
>> greater than 1, ungobble the r and return the integer part"
>>                                         sourceStream skip: -1.
>>                                         ^neg
>>                                                 ifTrue: [base negated]
>>                                                 ifFalse: [base]].
>>                         oldNeg := neg.
>>                         self peekSignIsMinus ifTrue: [neg := neg not].
>>                         integerPart := self nextUnsignedIntegerOrNilBase:
>> base.
>>                         integerPart ifNil: [
>>                                 (sourceStream peekFor: $.) ifTrue: [self
>> readNumberWithoutIntegerPartOrNil ifNotNil: [:aNumber | ^aNumber]].
>>                                 sourceStream position: pos.
>>                                         ^oldNeg
>>                                                 ifTrue: [base negated]
>>                                                 ifFalse: [base]].
>>                         numberOfTrailingZeroInIntegerPart := nDigits -
>> lastNonZero].
>>         ^ (sourceStream peekFor: $.)
>>                 ifTrue: [self
>> readNumberWithFractionPartNumberOfTrailingZeroInIntegerPart:
>> numberOfTrailingZeroInIntegerPart]
>>                 ifFalse: [self makeIntegerOrScaledInteger]!
>>
>> Item was changed:
>>   ----- Method: FORTRANNumberParser>>nextNumber (in category
>> 'parsing-public') -----
>>   nextNumber
>>         "main method for reading a number with FORTRAN syntax.
>>         This one can read Real and Integer (not complex)"
>>
>>         | numberOfTrailingZeroInIntegerPart numberOfNonZeroFractionDigits
>> mantissa value numberOfTrailingZeroInFractionPart noInt |
>> +       base := self defaultBase..
>> -       base := 10.
>>         (self nextMatchAll: 'NaN') ifTrue: [^Float nan].
>>         neg := self peekSignIsMinus.
>>         (self nextMatchAll: 'Infinity')
>>                 ifTrue: [^neg ifTrue: [Float negativeInfinity] ifFalse:
>> [Float infinity]].
>>         (noInt := sourceStream peekFor: $.)
>>                 ifTrue:
>>                         [integerPart := 0.
>>                         numberOfTrailingZeroInIntegerPart := 0]
>>                 ifFalse:
>>                         [integerPart := self nextUnsignedIntegerBase:
>> base.
>>                         numberOfTrailingZeroInIntegerPart := nDigits -
>> lastNonZero].
>>         (noInt or: [sourceStream peekFor: $.])
>>                 ifTrue:
>>                         [fractionPart := self nextUnsignedIntegerBase:
>> base ifFail: [nil].
>>                         fractionPart isNil
>>                                 ifTrue:
>>                                         [noInt
>>                                                 ifTrue:
>>                                                         ["no interger
>> part, no fraction part..."
>>                                                         self expected: 'a
>> digit 0 to 9'.
>>                                                         ^nil].
>>                                         fractionPart := 0]
>>                                 ifFalse:
>>                                         [numberOfNonZeroFractionDigits :=
>> lastNonZero.
>>
>> numberOfTrailingZeroInFractionPart := nDigits - lastNonZero].
>>                         self readExponent]
>>                 ifFalse:
>>                         [self readExponent ifFalse: [^neg ifTrue:
>> [integerPart negated] ifFalse: [integerPart]].
>>                         fractionPart := 0].
>>         fractionPart isZero
>>                 ifTrue:
>>                         [mantissa := integerPart // (base raisedTo:
>> numberOfTrailingZeroInIntegerPart).
>>                         exponent := exponent +
>> numberOfTrailingZeroInIntegerPart]
>>                 ifFalse:
>>                         [mantissa := integerPart * (base raisedTo:
>> numberOfNonZeroFractionDigits)
>>                                                 + (fractionPart // (base
>> raisedTo: numberOfTrailingZeroInFractionPart)).
>>                         exponent := exponent -
>> numberOfNonZeroFractionDigits].
>>         value := self
>>                                 makeFloatFromMantissa: mantissa
>>                                 exponent: exponent
>>                                 base: base.
>>         ^neg ifTrue: [value isZero ifTrue: [Float negativeZero] ifFalse:
>> [value negated]] ifFalse: [value]!
>>
>> Item was added:
>> + ----- Method: Integer class>>readFrom:base:ifFail: (in category
>> 'instance creation') -----
>> + readFrom: aStringOrStream base: base ifFail: aBlock
>> +       "Answer an instance of one of the concrete subclasses if Integer.
>> +       Initial plus or minus sign accepted, and bases > 10 use letters
>> A-Z.
>> +       Imbedded radix specifiers not allowed;  use Number class
>> readFrom: for that.
>> +       Execute aBlock if there are no digits."
>> +
>> +       ^(ExtendedNumberParser on: aStringOrStream) nextIntegerBase: base
>> ifFail: aBlock!
>>
>> Item was changed:
>>   Object subclass: #NumberParser
>> +       instanceVariableNames: 'sourceStream base neg integerPart
>> fractionPart exponent scale nDigits lastNonZero requestor failBlock
>> defaultBase'
>> -       instanceVariableNames: 'sourceStream base neg integerPart
>> fractionPart exponent scale nDigits lastNonZero requestor failBlock'
>>         classVariableNames: ''
>>         poolDictionaries: ''
>>         category: 'Kernel-Numbers'!
>>
>> + !NumberParser commentStamp: 'ct 10/27/2021 22:04' prior: 0!
>> - !NumberParser commentStamp: 'nice 3/15/2010 00:16' prior: 0!
>>   NumberParser is an abstract class for parsing and building numbers from
>> string/stream.
>>   It offers a framework with utility methods and exception handling.
>>
>>   Number syntax is not defined and should be subclassResponsibility.
>>
>>   Instance variables:
>>   sourceStream <Stream> the stream of characters from which the number is
>> read
>>   base <Integer> the radix in which to interpret digits
>>   neg <Boolean> true in case of minus sign
>>   integerPart <Integer> the integer part of the number
>>   fractionPart <Integer> the fraction part of the number if any
>>   exponent <Integer> the exponent used in scientific notation if any
>>   scale <Integer> the scale used in case of ScaledDecimal number if any
>>   nDigits <Integer> number of digits read to form an Integer
>>   lasNonZero <Integer> position of last non zero digit, starting at 1
>> from left, 0 if all digits are zero
>>   requestor <TextEditor | nil> can be used to insert an error message in
>> the requestor
>>   failBlock <BlockClosure> Block to execute whenever an error occurs.
>>         The fail block can have 0, 1 or 2 arguments (errorString and
>> source position)
>> + defaultBase <Integer> the default radix in which to interpret digits,
>> unless specified differently via radix notation!
>> - !
>>
>> Item was added:
>> + ----- Method: NumberParser>>defaultBase (in category 'accessing') -----
>> + defaultBase
>> +
>> +       ^ defaultBase!
>>
>> Item was added:
>> + ----- Method: NumberParser>>defaultBase: (in category 'accessing') -----
>> + defaultBase: anInteger
>> +
>> +       self assert: anInteger < 28 description: 'Default base must be
>> lower than 28 to keep radix r distinguishable from digits. For higher
>> bases, pass the base manually to #nextNumberBase: autc.'.
>> +       defaultBase := anInteger!
>>
>> Item was added:
>> + ----- Method: NumberParser>>defaultRadixBase (in category 'accessing')
>> -----
>> + defaultRadixBase
>> +
>> +       ^ 10!
>>
>> Item was added:
>> + ----- Method: NumberParser>>initialize (in category
>> 'initialize-release') -----
>> + initialize
>> +
>> +       defaultBase := 10!
>>
>> Item was changed:
>>   ----- Method: NumberParser>>nextInteger (in category 'parsing-public')
>> -----
>>   nextInteger
>>         "Read an Integer from sourceStream, asnwser that Integer.
>>         This is a generic version dealing with an optional sign and a
>> simple sequence of decimal digits.
>>         Subclass might define extended syntax."
>>
>> +       base := self defaultBase.
>> -       base := 10.
>>         ^self nextIntegerBase: base ifFail: [^self expected: ('a digit
>> between 0 and ' copyWith: (Character digitValue: base - 1))]!
>>
>> Item was changed:
>>   ----- Method: NumberParser>>nextUnsignedInteger (in category
>> 'parsing-public') -----
>>   nextUnsignedInteger
>>         "Read an Integer from sourceStream, asnwser that Integer.
>>         This is a generic version dealing with a simple sequence of
>> decimal digits.
>>         Subclass might define extended syntax."
>> +
>> +       base := self defaultBase.
>> -
>> -       base := 10.
>>         ^self nextUnsignedIntegerBase: base ifFail: [^self expected: ('a
>> digit between 0 and ' copyWith: (Character digitValue: base - 1))]!
>>
>> Item was changed:
>>   ----- Method: NumberParser>>on: (in category 'initialize-release') -----
>>   on: aStringOrStream
>>         sourceStream := aStringOrStream isString
>>                 ifTrue: [ aStringOrStream readStream ]
>>                 ifFalse: [ aStringOrStream ].
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := false.
>>         integerPart := fractionPart := exponent := scale := 0.
>>         requestor := failBlock := nil!
>>
>> Item was changed:
>>   ----- Method: NumberParser>>readExponent (in category
>> 'parsing-private') -----
>>   readExponent
>>         "read the exponent if any (stored in instVar).
>>         Answer true if found, answer false if none.
>>         If exponent letter is not followed by a digit,
>>         this is not considered as an error.
>>         Exponent are always read in base 10."
>>
>>         | eneg epos |
>>         exponent := 0.
>>         (self isExponentLetter: sourceStream peek) ifFalse: [^ false].
>>         sourceStream next.
>>         eneg := sourceStream peekFor: $-.
>>         epos := eneg not and: [self allowPlusSignInExponent and:
>> [sourceStream peekFor: $+]].
>> +       exponent := self nextUnsignedIntegerOrNilBase: self defaultBase.
>> -       exponent := self nextUnsignedIntegerOrNilBase: 10.
>>
> Above is the questionable change for reading the exponent...
>
>         exponent ifNil: ["Oops, there was no digit after the exponent
>> letter.Ungobble the letter"
>>                 exponent := 0.
>>                 sourceStream
>>                                                 skip: ((eneg or: [epos])
>>                                                                 ifTrue:
>> [-2]
>>                                                                 ifFalse:
>> [-1]).
>>                                         ^ false].
>>         eneg ifTrue: [exponent := exponent negated].
>>         ^true!
>>
>> Item was removed:
>> - ----- Method: SqNumberParser class>>on: (in category 'instance
>> creation') -----
>> - on: aStringOrStream
>> -       ^self new on: aStringOrStream!
>>
>> Item was removed:
>> - ----- Method: SqNumberParser class>>parse: (in category 'instance
>> creation') -----
>> - parse: aStringOrStream
>> -       ^(self new)
>> -               on: aStringOrStream;
>> -               nextNumber!
>>
>> Item was removed:
>> - ----- Method: SqNumberParser class>>parse:onError: (in category
>> 'instance creation') -----
>> - parse: aStringOrStream onError: failBlock
>> -       ^(self new)
>> -               on: aStringOrStream;
>> -               failBlock: failBlock;
>> -               nextNumber!
>>
>> Item was changed:
>>   ----- Method: SqNumberParser>>nextFraction (in category
>> 'parsing-public') -----
>>   nextFraction
>>         | numerator denominator numberOfTrailingZeroInIntegerPart |
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := self peekSignIsMinus.
>>         (integerPart := self nextUnsignedIntegerOrNilBase: base)
>>                 ifNil: ["No integerPart, raise an error"
>>                         ^ self expected: 'a digit'].
>>         numberOfTrailingZeroInIntegerPart := nDigits - lastNonZero.
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         (base := integerPart) < 2
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.
>>                                         ^ self expected: 'an integer
>> greater than 1 as valid radix'].
>>                         self peekSignIsMinus
>>                                 ifTrue: [neg := neg not].
>>                         integerPart := self nextUnsignedIntegerBase: base.
>>                         numberOfTrailingZeroInIntegerPart := nDigits -
>> lastNonZero].
>>         (sourceStream peekFor: $.)
>>                 ifTrue:
>>                         [^self
>> readFractionPartNumberOfTrailingZeroInIntegerPart:
>> numberOfTrailingZeroInIntegerPart].
>>         numerator := neg
>>                 ifTrue: [integerPart negated]
>>                 ifFalse: [integerPart].
>>         self readExponent ifTrue: [numerator := numerator * (base
>> raisedToInteger: exponent)].
>>         (sourceStream peekFor: $/) ifFalse: [^numerator].
>> +       base := self defaultBase.
>> -       base := 10.
>>         (denominator := self nextUnsignedIntegerOrNilBase: base)
>>                 ifNil:
>>                         [sourceStream skip: -1. "Not a valid denominator,
>> ungobble / and return numerator"
>>                         ^numerator].
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         (base := denominator) < 2
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.
>>                                         ^ self expected: 'an integer
>> greater than 1 as valid radix'].
>>                         denominator := self nextUnsignedIntegerBase:
>> base].
>>         self readExponent ifTrue: [denominator := denominator * (base
>> raisedToInteger: exponent)].
>>         ^numerator / denominator!
>>
>> Item was changed:
>>   ----- Method: SqNumberParser>>nextInteger (in category
>> 'parsing-public') -----
>>   nextInteger
>>         "Read an Integer from sourceStream, asnwser that Integer.
>>         In Smalltalk syntax, a radix can be specified, and an exponent
>> too."
>>
>>         | numberOfTrailingZeroInIntegerPart |
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := self peekSignIsMinus.
>>         integerPart := self nextUnsignedIntegerOrNilBase: base.
>>         numberOfTrailingZeroInIntegerPart := nDigits - lastNonZero.
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         (base := integerPart) < 2
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.
>>                                         ^ self expected: 'an integer
>> greater than 1 as valid radix'].
>>                         self peekSignIsMinus
>>                                 ifTrue: [neg := neg not].
>>                         integerPart := self nextUnsignedIntegerBase: base.
>>                         numberOfTrailingZeroInIntegerPart := nDigits -
>> lastNonZero].
>>         ^ self makeIntegerOrScaledInteger!
>>
>> Item was changed:
>>   ----- Method: SqNumberParser>>nextNumber (in category 'parsing-public')
>> -----
>>   nextNumber
>>         "main method for reading a number.
>>         This one can read Float Integer and ScaledDecimal"
>>
>>         | numberOfTrailingZeroInIntegerPart |
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := self peekSignIsMinus.
>>         integerPart := self nextUnsignedIntegerOrNilBase: base.
>>         integerPart ifNil: [
>>                 "This is not a regular number beginning with a digit
>>                 It is time to check for exceptional condition NaN and
>> Infinity"
>>                 ^self readNamedFloatOrFail].
>>         numberOfTrailingZeroInIntegerPart := nDigits - lastNonZero.
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         (base := integerPart) < 2
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.
>>                                         ^ self expected: 'an integer
>> greater than 1 as valid radix'].
>>                         self peekSignIsMinus
>>                                 ifTrue: [neg := neg not].
>>                         integerPart := self nextUnsignedIntegerBase: base.
>>                         numberOfTrailingZeroInIntegerPart := nDigits -
>> lastNonZero].
>>         ^ (sourceStream peekFor: $.)
>>                 ifTrue: [self
>> readNumberWithFractionPartNumberOfTrailingZeroInIntegerPart:
>> numberOfTrailingZeroInIntegerPart]
>>                 ifFalse: [self makeIntegerOrScaledInteger]!
>>
>> Item was changed:
>>   ----- Method: SqNumberParser>>nextScaledDecimal (in category
>> 'parsing-public') -----
>>   nextScaledDecimal
>>         "Main method for reading a (scaled) decimal number.
>>         Good Gracious, do not accept a decimal in another base than 10!!
>>         In other words, do not accept radix notation like 2r1.1, even not
>> 10r5.3
>>         Do not accept exponent notation neither, like 1.0e-3"
>>
>>         | numberOfNonZeroFractionDigits
>> numberOfTrailingZeroInFractionPart |
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := sourceStream peekFor: $-.
>>         integerPart := self nextUnsignedIntegerBase: base.
>>         (sourceStream peekFor: $.)
>>                 ifTrue: [fractionPart := self
>> nextUnsignedIntegerOrNilBase: base.
>>                         fractionPart ifNil: ["Oops, the decimal point
>> seems not part of this number"
>>                                                         sourceStream
>> skip: -1.
>>                                                         ^ neg
>>                                                                 ifTrue:
>> [integerPart negated asScaledDecimal: 0]
>>                                                                 ifFalse:
>> [integerPart asScaledDecimal: 0]].
>>                         numberOfNonZeroFractionDigits := lastNonZero.
>>                         numberOfTrailingZeroInFractionPart := nDigits -
>> lastNonZero.
>>                         (self readScaleWithDefaultNumberOfDigits: nDigits)
>>                                 ifFalse: ["No scale were provided. use
>> number of digits after decimal point as scale"
>>                                         scale := nDigits].
>>                         ^self
>> makeScaledDecimalWithNumberOfNonZeroFractionDigits:
>> numberOfNonZeroFractionDigits andNumberOfTrailingZeroInFractionPart:
>> numberOfTrailingZeroInFractionPart].
>>         self readScaleWithDefaultNumberOfDigits: 0.
>>         neg     ifTrue: [integerPart := integerPart negated].
>>         ^integerPart asScaledDecimal: scale!
>>
>> Item was changed:
>>   ----- Method: SqNumberParser>>nextUnsignedInteger (in category
>> 'parsing-public') -----
>>   nextUnsignedInteger
>>         "Read an unsigned Integer from sourceStream, asnwser that Integer.
>>         In Smalltalk syntax, a radix can be specified, and an exponent
>> too."
>>
>> +       base := self defaultBase.
>> -       base := 10.
>>         neg := false.
>>         integerPart := self nextUnsignedIntegerOrNilBase: base.
>>         (sourceStream peekFor: $r)
>>                 ifTrue: ["<base>r<integer>"
>>                         (base := integerPart) < 2
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.
>>                                         ^ self expected: 'an integer
>> greater than 1 as valid radix'].
>>                         integerPart := self nextUnsignedIntegerBase:
>> base].
>>         ^ self makeIntegerOrScaledInteger!
>>
>> Item was changed:
>>   ----- Method: SqNumberParser>>readScaleWithDefaultNumberOfDigits: (in
>> category 'parsing-private') -----
>>   readScaleWithDefaultNumberOfDigits: anInteger
>>         "Read the scale if any and store it into scale instance Variable.
>>         Answer true if found, answer false if none.
>>         The scale is specified by letter s, optionnally followed by a
>> positive integer in base 10.
>>         If no integer is specified, that means using as many digits as
>> provided after the fraction separator, as provided by parameter anInteger.
>>         A letter s followed by another letter is not considered as a
>> scale specification, because it could be part of a message."
>>
>>         scale := 0.
>>         sourceStream atEnd
>>                 ifTrue: [ ^ false ].
>>         (sourceStream peekFor: $s)
>>                 ifFalse: [ ^ false ].
>> +       scale := self nextUnsignedIntegerOrNilBase: self defaultBase.
>> -       scale := self nextUnsignedIntegerOrNilBase: 10.
>>         scale
>>                 ifNil: [
>>                         scale := anInteger.
>>                         (sourceStream peek ifNil: [ false ] ifNotNil: [
>> :nextChar | nextChar isLetter ])
>>                                 ifTrue: [
>>                                         sourceStream skip: -1.  "ungobble
>> the s"
>>                                         ^ false ]
>>                                 ifFalse: [ ^ true ] ].
>>         ^ true!
>>
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20211202/5e00f59f/attachment-0001.html>


More information about the Squeak-dev mailing list