[GHC] #15350: gcdExtInteger violates assertion
GHC
ghc-devs at haskell.org
Fri Jul 6 23:20:54 UTC 2018
#15350: gcdExtInteger violates assertion
-------------------------------------+-------------------------------------
Reporter: Bodigrim | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Core Libraries | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Runtime crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by Bodigrim:
Old description:
> {{{#!haskell
> {-# LANGUAGE UnboxedTuples #-}
> import GHC.Integer.GMP.Internals
>
> main = let (# _, s #) = gcdExtInteger 2 (2^65 + 1) in print s
> }}}
>
> fails with
>
> {{{#!haskell
> 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. Otherwise I'll
> be happy to prepare a patch for Phabricator.
>
> {{{#!diff
> - s@(MBN# s#) <- newBigNat# (absI# xn#)
> + s@(MBN# s#) <- newBigNat# (absI# yn#)
> }}}
New description:
{{{#!haskell
{-# LANGUAGE UnboxedTuples #-}
import GHC.Integer.GMP.Internals
main = let (# _, s #) = gcdExtInteger 2 (2^65 + 1) in print s
}}}
fails with
{{{#!haskell
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.
{{{#!diff
- s@(MBN# s#) <- newBigNat# (absI# xn#)
+ s@(MBN# s#) <- newBigNat# (absI# yn#)
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15350#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list