[GHC] #14085: powModInteger sometimes ignores sign of argument
GHC
ghc-devs at haskell.org
Sun Aug 6 16:11:05 UTC 2017
#14085: powModInteger sometimes ignores sign of argument
-------------------------------------+-------------------------------------
Reporter: ocheron | Owner: ocheron
Type: bug | Status: new
Priority: normal | Milestone:
Component: Core Libraries | Version: 8.2.1
Resolution: | Keywords: integer-gmp
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3826
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by ocheron):
Working on a patch I found another issue with `gcdExtInteger` when first
argument is negative.
Program:
{{{#!haskell
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
import GHC.Integer.GMP.Internals
f a b = let (# g, s #) = gcdExtInteger a b in (g, s)
main = do
print $ f 100000000000000000000000000000 7
print $ f (-100000000000000000000000000000) 7
}}}
crashes with assertion when executed:
{{{
$ ghc -V && ghc --make a
The Glorious Glasgow Haskell Compilation System, version 8.2.1
[1 of 1] Compiling Main ( a.hs, a.o )
Linking a ...
$ ./a
(1,3)
Assertion failed: (sn <= xn), function integer_gmp_gcdext, file libraries
/integer-gmp/cbits/wrappers.c, line 315.
Abort trap: 6
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14085#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list