[Git][ghc/ghc][master] Bignum: fix bigNatCompareWord# bug (#18813)
Marge Bot
gitlab at gitlab.haskell.org
Sat Oct 10 18:51:28 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00
Bignum: fix bigNatCompareWord# bug (#18813)
- - - - -
4 changed files:
- libraries/ghc-bignum/src/GHC/Num/BigNat.hs
- + testsuite/tests/lib/integer/T18813.hs
- + testsuite/tests/lib/integer/T18813.stdout
- testsuite/tests/lib/integer/all.T
Changes:
=====================================
libraries/ghc-bignum/src/GHC/Num/BigNat.hs
=====================================
@@ -339,7 +339,7 @@ bigNatCompareWord# a b
| bigNatIsZero a = cmpW# 0## b
| isTrue# (wordArraySize# a ># 1#) = GT
| True
- = cmpW# (indexWordArray# a 1#) b
+ = cmpW# (indexWordArray# a 0#) b
-- | Compare a BigNat and a Word
bigNatCompareWord :: BigNat# -> Word -> Ordering
=====================================
testsuite/tests/lib/integer/T18813.hs
=====================================
@@ -0,0 +1,22 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# OPTIONS_GHC -O0 #-}
+
+import GHC.Exts
+import GHC.Num.BigNat (bigNatCompareWord#, bigNatFromWord#)
+import GHC.Num.Integer (integerGcd)
+
+main :: IO ()
+main = do
+ let
+ x = noinline (14205695611797621937 :: Integer)
+ y = noinline (2 :: Word)
+ print (integerGcd x (toInteger y))
+ print (toInteger (gcd (fromInteger x) y :: Word))
+
+ let
+ x@(W# x#) = 1 :: Word
+ !x' = bigNatFromWord# x#
+ print (bigNatCompareWord# x' x#)
+ print (compare x x)
=====================================
testsuite/tests/lib/integer/T18813.stdout
=====================================
@@ -0,0 +1,4 @@
+1
+1
+EQ
+EQ
=====================================
testsuite/tests/lib/integer/all.T
=====================================
@@ -11,6 +11,7 @@ test('integerPowMod', [], compile_and_run, [''])
test('integerGcdExt', [], compile_and_run, [''])
test('integerRecipMod', [], compile_and_run, [''])
test('bignumMatch', [], compile, [''])
+test('T18813', [], compile_and_run, [''])
# skip ghci as it doesn't support unboxed tuples
test('integerImportExport', [omit_ways(['ghci'])], compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74ee1237bf243dd7d8b758a53695575c364c3088
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74ee1237bf243dd7d8b758a53695575c364c3088
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/20201010/c0dd3536/attachment-0001.html>
More information about the ghc-commits
mailing list