Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
a766286f
by Reed Mullanix at 2025-08-13T21:04:36-04:00
6 changed files:
- libraries/base/changelog.md
- libraries/ghc-bignum/changelog.md
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/all.T
Changes:
... | ... | @@ -5,6 +5,7 @@ |
5 | 5 | * 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))
|
6 | 6 | * Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
|
7 | 7 | * `GHC.Exts.IOPort#` and its related operations have been removed ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213))
|
8 | + * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
|
|
8 | 9 | |
9 | 10 | ## 4.22.0.0 *TBA*
|
10 | 11 | * Shipped with GHC 9.14.1
|
... | ... | @@ -5,6 +5,8 @@ |
5 | 5 | - `ghc-bignum`'s implementation has been merged into `ghc-internal`.
|
6 | 6 | Downstream users should import `GHC.Num.{Integer,Natural,BigNat}` stable
|
7 | 7 | modules from `base` instead.
|
8 | +- Fix bug where `naturalAndNot` was incorrectly truncating results (#26230)
|
|
9 | + |
|
8 | 10 | |
9 | 11 | ## 1.3
|
10 | 12 |
... | ... | @@ -488,7 +488,7 @@ naturalAndNot :: Natural -> Natural -> Natural |
488 | 488 | {-# NOINLINE naturalAndNot #-}
|
489 | 489 | naturalAndNot (NS n) (NS m) = NS (n `and#` not# m)
|
490 | 490 | naturalAndNot (NS n) (NB m) = NS (n `and#` not# (bigNatToWord# m))
|
491 | -naturalAndNot (NB n) (NS m) = NS (bigNatToWord# n `and#` not# m)
|
|
491 | +naturalAndNot (NB n) (NS m) = NB (bigNatAndNotWord# n m)
|
|
492 | 492 | naturalAndNot (NB n) (NB m) = naturalFromBigNat# (bigNatAndNot n m)
|
493 | 493 | |
494 | 494 | naturalOr :: Natural -> Natural -> Natural
|
1 | +import Data.Bits
|
|
2 | +import GHC.Num.Natural
|
|
3 | + |
|
4 | +main = do
|
|
5 | + print $ naturalAndNot ((2 ^ 4) .|. (2 ^ 3)) (2 ^ 3)
|
|
6 | + print $ naturalAndNot ((2 ^ 129) .|. (2 ^ 65)) (2 ^ 65)
|
|
7 | + print $ naturalAndNot ((2 ^ 4) .|. (2 ^ 3)) ((2 ^ 65) .|. (2 ^ 3))
|
|
8 | + print $ naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3) |
1 | +16
|
|
2 | +680564733841876926926749214863536422912
|
|
3 | +16
|
|
4 | +36893488147419103232 |
... | ... | @@ -88,3 +88,4 @@ test('div01', normal, compile_and_run, ['']) |
88 | 88 | test('T24245', normal, compile_and_run, [''])
|
89 | 89 | test('T25653', normal, compile_and_run, [''])
|
90 | 90 | test('T18619', exit_code(1), compile_and_run, [''])
|
91 | +test('T26230', normal, compile_and_run, ['']) |