Copyright | (c) Herbert Valerio Riedel 2014 |
---|---|
License | BSD3 |
Maintainer | ghc-devs@haskell.org |
Stability | provisional |
Portability | non-portable (GHC Extensions) |
Safe Haskell | None |
Language | Haskell2010 |
This modules provides access to the Integer
constructors and
exposes some highly optimized GMP-operations.
Note that since integer-gmp
does not depend on base
, error
reporting via exceptions, error
, or undefined
is not
available. Instead, the low-level functions will crash the runtime
if called with invalid arguments.
See also GHC Commentary: Libraries/Integer.
Synopsis
- data Integer
- isValidInteger# :: Integer -> Int#
- module GHC.Integer
- gcdInteger :: Integer -> Integer -> Integer
- gcdExtInteger :: Integer -> Integer -> (# Integer, Integer #)
- lcmInteger :: Integer -> Integer -> Integer
- sqrInteger :: Integer -> Integer
- powModInteger :: Integer -> Integer -> Integer -> Integer
- powModSecInteger :: Integer -> Integer -> Integer -> Integer
- recipModInteger :: Integer -> Integer -> Integer
- wordToNegInteger :: Word# -> Integer
- bigNatToInteger :: BigNat -> Integer
- bigNatToNegInteger :: BigNat -> Integer
- data BigNat = BN# ByteArray#
- type GmpLimb = Word
- type GmpLimb# = Word#
- type GmpSize = Int
- type GmpSize# = Int#
- isValidBigNat# :: BigNat -> Int#
- sizeofBigNat# :: BigNat -> GmpSize#
- zeroBigNat :: BigNat
- oneBigNat :: BigNat
- nullBigNat :: BigNat
- byteArrayToBigNat# :: ByteArray# -> GmpSize# -> BigNat
- wordToBigNat :: Word# -> BigNat
- wordToBigNat2 :: Word# -> Word# -> BigNat
- bigNatToInt :: BigNat -> Int#
- bigNatToWord :: BigNat -> Word#
- indexBigNat# :: BigNat -> GmpSize# -> GmpLimb#
- plusBigNat :: BigNat -> BigNat -> BigNat
- plusBigNatWord :: BigNat -> GmpLimb# -> BigNat
- minusBigNat :: BigNat -> BigNat -> BigNat
- minusBigNatWord :: BigNat -> GmpLimb# -> BigNat
- timesBigNat :: BigNat -> BigNat -> BigNat
- timesBigNatWord :: BigNat -> GmpLimb# -> BigNat
- sqrBigNat :: BigNat -> BigNat
- quotRemBigNat :: BigNat -> BigNat -> (# BigNat, BigNat #)
- quotRemBigNatWord :: BigNat -> GmpLimb# -> (# BigNat, GmpLimb# #)
- quotBigNatWord :: BigNat -> GmpLimb# -> BigNat
- quotBigNat :: BigNat -> BigNat -> BigNat
- remBigNat :: BigNat -> BigNat -> BigNat
- remBigNatWord :: BigNat -> GmpLimb# -> Word#
- gcdBigNat :: BigNat -> BigNat -> BigNat
- gcdBigNatWord :: BigNat -> Word# -> Word#
- powModBigNat :: BigNat -> BigNat -> BigNat -> BigNat
- powModBigNatWord :: BigNat -> BigNat -> GmpLimb# -> GmpLimb#
- recipModBigNat :: BigNat -> BigNat -> BigNat
- shiftRBigNat :: BigNat -> Int# -> BigNat
- shiftLBigNat :: BigNat -> Int# -> BigNat
- testBitBigNat :: BigNat -> Int# -> Bool
- clearBitBigNat :: BigNat -> Int# -> BigNat
- complementBitBigNat :: BigNat -> Int# -> BigNat
- setBitBigNat :: BigNat -> Int# -> BigNat
- andBigNat :: BigNat -> BigNat -> BigNat
- xorBigNat :: BigNat -> BigNat -> BigNat
- popCountBigNat :: BigNat -> Int#
- orBigNat :: BigNat -> BigNat -> BigNat
- bitBigNat :: Int# -> BigNat
- isZeroBigNat :: BigNat -> Bool
- isNullBigNat# :: BigNat -> Int#
- compareBigNatWord :: BigNat -> GmpLimb# -> Ordering
- compareBigNat :: BigNat -> BigNat -> Ordering
- eqBigNatWord :: BigNat -> GmpLimb# -> Bool
- eqBigNatWord# :: BigNat -> GmpLimb# -> Int#
- eqBigNat :: BigNat -> BigNat -> Bool
- eqBigNat# :: BigNat -> BigNat -> Int#
- gtBigNatWord# :: BigNat -> GmpLimb# -> Int#
- gcdInt :: Int# -> Int# -> Int#
- gcdWord :: Word# -> Word# -> Word#
- powModWord :: GmpLimb# -> GmpLimb# -> GmpLimb# -> GmpLimb#
- recipModWord :: GmpLimb# -> GmpLimb# -> GmpLimb#
- testPrimeInteger :: Integer -> Int# -> Int#
- testPrimeBigNat :: BigNat -> Int# -> Int#
- testPrimeWord# :: GmpLimb# -> Int# -> Int#
- nextPrimeInteger :: Integer -> Integer
- nextPrimeBigNat :: BigNat -> BigNat
- nextPrimeWord# :: GmpLimb# -> GmpLimb#
- sizeInBaseBigNat :: BigNat -> Int# -> Word#
- sizeInBaseInteger :: Integer -> Int# -> Word#
- sizeInBaseWord# :: Word# -> Int# -> Word#
- exportBigNatToAddr :: BigNat -> Addr# -> Int# -> IO Word
- exportIntegerToAddr :: Integer -> Addr# -> Int# -> IO Word
- exportWordToAddr :: Word -> Addr# -> Int# -> IO Word
- exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
- exportIntegerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
- exportWordToMutableByteArray :: Word -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word
- importBigNatFromAddr :: Addr# -> Word# -> Int# -> IO BigNat
- importIntegerFromAddr :: Addr# -> Word# -> Int# -> IO Integer
- importBigNatFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> BigNat
- importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer
The Integer
type
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
For more information about this type's representation, see the comments in its implementation.
S# !Int# | |
Jp# !BigNat | iff value in |
Jn# !BigNat | iff value in |
Instances
Eq Integer # | |
Ord Integer # | |
isValidInteger# :: Integer -> Int# Source #
Basic Integer
operations
module GHC.Integer
Additional Integer
operations
gcdExtInteger :: Integer -> Integer -> (# Integer, Integer #) Source #
Extended euclidean algorithm.
For a
and b
, compute their greatest common divisor g
and the coefficient s
satisfying as + bt = g
.
Since: integer-gmp-0.5.1.0
powModInteger :: Integer -> Integer -> Integer -> Integer Source #
"
" computes base powModInteger
b e mb
raised to
exponent e
modulo abs(m)
.
Negative exponents are supported if an inverse modulo m
exists.
Warning: It's advised to avoid calling this primitive with
negative exponents unless it is guaranteed the inverse exists, as
failure to do so will likely cause program abortion due to a
divide-by-zero fault. See also recipModInteger
.
Future versions of integer_gmp
may not support negative e
values anymore.
Since: integer-gmp-0.5.1.0
powModSecInteger :: Integer -> Integer -> Integer -> Integer Source #
"
" computes base powModSecInteger
b e mb
raised to
exponent e
modulo m
. It is required that e >= 0
and
m
is odd.
This is a "secure" variant of powModInteger
using the
mpz_powm_sec()
function which is designed to be resilient to side
channel attacks and is therefore intended for cryptographic
applications.
This primitive is only available when the underlying GMP library
supports it (GMP >= 5). Otherwise, it internally falls back to
, and a warning will be emitted when used.powModInteger
Since: integer-gmp-1.0.2.0
recipModInteger :: Integer -> Integer -> Integer Source #
"
" computes the inverse of recipModInteger
x mx
modulo m
. If
the inverse exists, the return value y
will satisfy 0 < y <
abs(m)
, otherwise the result is 0
.
Since: integer-gmp-0.5.1.0
Additional conversion operations to Integer
wordToNegInteger :: Word# -> Integer Source #
bigNatToInteger :: BigNat -> Integer Source #
bigNatToNegInteger :: BigNat -> Integer Source #
The BigNat
type
Type representing raw arbitrary-precision Naturals
This is common type used by Natural
and Integer
. As this type
consists of a single constructor wrapping a ByteArray#
it can be
unpacked.
Essential invariants:
ByteArray#
size is an exact multiple ofWord#
size- limbs are stored in least-significant-limb-first order,
- the most-significant limb must be non-zero, except for
0
which is represented as a 1-limb.
isValidBigNat# :: BigNat -> Int# Source #
sizeofBigNat# :: BigNat -> GmpSize# Source #
Return number of limbs contained in BigNat
.
The result is always >= 1
since even zero is encoded with 1 limb.
zeroBigNat :: BigNat Source #
CAF representing the value 0 :: BigNat
nullBigNat :: BigNat Source #
Special 0-sized bigNat returned in case of arithmetic underflow
This is currently only returned by the following operations:
Other operations such as quotBigNat
may return nullBigNat
as
well as a dummy/place-holder value instead of undefined
since we
can't throw exceptions. But that behaviour should not be relied
upon.
NB: isValidBigNat# nullBigNat
is false
Conversions to/from BigNat
byteArrayToBigNat# :: ByteArray# -> GmpSize# -> BigNat Source #
Construct BigNat
from existing ByteArray#
containing n
GmpLimb
s in least-significant-first order.
If possible ByteArray#
, will be used directly (i.e. shared
without cloning the ByteArray#
into a newly allocated one)
Note: size parameter (times sizeof(GmpLimb)
) must be less or
equal to its sizeofByteArray#
.
wordToBigNat2 :: Word# -> Word# -> BigNat Source #
Construct BigNat from 2 limbs. The first argument is the most-significant limb.
bigNatToInt :: BigNat -> Int# Source #
Equivalent to word2Int#
. bigNatToWord
bigNatToWord :: BigNat -> Word# Source #
Same as indexBigNat#
bn 0#
indexBigNat# :: BigNat -> GmpSize# -> GmpLimb# Source #
Extract n-th (0-based) limb in BigNat
.
n must be less than size as reported by sizeofBigNat#
.
BigNat
arithmetic operations
minusBigNat :: BigNat -> BigNat -> BigNat Source #
Returns nullBigNat
(see isNullBigNat#
) in case of underflow
minusBigNatWord :: BigNat -> GmpLimb# -> BigNat Source #
Returns nullBigNat
(see isNullBigNat#
) in case of underflow
quotRemBigNat :: BigNat -> BigNat -> (# BigNat, BigNat #) Source #
If divisor is zero, (#
is returnednullBigNat
, nullBigNat
#)
quotRemBigNatWord :: BigNat -> GmpLimb# -> (# BigNat, GmpLimb# #) Source #
Note: Result of div/0 undefined
powModBigNat :: BigNat -> BigNat -> BigNat -> BigNat Source #
Version of powModInteger
operating on BigNat
s
Since: integer-gmp-1.0.0.0
powModBigNatWord :: BigNat -> BigNat -> GmpLimb# -> GmpLimb# Source #
Version of powModInteger
for Word#
-sized moduli
Since: integer-gmp-1.0.0.0
recipModBigNat :: BigNat -> BigNat -> BigNat Source #
Version of recipModInteger
operating on BigNat
s
Since: integer-gmp-1.0.0.0
BigNat
logic operations
popCountBigNat :: BigNat -> Int# Source #
bitBigNat :: Int# -> BigNat Source #
Specialised version of
bitBigNat = shiftLBigNat (wordToBigNat 1##)
avoiding a few redundant allocations
BigNat
comparison predicates
Miscellaneous GMP-provided operations
gcdInt :: Int# -> Int# -> Int# Source #
Compute greatest common divisor.
Warning: result may become negative if (at least) one argument
is minBound
gcdWord :: Word# -> Word# -> Word# Source #
Compute greatest common divisor.
Since: integer-gmp-1.0.0.0
powModWord :: GmpLimb# -> GmpLimb# -> GmpLimb# -> GmpLimb# Source #
Version of powModInteger
operating on Word#
s
Since: integer-gmp-1.0.0.0
recipModWord :: GmpLimb# -> GmpLimb# -> GmpLimb# Source #
Version of recipModInteger
operating on Word#
s
Since: integer-gmp-1.0.0.0
Primality tests
testPrimeInteger :: Integer -> Int# -> Int# Source #
Probalistic Miller-Rabin primality test.
"
" determines whether testPrimeInteger
n kn
is prime
and returns one of the following results:
2#
is returned ifn
is definitely prime,1#
ifn
is a probable prime, or0#
ifn
is definitely not a prime.
The k
argument controls how many test rounds are performed for
determining a probable prime. For more details, see
GMP documentation for `mpz_probab_prime_p()`.
Since: integer-gmp-0.5.1.0
testPrimeBigNat :: BigNat -> Int# -> Int# Source #
Version of testPrimeInteger
operating on BigNat
s
Since: integer-gmp-1.0.0.0
testPrimeWord# :: GmpLimb# -> Int# -> Int# Source #
Version of testPrimeInteger
operating on Word#
s
Since: integer-gmp-1.0.0.0
nextPrimeInteger :: Integer -> Integer Source #
Compute next prime greater than n
probalistically.
According to the GMP documentation, the underlying function
mpz_nextprime()
"uses a probabilistic algorithm to identify
primes. For practical purposes it's adequate, the chance of a
composite passing will be extremely small."
Since: integer-gmp-0.5.1.0
nextPrimeBigNat :: BigNat -> BigNat Source #
Version of nextPrimeInteger
operating on BigNat
s
Since: integer-gmp-1.0.0.0
nextPrimeWord# :: GmpLimb# -> GmpLimb# Source #
Version of nextPrimeInteger
operating on Word#
s
Since: integer-gmp-1.0.0.0
Import/export functions
Compute size of serialisation
sizeInBaseBigNat :: BigNat -> Int# -> Word# Source #
Version of sizeInBaseInteger
operating on BigNat
Since: integer-gmp-1.0.0.0
sizeInBaseInteger :: Integer -> Int# -> Word# Source #
Compute number of digits (without sign) in given base
.
This function wraps mpz_sizeinbase()
which has some
implementation pecularities to take into account:
- "
" (see also comment insizeInBaseInteger
0 base = 1exportIntegerToMutableByteArray
). - This function is only defined if
base >= 2#
andbase <= 256#
(Note: the documentation claims that onlybase <= 62#
is supported, however the actual implementation supports up to base 256). - If
base
is a power of 2, the result will be exact. In other cases (e.g. forbase = 10#
), the result may be 1 digit too large sometimes. - "
" can be used to determine the most significant bit ofsizeInBaseInteger
i 2#i
.
Since: integer-gmp-0.5.1.0
sizeInBaseWord# :: Word# -> Int# -> Word# Source #
Version of sizeInBaseInteger
operating on Word#
Since: integer-gmp-1.0.0.0
Export
exportBigNatToAddr :: BigNat -> Addr# -> Int# -> IO Word Source #
Version of exportIntegerToAddr
operating on BigNat
s.
exportIntegerToAddr :: Integer -> Addr# -> Int# -> IO Word Source #
Dump Integer
(without sign) to addr
in base-256 representation.
exportIntegerToAddr
i addr e
See description of exportIntegerToMutableByteArray
for more details.
Since: integer-gmp-1.0.0.0
exportWordToAddr :: Word -> Addr# -> Int# -> IO Word Source #
Version of exportIntegerToAddr
operating on Word
s.
exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word Source #
Version of exportIntegerToMutableByteArray
operating on BigNat
s.
Since: integer-gmp-1.0.0.0
exportIntegerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word Source #
Dump Integer
(without sign) to mutable byte-array in base-256
representation.
The call
exportIntegerToMutableByteArray
i mba offset msbf
writes
- the
Integer
i
- into the
MutableByteArray#
mba
starting atoffset
- with most significant byte first if
msbf
is1#
or least significant byte first ifmsbf
is0#
, and - returns number of bytes written.
Use "
" to compute the exact number of
bytes written in advance for sizeInBaseInteger
i 256#i /= 0
. In case of i == 0
,
exportIntegerToMutableByteArray
will write and report zero bytes
written, whereas sizeInBaseInteger
report one byte.
It's recommended to avoid calling exportIntegerToMutableByteArray
for small
integers as this function would currently convert those to big
integers in msbf to call mpz_export()
.
Since: integer-gmp-1.0.0.0
exportWordToMutableByteArray :: Word -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word Source #
Version of exportIntegerToMutableByteArray
operating on Word
s.
Since: integer-gmp-1.0.0.0
Import
importBigNatFromAddr :: Addr# -> Word# -> Int# -> IO BigNat Source #
Version of importIntegerFromAddr
constructing a BigNat
importIntegerFromAddr :: Addr# -> Word# -> Int# -> IO Integer Source #
Read Integer
(without sign) from memory location at addr
in
base-256 representation.
importIntegerFromAddr
addr size msbf
See description of importIntegerFromByteArray
for more details.
Since: integer-gmp-1.0.0.0
importBigNatFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> BigNat Source #
Version of importIntegerFromByteArray
constructing a BigNat
importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer Source #
Read Integer
(without sign) from byte-array in base-256 representation.
The call
importIntegerFromByteArray
ba offset size msbf
reads
size
bytes from theByteArray#
ba
starting atoffset
- with most significant byte first if
msbf
is1#
or least significant byte first ifmsbf
is0#
, and - returns a new
Integer
Since: integer-gmp-1.0.0.0