[Git][ghc/ghc][master] Fix bugs in `integerRecipMod` and `integerPowMod`

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8ded2330 by kwxm at 2025-05-20T17:24:07-04:00 Fix bugs in `integerRecipMod` and `integerPowMod` This fixes #26017. * `integerRecipMod x 1` now returns `(# 1 | #)` for all x; previously it incorrectly returned `(# | () #)`, indicating failure. * `integerPowMod 0 e m` now returns `(# | () #)` for e<0 and m>1, indicating failure; previously it incorrectly returned `(# 0 | #)`. - - - - - 7 changed files: - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - + testsuite/tests/lib/integer/T26017.hs - + testsuite/tests/lib/integer/T26017.stdout - testsuite/tests/lib/integer/all.T - testsuite/tests/lib/integer/integerRecipMod.hs - testsuite/tests/lib/integer/integerRecipMod.stdout Changes: ===================================== libraries/base/changelog.md ===================================== @@ -23,6 +23,9 @@ * `GHC.ExecutionStack.Internal`. * Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329) + * 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)). + + ## 4.21.0.0 *TBA* * Change `SrcLoc` to be a strict and unboxed (finishing [CLC proposal #55](https://github.com/haskell/core-libraries-committee/issues/55)) * 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 -- | Computes the modular inverse. -- --- I.e. y = integerRecipMod# x m --- = x^(-1) `mod` m +-- @integerRecipMod# x m@ behaves as follows: -- --- with 0 < y < |m| +-- * If m > 1 and gcd x m = 1, it returns an integer y with 0 < y < m such +-- that x*y is congruent to 1 modulo m. -- +-- * If m > 1 and gcd x m > 1, it fails. +-- +-- * If m = 1, it returns @0@ for all x. The computation effectively takes +-- place in the zero ring, which has a single element 0 with 0+0 = 0*0 = 0: +-- the element 0 is the multiplicative identity element and is its own +-- multiplicative inverse. +-- +-- * If m = 0, it fails. +-- +-- NB. Successful evaluation returns a value of the form @(# n | #)@; failure is +-- indicated by returning @(# | () #)@. integerRecipMod# :: Integer -> Natural -> (# Natural | () #) integerRecipMod# x m - | integerIsZero x = (# | () #) | naturalIsZero m = (# | () #) - | naturalIsOne m = (# | () #) + | naturalIsOne m = (# naturalZero | #) + | integerIsZero x = (# | () #) | True = Backend.integer_recip_mod x m -- | Computes the modular exponentiation. -- --- I.e. y = integer_powmod b e m --- = b^e `mod` m +-- @integerPowMod# b e m@ behaves as follows: -- --- with 0 <= y < abs m +-- * If m > 1 and e >= 0, it returns an integer y with 0 <= y < m +-- and y congruent to b^e modulo m. -- --- If e is negative, we use `integerRecipMod#` to try to find a modular --- multiplicative inverse (which may not exist). +-- * If m > 1 and e < 0, it uses `integerRecipMod#` to try to find a modular +-- multiplicative inverse b' (which only exists if gcd b m = 1) and then +-- caculates (b')^(-e) modulo m (note that -e > 0); if the inverse does not +-- exist then it fails. +-- +-- * If m = 1, it returns @0@ for all b and e. +-- +-- * If m = 0, it fails. +-- +-- NB. Successful evaluation returns a value of the form @(# n | #)@; failure is +-- indicated by returning @(# | () #)@. + integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #) integerPowMod# !b !e !m - | naturalIsZero m = (# | () #) - | naturalIsOne m = (# naturalZero | #) - | integerIsZero e = (# naturalOne | #) - | integerIsZero b = (# naturalZero | #) - | integerIsOne b = (# naturalOne | #) + | naturalIsZero m = (# | () #) + | naturalIsOne m = (# naturalZero | #) + | integerIsZero e = (# naturalOne | #) + | integerIsZero b + && integerGt e 0 = (# naturalZero | #) + | integerIsOne b = (# naturalOne | #) -- when the exponent is negative, try to find the modular multiplicative -- inverse and use it instead | integerIsNegative e = case integerRecipMod# b m of ===================================== testsuite/tests/lib/integer/T26017.hs ===================================== @@ -0,0 +1,39 @@ +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE MagicHash #-} + +module Main (main) where + +import Data.List (group) +import Data.Bits +import Data.Word +import Control.Monad + +import GHC.Word +import GHC.Base +import GHC.Num.Natural +import GHC.Num.Integer + +integerPowMod :: Integer -> Integer -> Natural -> Maybe Natural +integerPowMod b e m = case integerPowMod# b e m of + (# n | #) -> Just n + (# | () #) -> Nothing + +integerRecipMod :: Integer -> Natural -> Maybe Natural +integerRecipMod b m = + case integerRecipMod# b m of + (# n | #) -> Just n + (# | () #) -> Nothing + +main :: IO () +main = do + print $ integerPowMod 0 (-1) 17 + print $ integerPowMod 0 (-1) (2^1000) + + print $ integerPowMod 0 (-100000) 17 + print $ integerPowMod 0 (-100000) (2^1000) + + print $ integerRecipMod 0 1 + print $ integerRecipMod 1 1 + print $ integerRecipMod 7819347813478123471346279134789352789578923 1 + print $ integerRecipMod (-1) 1 + print $ integerRecipMod (-7819347813478123471346279134789352789578923) 1 ===================================== testsuite/tests/lib/integer/T26017.stdout ===================================== @@ -0,0 +1,9 @@ +Nothing +Nothing +Nothing +Nothing +Just 0 +Just 0 +Just 0 +Just 0 +Just 0 ===================================== testsuite/tests/lib/integer/all.T ===================================== @@ -27,3 +27,4 @@ test('integerImportExport', normal, compile_and_run, ['']) test('T19345', [], compile_and_run, ['']) test('T20066', [exit_code(1)], compile_and_run, ['']) +test('T26017', [], compile_and_run, ['']) ===================================== testsuite/tests/lib/integer/integerRecipMod.hs ===================================== @@ -28,6 +28,8 @@ main = do -- positive modulo print $ mapMaybe f [-7..71] - -- modulo == 1 or 0 + -- modulo == 1 -> succeed and return 0 print (recipModInteger 77 1) + + -- modulo == 0 -> fail print (recipModInteger 77 0) ===================================== testsuite/tests/lib/integer/integerRecipMod.stdout ===================================== @@ -1,3 +1,3 @@ [(-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)] -Nothing +Just 0 Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ded23300367c6e032b3c5a635fd506b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ded23300367c6e032b3c5a635fd506b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)