[commit: packages/integer-gmp] master: Rename `{import, export}Integer` (22c23c6)

git at git.haskell.org git at git.haskell.org
Thu Nov 7 23:38:29 UTC 2013


Repository : ssh://git@git.haskell.org/integer-gmp

On branch  : master
Link       : http://git.haskell.org/packages/integer-gmp.git/commitdiff/22c23c6b6395e76d9717bca43f42a52cf84fc92d

>---------------------------------------------------------------

commit 22c23c6b6395e76d9717bca43f42a52cf84fc92d
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Thu Nov 7 21:40:57 2013 +0100

    Rename `{import,export}Integer`
    
    This renames to more verbose names which include the type these
    operations import/export from/to:
    
     - `importIntegerFromByteArray`, and
     - `exportIntegerToMutableByteArray`.
    
    This follows the naming convention used for other primitive operations,
    such as the recently added `copyMutableByteArrayToAddr` operation.
    
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


>---------------------------------------------------------------

22c23c6b6395e76d9717bca43f42a52cf84fc92d
 GHC/Integer/GMP/Internals.hs |    2 +-
 GHC/Integer/GMP/Prim.hs      |    8 ++++----
 GHC/Integer/Type.lhs         |   28 ++++++++++++++--------------
 cbits/gmp-wrappers.cmm       |    4 ++--
 4 files changed, 21 insertions(+), 21 deletions(-)

