[Git][ghc/ghc][master] ghc-internal: Fix naturalAndNot for NB/NS case

13 Aug
2025
13 Aug
'25
9:15 p.m.
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00 ghc-internal: Fix naturalAndNot for NB/NS case When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the result: ```
naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3) 0
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
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:
=====================================
libraries/base/changelog.md
=====================================
@@ -5,6 +5,7 @@
* 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))
* Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
* `GHC.Exts.IOPort#` and its related operations have been removed ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213))
+ * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
## 4.22.0.0 *TBA*
* Shipped with GHC 9.14.1
=====================================
libraries/ghc-bignum/changelog.md
=====================================
@@ -5,6 +5,8 @@
- `ghc-bignum`'s implementation has been merged into `ghc-internal`.
Downstream users should import `GHC.Num.{Integer,Natural,BigNat}` stable
modules from `base` instead.
+- Fix bug where `naturalAndNot` was incorrectly truncating results (#26230)
+
## 1.3
=====================================
libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
=====================================
@@ -488,7 +488,7 @@ naturalAndNot :: Natural -> Natural -> Natural
{-# NOINLINE naturalAndNot #-}
naturalAndNot (NS n) (NS m) = NS (n `and#` not# m)
naturalAndNot (NS n) (NB m) = NS (n `and#` not# (bigNatToWord# m))
-naturalAndNot (NB n) (NS m) = NS (bigNatToWord# n `and#` not# m)
+naturalAndNot (NB n) (NS m) = NB (bigNatAndNotWord# n m)
naturalAndNot (NB n) (NB m) = naturalFromBigNat# (bigNatAndNot n m)
naturalOr :: Natural -> Natural -> Natural
=====================================
testsuite/tests/numeric/should_run/T26230.hs
=====================================
@@ -0,0 +1,8 @@
+import Data.Bits
+import GHC.Num.Natural
+
+main = do
+ print $ naturalAndNot ((2 ^ 4) .|. (2 ^ 3)) (2 ^ 3)
+ print $ naturalAndNot ((2 ^ 129) .|. (2 ^ 65)) (2 ^ 65)
+ print $ naturalAndNot ((2 ^ 4) .|. (2 ^ 3)) ((2 ^ 65) .|. (2 ^ 3))
+ print $ naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
=====================================
testsuite/tests/numeric/should_run/T26230.stdout
=====================================
@@ -0,0 +1,4 @@
+16
+680564733841876926926749214863536422912
+16
+36893488147419103232
=====================================
testsuite/tests/numeric/should_run/all.T
=====================================
@@ -88,3 +88,4 @@ test('div01', normal, compile_and_run, [''])
test('T24245', normal, compile_and_run, [''])
test('T25653', normal, compile_and_run, [''])
test('T18619', exit_code(1), compile_and_run, [''])
+test('T26230', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a766286fe759251eceb304c54ba52841c2a51f86
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a766286fe759251eceb304c54ba52841c2a51f86
You're receiving this email because of your account on gitlab.haskell.org.
43
Age (days ago)
43
Last active (days ago)
0 comments
1 participants
participants (1)
-
Marge Bot (@marge-bot)