The Trunk: Kernel-nice.396.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Kernel-nice.396.mcz

commits-2
Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.396.mcz

==================== Summary ====================

Name: Kernel-nice.396
Author: nice
Time: 13 February 2010, 2:58:57.708 am
UUID: b435f6ab-8347-cc45-b850-ef0aa041a44d
Ancestors: Kernel-nice.395

Now read Float "exactly" (answer nearest Float) by using SqNumberParser.
This solves http://bugs.squeak.org/view.php?id=6982
This requires a fix of Float initialize, otherwise the old max float literal would overflow.

As mentionned by John McIntosh, this change has side effects and makes a few tests fail:
1) reading an invalid number raise an Error rather than answering 0
2) undocumented syntax .1e2 and 1.e2 are no more accepted

IMO, we should not fix 1), we should fix the users. For this we provide a #readFrom:ifFail:
We can fix 2) later by using ExtendedNumberParser where due.

=============== Diff against Kernel-nice.395 ===============

Item was changed:
  ----- Method: Integer class>>readFrom: (in category 'instance creation') -----
+ readFrom: aStringOrStream
- readFrom: aStream
  "Answer a new Integer as described on the stream, aStream.
  Embedded radix specifiers not allowed - use Number readFrom: for that."
+ ^self readFrom: aStringOrStream base: 10!
- ^self readFrom: aStream base: 10!

Item was changed:
  ----- Method: Number class>>readFrom:base: (in category 'instance creation') -----
  readFrom: stringOrStream base: base
  "Answer a number as described on aStream in the given number base."
 
+ ^(SqNumberParser on: stringOrStream) nextNumberBase: base!
- | aStream sign |
- aStream := (stringOrStream isString)
- ifTrue: [ReadStream on: stringOrStream]
- ifFalse: [stringOrStream].
- (aStream nextMatchAll: 'NaN') ifTrue: [^ Float nan].
- sign := (aStream peekFor: $-) ifTrue: [-1] ifFalse: [1].
- (aStream nextMatchAll: 'Infinity') ifTrue: [^ Float infinity * sign].
- ^ self readRemainderOf: (Integer readFrom: aStream base: base)
- from: aStream base: base withSign: sign!

Item was added:
+ ----- Method: Integer class>>readFrom:ifFail: (in category 'instance creation') -----
+ readFrom: aStringOrStream ifFail: aBlock
+ "Answer an instance of one of the concrete subclasses if Integer.
+ Initial minus sign accepted.
+ Imbedded radix specifiers not allowed;  use Number
+ class readFrom: for that.
+ Execute aBlock if there are no digits."
+
+ ^(SqNumberParser on: aStringOrStream) nextIntegerBase: 10 ifFail: aBlock!

Item was added:
+ ----- Method: Float class>>readFrom:ifFail: (in category 'instance creation') -----
+ readFrom: aStream ifFail: aBlock
+ "Answer a new Float as described on the stream, aStream."
+
+ ^(super readFrom: aStream ifFail: [^aBlock value]) asFloat!

Item was changed:
  ----- Method: Float class>>initialize (in category 'class initialization') -----
  initialize
  "Float initialize"
  "Constants from Computer Approximations, pp. 182-183:
  Pi = 3.14159265358979323846264338327950288
  Pi/2 = 1.57079632679489661923132169163975144
  Pi*2 = 6.28318530717958647692528676655900576
  Pi/180 = 0.01745329251994329576923690768488612
  2.0 ln = 0.69314718055994530941723212145817657
  2.0 sqrt = 1.41421356237309504880168872420969808"
 
  Pi := 3.14159265358979323846264338327950288.
  Halfpi := Pi / 2.0.
  Twopi := Pi * 2.0.
  ThreePi := Pi * 3.0.
  RadiansPerDegree := Pi / 180.0.
 
  Ln2 := 0.69314718055994530941723212145817657.
  Ln10 := 10.0 ln.
  Sqrt2 := 1.41421356237309504880168872420969808.
  E := 2.718281828459045235360287471353.
 
  Epsilon := 0.000000000001.  "Defines precision of mathematical functions"
 
+ MaxVal := 1.7976931348623157e308.
- MaxVal := 1.7976931348623159e308.
  MaxValLn := 709.782712893384.
  MinValLogBase2 := -1074.
 
  Infinity := MaxVal * MaxVal.
  NegativeInfinity := 0.0 - Infinity.
  NaN := Infinity - Infinity.
  NegativeZero := 1.0 / Infinity negated.
  !

Item was changed:
  ----- Method: Number class>>readFrom: (in category 'instance creation') -----
  readFrom: stringOrStream
  "Answer a number as described on aStream.  The number may
+ be any accepted Smalltalk literal Number format.
+ It can include a leading radix specification, as in 16rFADE.
+ It can as well be NaN, Infinity or -Infinity for conveniency."
+
+ ^(SqNumberParser on: stringOrStream) nextNumber!
- include a leading radix specification, as in 16rFADE"
- | value base aStream sign |
- aStream := (stringOrStream isString)
- ifTrue: [ReadStream on: stringOrStream]
- ifFalse: [stringOrStream].
- (aStream nextMatchAll: 'NaN') ifTrue: [^ Float nan].
- sign := (aStream peekFor: $-) ifTrue: [-1] ifFalse: [1].
- (aStream nextMatchAll: 'Infinity') ifTrue: [^ Float infinity * sign].
- base := 10.
- value := Integer readFrom: aStream base: base.
- (aStream peekFor: $r)
- ifTrue:
- ["<base>r<integer>"
- (base := value) < 2 ifTrue: [^self error: 'Invalid radix'].
- (aStream peekFor: $-) ifTrue: [sign := sign negated].
- value := Integer readFrom: aStream base: base].
- ^ self readRemainderOf: value from: aStream base: base withSign: sign.!