diff --git a/GHC/Integer/GMP/Internals.hs b/GHC/Integer/GMP/Internals.hs
index 51727f8..54fe70a 100644
--- a/GHC/Integer/GMP/Internals.hs
+++ b/GHC/Integer/GMP/Internals.hs
@@ -1,6 +1,6 @@
 {-# LANGUAGE NoImplicitPrelude #-}
 
-module GHC.Integer.GMP.Internals (Integer(..), gcdInt, gcdInteger, gcdExtInteger, lcmInteger, powInteger, powModInteger, powModSecInteger, recipModInteger, nextPrimeInteger, testPrimeInteger, sizeInBaseInteger, importInteger, exportInteger)
+module GHC.Integer.GMP.Internals (Integer(..), gcdInt, gcdInteger, gcdExtInteger, lcmInteger, powInteger, powModInteger, powModSecInteger, recipModInteger, nextPrimeInteger, testPrimeInteger, sizeInBaseInteger, importIntegerFromByteArray, exportIntegerToMutableByteArray)
     where
 
 import GHC.Integer.Type
diff --git a/GHC/Integer/GMP/Prim.hs b/GHC/Integer/GMP/Prim.hs
index 99b5a8a..1152166 100644
--- a/GHC/Integer/GMP/Prim.hs
+++ b/GHC/Integer/GMP/Prim.hs
@@ -50,8 +50,8 @@ module GHC.Integer.GMP.Prim (
     testPrimeInteger#,
 
     sizeInBaseInteger#,
-    exportInteger#,
-    importInteger#,
+    exportIntegerToMutableByteArray#,
+    importIntegerFromByteArray#,
 
 #if WORD_SIZE_IN_BITS < 64
     int64ToInteger#,  integerToInt64#,
@@ -231,12 +231,12 @@ foreign import prim "integer_cmm_sizeInBasezh" sizeInBaseInteger#
 
 -- |
 --
-foreign import prim "integer_cmm_exportIntegerzh" exportInteger#
+foreign import prim "integer_cmm_exportIntegerToMutableByteArrayzh" exportIntegerToMutableByteArray#
   :: Int# -> ByteArray# -> MutableByteArray# s -> Word# -> Int# -> State# s -> (# State# s, Word# #)
 
 -- |
 --
-foreign import prim "integer_cmm_importIntegerzh" importInteger#
+foreign import prim "integer_cmm_importIntegerFromByteArrayzh" importIntegerFromByteArray#
   :: ByteArray# -> Word# -> Word# -> Int# -> (# Int#, ByteArray# #)
 
 -- |
diff --git a/GHC/Integer/Type.lhs b/GHC/Integer/Type.lhs
index a8d7f09..2a654ea 100644
--- a/GHC/Integer/Type.lhs
+++ b/GHC/Integer/Type.lhs
@@ -47,7 +47,7 @@ import GHC.Integer.GMP.Prim (
     testBitInteger#, mul2ExpInteger#, fdivQ2ExpInteger#,
     powInteger#, powModInteger#, powModSecInteger#, recipModInteger#,
     nextPrimeInteger#, testPrimeInteger#,
-    sizeInBaseInteger#, exportInteger#, importInteger#,
+    sizeInBaseInteger#, exportIntegerToMutableByteArray#, importIntegerFromByteArray#,
 #if WORD_SIZE_IN_BITS < 64
     int64ToInteger#,  integerToInt64#,
     word64ToInteger#, integerToWord64#,
@@ -686,7 +686,7 @@ nextPrimeInteger (J# s d) = case nextPrimeInteger# s d of (# s', d' #) -> J# s'
 -- This function wraps @mpz_sizeinbase()@ which has some
 -- implementation pecularities to take into account:
 --
--- * @sizeInBaseInteger 0 base = 1@ (see also comment in 'exportInteger').
+-- * @sizeInBaseInteger 0 base = 1@ (see also comment in 'exportIntegerToMutableByteArray').
 --
 -- * This function is only defined if @base >= 2#@ and @base <= 256#@
 --   (Note: the documentation claims that only @base <= 62#@ is
@@ -705,7 +705,7 @@ sizeInBaseInteger (J# s d) b = sizeInBaseInteger# s d b
 
 -- | Dump 'Integer' (without sign) to mutable byte-array in base-256 representation.
 --
--- The call @exportInteger i mba offset order@ writes
+-- The call @exportIntegerToMutableByteArray i mba offset order@ writes
 --
 -- * the 'Integer' @i@
 --
@@ -718,20 +718,20 @@ sizeInBaseInteger (J# s d) b = sizeInBaseInteger# s d b
 --
 -- Use @sizeInBaseInteger i 256#@ to compute the exact number of bytes
 -- written in advance for @i /= 0 at . In case of @i == 0@,
--- 'exportInteger' will write and report zero bytes written, whereas
+-- 'exportIntegerToMutableByteArray' will write and report zero bytes written, whereas
 -- 'sizeInBaseInteger' report one byte.
 --
--- It's recommended to avoid calling 'exportInteger' for small
+-- It's recommended to avoid calling 'exportIntegerToMutableByteArray' for small
 -- integers as this function would currently convert those to big
 -- integers in order to call @mpz_export()@.
-{-# NOINLINE exportInteger #-}
-exportInteger :: Integer -> MutableByteArray# s -> Word# -> Int# -> State# s -> (# State# s, Word# #)
-exportInteger j@(S# _) mba o e = exportInteger (toBig j) mba o e -- TODO
-exportInteger (J# s d) mba o e = exportInteger# s d mba o e
+{-# NOINLINE exportIntegerToMutableByteArray #-}
+exportIntegerToMutableByteArray :: Integer -> MutableByteArray# s -> Word# -> Int# -> State# s -> (# State# s, Word# #)
+exportIntegerToMutableByteArray j@(S# _) mba o e = exportIntegerToMutableByteArray (toBig j) mba o e -- TODO
+exportIntegerToMutableByteArray (J# s d) mba o e = exportIntegerToMutableByteArray# s d mba o e
 
 -- | Read 'Integer' (without sign) from byte-array in base-256 representation.
 --
--- The call @importInteger ba offset size order@ reads
+-- The call @importIntegerFromByteArray ba offset size order@ reads
 --
 -- * @size@ bytes from the 'ByteArray#' @mba@ starting at @offset@
 --
@@ -740,12 +740,12 @@ exportInteger (J# s d) mba o e = exportInteger# s d mba o e
 --
 -- * returns a new 'Integer'
 --
--- It's recommended to avoid calling 'importInteger' for known to be
+-- It's recommended to avoid calling 'importIntegerFromByteArray' for known to be
 -- small integers as this function currently always returns a big
 -- integer even if it would fit into a small integer.
-{-# NOINLINE importInteger #-}
-importInteger :: ByteArray# -> Word# -> Word# -> Int# -> Integer
-importInteger ba o l e = case importInteger# ba o l e of (# s', d' #) -> J# s' d'
+{-# NOINLINE importIntegerFromByteArray #-}
+importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer
+importIntegerFromByteArray ba o l e = case importIntegerFromByteArray# ba o l e of (# s', d' #) -> J# s' d'
 
 \end{code}
 
diff --git a/cbits/gmp-wrappers.cmm b/cbits/gmp-wrappers.cmm
index 0da3db8..a4f4f0c 100644
--- a/cbits/gmp-wrappers.cmm
+++ b/cbits/gmp-wrappers.cmm
@@ -69,7 +69,7 @@ import "integer-gmp" integer_cbits_decodeDouble;
    the case for all the platforms that GHC supports, currently.
    -------------------------------------------------------------------------- */
 
-integer_cmm_importIntegerzh (P_ ba, W_ of, W_ sz, W_ e)
+integer_cmm_importIntegerFromByteArrayzh (P_ ba, W_ of, W_ sz, W_ e)
 {
   W_ src_ptr;
   W_ mp_result;
@@ -90,7 +90,7 @@ again:
 }
 
 /* :: Int# -> ByteArray# -> MutableByteArray# s -> Word# -> Int# -> State# s -> (# State# s, Word# #) */
-integer_cmm_exportIntegerzh (W_ s1, P_ d1, P_ mba, W_ of, W_ e)
+integer_cmm_exportIntegerToMutableByteArrayzh (W_ s1, P_ d1, P_ mba, W_ of, W_ e)
 {
   W_ dst_ptr;
   W_ mp_tmp;



More information about the ghc-commits mailing list