gcdExtInteger violates assertion
{-# LANGUAGE UnboxedTuples #-}
import GHC.Integer.GMP.Internals
main = let (# _, s #) = gcdExtInteger 2 (2^65 + 1) in print s
fails with
Assertion failed: (sn <= mp_size_abs(xn)), function integer_gmp_gcdext, file libraries/integer-gmp/cbits/wrappers.c, line 316.
Abort trap: 6
It happens because s = -2^64
and does not fit one-limbed BigNat
. The implementation of gcdExtInteger x y
(https://github.com/ghc/ghc/blob/master/libraries/integer-gmp/src/GHC/Integer/Type.hs#L1392) allocates for s
a buffer, equal to size of x
(one limb in our case), but according to GMP manual (https://gmplib.org/manual/Number-Theoretic-Functions.html#index-mpz_005fgcdext) it should be equal to size of y
(two limbs in our case).
Hopefully, the diff is simple enough for a PR on GitHub (https://github.com/ghc/ghc/pull/163). Otherwise I'll be happy to prepare a patch for Phabricator.
- s@(MBN# s#) <- newBigNat# (absI# xn#)
+ s@(MBN# s#) <- newBigNat# (absI# yn#)
Reopening, because
{-# LANGUAGE UnboxedTuples #-}
import GHC.Integer.GMP.Internals
main = let (# _, s #) = gcdExtInteger (- (2^63 - 1) * 2^63) 0 in print s
fails in GHC 8.6.1 with
Assertion failed: (0 <= gn && gn <= gn0), function integer_gmp_gcdext, file libraries/integer-gmp/cbits/wrappers.c, line 309.
Abort trap: 6
I have not yet understood what is going on.