Item was added:
+ ----- Method: Number class>>readFrom:ifFail: (in category 'instance creation') -----
+ readFrom: stringOrStream ifFail: aBlock
+ "Answer a number as described on aStream.  The number may
+ be any accepted Smalltalk literal Number format.
+ It can include a leading radix specification, as in 16rFADE.
+ It can as well be NaN, Infinity or -Infinity for conveniency.
+ If input does not represent a valid number, then execute fail block
+ and leave the stream positioned before offending character"
+
+ ^(SqNumberParser on: stringOrStream) failBlock: aBlock; nextNumber!

Item was changed:
  ----- Method: Integer class>>readFrom:base: (in category 'instance creation') -----
+ readFrom: aStringOrStream base: base
- readFrom: aStream base: base
  "Answer an instance of one of the concrete subclasses if Integer.
  Initial minus sign accepted, and bases > 10 use letters A-Z.
  Imbedded radix specifiers not allowed;  use Number
+ class readFrom: for that.
+ Raise an Error if there are no digits."
- class readFrom: for that. Answer zero if there are no digits."
 
+ ^(SqNumberParser on: aStringOrStream) nextIntegerBase: base!
- | digit value neg |
- neg := aStream peekFor: $-.
- value := 0.
- [aStream atEnd]
- whileFalse:
- [digit := aStream next digitValue.
- (digit < 0 or: [digit >= base])
- ifTrue:
- [aStream skip: -1.
- neg ifTrue: [^value negated].
- ^value]
- ifFalse: [value := value * base + digit]].
- neg ifTrue: [^value negated].
- ^value!

Item was removed:
- ----- Method: Number class>>readScaledDecimal:fractionPart:digits:base:sign:from: (in category 'private') -----
- readScaledDecimal: integerPart fractionPart: fractionPart digits: fractionDigits base: base sign: sign from: aStream
- "Complete creation of a ScaledDecimal, reading scale from aStream. Answer
- a ScaledDecimal, or nil if parsing fails.
- <number>s[<scale>]"
-
- | scale decimalMultiplier decimalFraction |
- aStream atEnd ifTrue: [^ nil].
- (aStream next == $s) ifFalse: [^ nil].
- "<number>s<scale>"
- (aStream atEnd not and: [aStream peek digitValue between: 0 and: 9])
- ifTrue: [scale := Integer readFrom: aStream]
- ifFalse: [^ nil].
- scale isNil
- ifTrue: ["<number>s"
- fractionDigits = 0
- ifTrue: ["<integer>s"
- scale := 0]
- ifFalse: ["<integer>.<fraction>s"
- scale := fractionDigits]].
- fractionPart isNil
- ifTrue: [^ ScaledDecimal newFromNumber: integerPart * sign scale: scale]
- ifFalse: [decimalMultiplier := base raisedTo: fractionDigits.
- decimalFraction := integerPart * decimalMultiplier + fractionPart * sign / decimalMultiplier.
- ^ ScaledDecimal newFromNumber: decimalFraction scale: scale]!

Item was removed:
- ----- Method: Number class>>readExponent:base:from: (in category 'private') -----
- readExponent: baseValue base: base from: aStream
- "Complete creation of a number, reading exponent from aStream. Answer the
- number, or nil if parsing fails.
- <number>(e|d|q)<exponent>>"
-
- | sign exp value |
- ('edq' includes: aStream next) ifFalse: [^ nil].
- sign := ((aStream peek) == $-)
- ifTrue: [aStream next. -1]
- ifFalse: [1].
- (aStream atEnd or: [(aStream peek digitValue between: 0 and: 9) not])
- ifTrue: [^ nil]. "Avoid throwing an error"
- exp := (Integer readFrom: aStream base: 10) * sign.
- value := baseValue * (base raisedTo: exp).
- ^ value
- !

Item was removed:
- ----- Method: Number class>>readRemainderOf:from:base:withSign: (in category 'private') -----
- readRemainderOf: integerPart from: aStream base: base withSign: sign
- "Read optional fractional part and exponent or decimal scale, and return the final result"
- "Changed 200/01/19 For ANSI Numeric Literals support."
- "Number readFrom: '3r-22.2'"
-
- | value fractionDigits fracpos fractionPart fraction pos v foundDecimal |
- #Numeric.
- value := integerPart.
- fractionDigits := 0.
- foundDecimal := false.
- (aStream peekFor: $.)
- ifTrue: ["<integer>.<fraction>"
- foundDecimal := true.
- (aStream atEnd not
- and: [aStream peek digitValue between: 0 and: base - 1])
- ifTrue: [fracpos := aStream position.
- fractionPart := Integer readFrom: aStream base: base.
- fraction := fractionPart asFloat
- / (base raisedTo: aStream position - fracpos).
- fractionDigits := aStream position - fracpos.
- value := value asFloat + fraction]].
-
- pos := aStream position.
- (v := self readScaledDecimal: integerPart
- fractionPart: fractionPart
- digits: fractionDigits
- base: base
- sign: sign
- from: aStream)
- ifNil: [aStream position: pos]
- ifNotNil: [^ v "<number>s<scale>>"].
-
- pos := aStream position.
- (v := self readExponent: value base: base from: aStream)
- ifNil: [aStream position: pos.
- (foundDecimal and: [fractionDigits = 0])
- ifTrue: ["oops - just <integer>."
- aStream skip: -1.
- "un-gobble the period"
- ^ value * sign]]
- ifNotNil: [value := v "<number>(e|d|q)<exponent>>"].
-
- (value isFloat
- and: [value = 0.0
- and: [sign = -1]])
- ifTrue: [^ Float negativeZero]
- ifFalse: [^ value * sign]!