Bodigrim pushed to branch wip/fix-toRational at Glasgow Haskell Compiler / GHC
Commits:
-
8aa42af4
by Andrew Lelechenko at 2025-06-15T17:25:10+01:00
4 changed files:
- libraries/base/changelog.md
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Real.hs
- testsuite/tests/numeric/should_run/T9810.stdout
Changes:
| ... | ... | @@ -11,6 +11,7 @@ |
| 11 | 11 | * `instance Functor NonEmpty` is now specified using `map` (rather than duplicating code). ([CLC proposal #300](https://github.com/haskell/core-libraries-committee/issues/300))
|
| 12 | 12 | * `fail` from `MonadFail` now carries `HasCallStack` constraint. ([CLC proposal #327](https://github.com/haskell/core-libraries-committee/issues/327))
|
| 13 | 13 | * The `Data.Enum.enumerate` function was introduced ([CLC #306](https://github.com/haskell/core-libraries-committee/issues/306))
|
| 14 | + * Fix issues with toRational for types capable to represent infinite and not-a-number values ([CLC proposal #338](https://github.com/haskell/core-libraries-committee/issues/338)
|
|
| 14 | 15 | * Worker threads used by various `base` facilities are now labelled with descriptive thread labels ([CLC proposal #305](https://github.com/haskell/core-libraries-committee/issues/305), [GHC #25452](https://gitlab.haskell.org/ghc/ghc/-/issues/25452)). Specifically, these include:
|
| 15 | 16 | * `Control.Concurrent.threadWaitRead`
|
| 16 | 17 | * `Control.Concurrent.threadWaitWrite`
|
| ... | ... | @@ -430,14 +430,10 @@ naturalToFloat# (NB b) = case integerToBinaryFloat' (IP b) of |
| 430 | 430 | |
| 431 | 431 | -- | @since base-2.01
|
| 432 | 432 | --
|
| 433 | --- Beware that 'toRational' generates garbage for non-finite arguments:
|
|
| 434 | ---
|
|
| 435 | --- >>> toRational (1/0 :: Float)
|
|
| 436 | --- 340282366920938463463374607431768211456 % 1
|
|
| 437 | --- >>> toRational (0/0 :: Float)
|
|
| 438 | --- 510423550381407695195061911147652317184 % 1
|
|
| 439 | ---
|
|
| 440 | 433 | instance Real Float where
|
| 434 | + toRational x
|
|
| 435 | + | isInfinite x = if x > 0 then infinity else -infinity
|
|
| 436 | + | isNaN x = notANumber
|
|
| 441 | 437 | toRational (F# x#) =
|
| 442 | 438 | case decodeFloat_Int# x# of
|
| 443 | 439 | (# m#, e# #)
|
| ... | ... | @@ -686,14 +682,10 @@ naturalToDouble# (NB b) = case integerToBinaryFloat' (IP b) of |
| 686 | 682 | |
| 687 | 683 | -- | @since base-2.01
|
| 688 | 684 | --
|
| 689 | --- Beware that 'toRational' generates garbage for non-finite arguments:
|
|
| 690 | ---
|
|
| 691 | --- >>> toRational (1/0)
|
|
| 692 | --- 179769313 (and 300 more digits...) % 1
|
|
| 693 | --- >>> toRational (0/0)
|
|
| 694 | --- 269653970 (and 300 more digits...) % 1
|
|
| 695 | ---
|
|
| 696 | 685 | instance Real Double where
|
| 686 | + toRational x
|
|
| 687 | + | isInfinite x = if x > 0 then infinity else -infinity
|
|
| 688 | + | isNaN x = notANumber
|
|
| 697 | 689 | toRational (D# x#) =
|
| 698 | 690 | case integerDecodeDouble# x# of
|
| 699 | 691 | (# m, e# #)
|
| ... | ... | @@ -703,15 +703,6 @@ fromIntegral = fromInteger . toInteger |
| 703 | 703 | |
| 704 | 704 | -- | General coercion to 'Fractional' types.
|
| 705 | 705 | --
|
| 706 | --- WARNING: This function goes through the 'Rational' type, which does not have values for 'NaN' for example.
|
|
| 707 | --- This means it does not round-trip.
|
|
| 708 | ---
|
|
| 709 | --- For 'Double' it also behaves differently with or without -O0:
|
|
| 710 | ---
|
|
| 711 | --- > Prelude> realToFrac nan -- With -O0
|
|
| 712 | --- > -Infinity
|
|
| 713 | --- > Prelude> realToFrac nan
|
|
| 714 | --- > NaN
|
|
| 715 | 706 | realToFrac :: (Real a, Fractional b) => a -> b
|
| 716 | 707 | {-# NOINLINE [1] realToFrac #-}
|
| 717 | 708 | -- See Note [Allow time for type-specialisation rules to fire]
|
| 1 | 1 | ## Double ##
|
| 2 | 2 | Infinity
|
| 3 | 3 | -Infinity
|
| 4 | -Infinity
|
|
| 4 | +NaN
|
|
| 5 | 5 | Infinity
|
| 6 | 6 | -Infinity
|
| 7 | 7 | Infinity
|
| 8 | 8 | ## Float ##
|
| 9 | 9 | Infinity
|
| 10 | 10 | -Infinity
|
| 11 | -Infinity
|
|
| 11 | +NaN
|
|
| 12 | 12 | Infinity
|
| 13 | 13 | -Infinity
|
| 14 | 14 | Infinity |