Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

7 changed files:

Changes:

  • libraries/base/changelog.md
    ... ... @@ -23,6 +23,9 @@
    23 23
           * `GHC.ExecutionStack.Internal`.
    
    24 24
       * Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
    
    25 25
     
    
    26
    +  * Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)).
    
    27
    +
    
    28
    +
    
    26 29
     ## 4.21.0.0 *TBA*
    
    27 30
       * Change `SrcLoc` to be a strict and unboxed (finishing [CLC proposal #55](https://github.com/haskell/core-libraries-committee/issues/55))
    
    28 31
       * Introduce `Data.Bounded` module exporting the `Bounded` typeclass (finishing [CLC proposal #208](https://github.com/haskell/core-libraries-committee/issues/208))
    

  • libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs
    ... ... @@ -1333,38 +1333,60 @@ integerGcde a b = case integerGcde# a b of
    1333 1333
     
    
    1334 1334
     -- | Computes the modular inverse.
    
    1335 1335
     --
    
    1336
    --- I.e. y = integerRecipMod# x m
    
    1337
    ---        = x^(-1) `mod` m
    
    1336
    +-- @integerRecipMod# x m@ behaves as follows:
    
    1338 1337
     --
    
    1339
    --- with 0 < y < |m|
    
    1338
    +--   * If m > 1 and gcd x m = 1, it returns an integer y with 0 < y < m such
    
    1339
    +--     that x*y is congruent to 1 modulo m.
    
    1340 1340
     --
    
    1341
    +--   * If m > 1 and gcd x m > 1, it fails.
    
    1342
    +--
    
    1343
    +--   * If m = 1, it returns @0@ for all x.  The computation effectively takes
    
    1344
    +--     place in the zero ring, which has a single element 0 with 0+0 = 0*0 = 0:
    
    1345
    +--     the element 0 is the multiplicative identity element and is its own
    
    1346
    +--     multiplicative inverse.
    
    1347
    +--
    
    1348
    +--   * If m = 0, it fails.
    
    1349
    +--
    
    1350
    +-- NB. Successful evaluation returns a value of the form @(# n | #)@; failure is
    
    1351
    +-- indicated by returning @(# | () #)@.
    
    1341 1352
     integerRecipMod#
    
    1342 1353
        :: Integer
    
    1343 1354
        -> Natural
    
    1344 1355
        -> (# Natural | () #)
    
    1345 1356
     integerRecipMod# x m
    
    1346
    -   | integerIsZero x = (# | () #)
    
    1347 1357
        | naturalIsZero m = (# | () #)
    
    1348
    -   | naturalIsOne  m = (# | () #)
    
    1358
    +   | naturalIsOne  m = (# naturalZero | #)
    
    1359
    +   | integerIsZero x = (# | () #)
    
    1349 1360
        | True            = Backend.integer_recip_mod x m
    
    1350 1361
     
    
    1351 1362
     
    
    1352 1363
     -- | Computes the modular exponentiation.
    
    1353 1364
     --
    
    1354
    --- I.e. y = integer_powmod b e m
    
    1355
    ---        = b^e `mod` m
    
    1365
    +-- @integerPowMod# b e m@ behaves as follows:
    
    1356 1366
     --
    
    1357
    --- with 0 <= y < abs m
    
    1367
    +--   * If m > 1 and e >= 0, it returns an integer y with 0 <= y < m
    
    1368
    +--     and y congruent to b^e modulo m.
    
    1358 1369
     --
    
    1359
    --- If e is negative, we use `integerRecipMod#` to try to find a modular
    
    1360
    --- multiplicative inverse (which may not exist).
    
    1370
    +--   * If m > 1 and e < 0, it uses `integerRecipMod#` to try to find a modular
    
    1371
    +--     multiplicative inverse b' (which only exists if gcd b m = 1) and then
    
    1372
    +--     caculates (b')^(-e) modulo m (note that -e > 0); if the inverse does not
    
    1373
    +--     exist then it fails.
    
    1374
    +--
    
    1375
    +--   * If m = 1, it returns @0@ for all b and e.
    
    1376
    +--
    
    1377
    +--   * If m = 0, it fails.
    
    1378
    +--
    
    1379
    +-- NB. Successful evaluation returns a value of the form @(# n | #)@; failure is
    
    1380
    +-- indicated by returning @(# | () #)@.
    
    1381
    +
    
    1361 1382
     integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #)
    
    1362 1383
     integerPowMod# !b !e !m
    
    1363
    -   | naturalIsZero m     = (# | () #)
    
    1364
    -   | naturalIsOne  m     = (# naturalZero | #)
    
    1365
    -   | integerIsZero e     = (# naturalOne  | #)
    
    1366
    -   | integerIsZero b     = (# naturalZero | #)
    
    1367
    -   | integerIsOne  b     = (# naturalOne  | #)
    
    1384
    +   | naturalIsZero m  = (# | () #)
    
    1385
    +   | naturalIsOne  m  = (# naturalZero | #)
    
    1386
    +   | integerIsZero e  = (# naturalOne  | #)
    
    1387
    +   | integerIsZero b
    
    1388
    +     && integerGt e 0 = (# naturalZero | #)
    
    1389
    +   | integerIsOne  b  = (# naturalOne  | #)
    
    1368 1390
          -- when the exponent is negative, try to find the modular multiplicative
    
    1369 1391
          -- inverse and use it instead
    
    1370 1392
        | integerIsNegative e = case integerRecipMod# b m of
    

  • testsuite/tests/lib/integer/T26017.hs
    1
    +{-# LANGUAGE UnboxedTuples #-}
    
    2
    +{-# LANGUAGE MagicHash #-}
    
    3
    +
    
    4
    +module Main (main) where
    
    5
    +
    
    6
    +import Data.List (group)
    
    7
    +import Data.Bits
    
    8
    +import Data.Word
    
    9
    +import Control.Monad
    
    10
    +
    
    11
    +import GHC.Word
    
    12
    +import GHC.Base
    
    13
    +import GHC.Num.Natural
    
    14
    +import GHC.Num.Integer
    
    15
    +
    
    16
    +integerPowMod :: Integer -> Integer -> Natural -> Maybe Natural
    
    17
    +integerPowMod b e m = case integerPowMod# b e m of
    
    18
    +   (# n  | #) -> Just n
    
    19
    +   (# | () #) -> Nothing
    
    20
    +
    
    21
    +integerRecipMod :: Integer -> Natural -> Maybe Natural
    
    22
    +integerRecipMod b m =
    
    23
    +  case integerRecipMod# b m of
    
    24
    +    (# n | #)  -> Just n
    
    25
    +    (# | () #) -> Nothing
    
    26
    +
    
    27
    +main :: IO ()
    
    28
    +main = do
    
    29
    +    print $ integerPowMod 0 (-1) 17
    
    30
    +    print $ integerPowMod 0 (-1) (2^1000)
    
    31
    +
    
    32
    +    print $ integerPowMod 0 (-100000) 17
    
    33
    +    print $ integerPowMod 0 (-100000) (2^1000)
    
    34
    +
    
    35
    +    print $ integerRecipMod 0 1
    
    36
    +    print $ integerRecipMod 1 1
    
    37
    +    print $ integerRecipMod 7819347813478123471346279134789352789578923 1
    
    38
    +    print $ integerRecipMod (-1) 1
    
    39
    +    print $ integerRecipMod (-7819347813478123471346279134789352789578923) 1

  • testsuite/tests/lib/integer/T26017.stdout
    1
    +Nothing
    
    2
    +Nothing
    
    3
    +Nothing
    
    4
    +Nothing
    
    5
    +Just 0
    
    6
    +Just 0
    
    7
    +Just 0
    
    8
    +Just 0
    
    9
    +Just 0

  • testsuite/tests/lib/integer/all.T
    ... ... @@ -27,3 +27,4 @@ test('integerImportExport', normal, compile_and_run, [''])
    27 27
     
    
    28 28
     test('T19345', [], compile_and_run, [''])
    
    29 29
     test('T20066', [exit_code(1)], compile_and_run, [''])
    
    30
    +test('T26017', [], compile_and_run, [''])

  • testsuite/tests/lib/integer/integerRecipMod.hs
    ... ... @@ -28,6 +28,8 @@ main = do
    28 28
        -- positive modulo
    
    29 29
        print $ mapMaybe f [-7..71]
    
    30 30
     
    
    31
    -   -- modulo == 1 or 0
    
    31
    +   -- modulo == 1 -> succeed and return 0
    
    32 32
        print (recipModInteger 77 1)
    
    33
    +
    
    34
    +   -- modulo == 0 -> fail
    
    33 35
        print (recipModInteger 77 0)

  • testsuite/tests/lib/integer/integerRecipMod.stdout
    1 1
     [(-7,149867),(-5,167851),(-1,209813),(1,1),(5,41963),(7,59947),(13,177535),(19,143557),(23,182447),(25,134281),(29,7235),(31,33841),(35,95915),(37,113413),(41,61409),(43,24397),(47,174101),(49,158431),(53,193979),(59,188477),(61,185737),(65,35507),(67,118999),(71,186173)]
    
    2
    -Nothing
    
    2
    +Just 0
    
    3 3
     Nothing