[Git][ghc/ghc][master] Bignum: add BigNat compat functions (#18613)

Marge Bot gitlab at gitlab.haskell.org
Tue Sep 1 03:06:34 UTC 2020



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


Commits:
a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00
Bignum: add BigNat compat functions (#18613)

- - - - -


1 changed file:

- libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs


Changes:

=====================================
libraries/integer-gmp/src/GHC/Integer/GMP/Internals.hs
=====================================
@@ -50,9 +50,22 @@ module GHC.Integer.GMP.Internals
     , zeroBigNat
     , oneBigNat
 
+      -- ** Conversions to/from 'BigNat'
+
+    , wordToBigNat
+    , wordToBigNat2
+    , bigNatToInt
+    , bigNatToWord
+    , indexBigNat#
+    , importBigNatFromByteArray
+    , exportBigNatToMutableByteArray
+
+
       -- ** 'BigNat' arithmetic operations
     , plusBigNat
     , plusBigNatWord
+    , minusBigNat
+    , minusBigNatWord
     , timesBigNat
     , timesBigNatWord
     , sqrBigNat
@@ -112,6 +125,8 @@ import qualified GHC.Num.BigNat as B
 import qualified GHC.Num.Primitives as P
 import GHC.Types
 import GHC.Prim
+import GHC.Exts (runRW#)
+import Control.Exception
 
 {-# COMPLETE S#, Jp#, Jn# #-}
 
@@ -199,6 +214,19 @@ plusBigNat (BN# a) (BN# b) = BN# (B.bigNatAdd a b)
 plusBigNatWord :: BigNat -> GmpLimb# -> BigNat
 plusBigNatWord (BN# a) w = BN# (B.bigNatAddWord# a w)
 
+{-# DEPRECATED minusBigNat "Use bigNatSub instead" #-}
+minusBigNat :: BigNat -> BigNat -> BigNat
+minusBigNat (BN# a) (BN# b) = case B.bigNatSub a b of
+   (# () | #) -> throw Underflow
+   (# | r #)  -> BN# r
+
+{-# DEPRECATED minusBigNatWord "Use bigNatSubWord# instead" #-}
+minusBigNatWord :: BigNat -> GmpLimb# -> BigNat
+minusBigNatWord (BN# a) b = case B.bigNatSubWord# a b of
+   (# () | #) -> throw Underflow
+   (# | r #)  -> BN# r
+
+
 {-# DEPRECATED timesBigNat "Use bigNatMul instead" #-}
 timesBigNat :: BigNat -> BigNat -> BigNat
 timesBigNat (BN# a) (BN# b) = BN# (B.bigNatMul a b)
@@ -344,3 +372,29 @@ exportBigNatToAddr :: BigNat -> Addr# -> Int# -> IO Word
 exportBigNatToAddr (BN# b) addr endian = IO \s ->
    case B.bigNatToAddr# b addr endian s of
       (# s', w #) -> (# s', W# w #)
+
+wordToBigNat :: Word# -> BigNat
+wordToBigNat w = BN# (B.bigNatFromWord# w)
+
+wordToBigNat2 :: Word# -> Word# -> BigNat
+wordToBigNat2 h l = BN# (B.bigNatFromWord2# h l)
+
+bigNatToInt :: BigNat -> Int#
+bigNatToInt (BN# b) = B.bigNatToInt# b
+
+bigNatToWord :: BigNat -> Word#
+bigNatToWord (BN# b) = B.bigNatToWord# b
+
+{-# DEPRECATED indexBigNat# "Use bigNatIndex# instead" #-}
+indexBigNat# :: BigNat -> GmpSize# -> GmpLimb#
+indexBigNat# (BN# b) i = B.bigNatIndex# b i
+
+{-# DEPRECATED importBigNatFromByteArray "Use bigNatFromByteArray# instead" #-}
+importBigNatFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> BigNat
+importBigNatFromByteArray ba off sz endian = case runRW# (B.bigNatFromByteArray# sz ba off endian) of
+   (# _, r #) -> BN# r
+
+{-# DEPRECATED exportBigNatToMutableByteArray "Use bigNatToMutableByteArray# instead" #-}
+exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
+exportBigNatToMutableByteArray (BN# ba) mba off endian = IO (\s -> case B.bigNatToMutableByteArray# ba mba off endian s of
+   (# s', r #) -> (# s', W# r #))



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a8a2568b7b64e5b9fca5b12df7da759de4db39ae

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a8a2568b7b64e5b9fca5b12df7da759de4db39ae
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200831/c6f9a856/attachment-0001.html>


More information about the ghc-commits mailing list