[Git][ghc/ghc][master] Fix bug in Natural multiplication (fix #18509)
Marge Bot
gitlab at gitlab.haskell.org
Wed Jul 29 19:09:09 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00
Fix bug in Natural multiplication (fix #18509)
A bug was lingering in Natural multiplication (inverting two limbs)
despite QuickCheck tests used during the development leading to wrong
results (independently of the selected backend).
- - - - -
6 changed files:
- libraries/ghc-bignum/src/GHC/Num/BigNat.hs
- libraries/ghc-bignum/src/GHC/Num/Natural.hs
- libraries/ghc-bignum/src/GHC/Num/WordArray.hs
- + testsuite/tests/numeric/should_run/T18509.hs
- + testsuite/tests/numeric/should_run/T18509.stdout
- testsuite/tests/numeric/should_run/all.T
Changes:
=====================================
libraries/ghc-bignum/src/GHC/Num/BigNat.hs
=====================================
@@ -228,8 +228,8 @@ bigNatToWordList bn = go (bigNatSize# bn)
-- | Convert two Word# (most-significant first) into a BigNat
bigNatFromWord2# :: Word# -> Word# -> BigNat#
bigNatFromWord2# 0## 0## = bigNatZero# (# #)
-bigNatFromWord2# 0## n = bigNatFromWord# n
-bigNatFromWord2# w1 w2 = wordArrayFromWord2# w1 w2
+bigNatFromWord2# 0## l = bigNatFromWord# l
+bigNatFromWord2# h l = wordArrayFromWord2# h l
-- | Convert a BigNat into a Word#
bigNatToWord# :: BigNat# -> Word#
=====================================
libraries/ghc-bignum/src/GHC/Num/Natural.hs
=====================================
@@ -86,8 +86,8 @@ naturalFromWord# x = NS x
-- | Convert two Word# (most-significant first) into a Natural
naturalFromWord2# :: Word# -> Word# -> Natural
naturalFromWord2# 0## 0## = naturalZero
-naturalFromWord2# 0## n = NS n
-naturalFromWord2# w1 w2 = NB (bigNatFromWord2# w2 w1)
+naturalFromWord2# 0## l = NS l
+naturalFromWord2# h l = NB (bigNatFromWord2# h l)
-- | Create a Natural from a Word
naturalFromWord :: Word -> Natural
=====================================
libraries/ghc-bignum/src/GHC/Num/WordArray.hs
=====================================
@@ -121,12 +121,14 @@ withNewWordArrayTrimedMaybe# sz act = case runRW# io of (# _, a #) -> a
-- | Create a WordArray# from two Word#
--
--- `byteArrayFromWord2# msw lsw = lsw:msw`
+-- `wordArrayFromWord2# h l
+-- where h is the most significant word
+-- l is the least significant word
wordArrayFromWord2# :: Word# -> Word# -> WordArray#
-wordArrayFromWord2# msw lsw =
+wordArrayFromWord2# h l =
withNewWordArray# 2# \mwa s ->
- case mwaWrite# mwa 0# lsw s of
- s -> mwaWrite# mwa 1# msw s
+ case mwaWrite# mwa 0# l s of
+ s -> mwaWrite# mwa 1# h s
-- | Create a WordArray# from one Word#
wordArrayFromWord# :: Word# -> WordArray#
=====================================
testsuite/tests/numeric/should_run/T18509.hs
=====================================
@@ -0,0 +1,6 @@
+import Numeric.Natural
+
+main :: IO ()
+main = do
+ print $ (0xFFFFFFFF0 * 0xFFFFFFFF0 :: Natural)
+ print $ (2 :: Natural) ^ (190 :: Int)
=====================================
testsuite/tests/numeric/should_run/T18509.stdout
=====================================
@@ -0,0 +1,2 @@
+4722366480670621958400
+1569275433846670190958947355801916604025588861116008628224
=====================================
testsuite/tests/numeric/should_run/all.T
=====================================
@@ -71,3 +71,4 @@ test('T497', normal, compile_and_run, ['-O'])
test('T17303', normal, compile_and_run, [''])
test('T18359', normal, compile_and_run, [''])
test('T18499', normal, compile_and_run, [''])
+test('T18509', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96c31ea1f0303ebabc59edccff2e88444fe02722
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96c31ea1f0303ebabc59edccff2e88444fe02722
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200729/ada5a99d/attachment-0001.html>
More information about the ghc-commits
mailing list