Copyright | (c) Sylvain Henry 2019 (c) Herbert Valerio Riedel 2014 |
---|---|
License | BSD3 |
Maintainer | sylvain@haskus.fr |
Stability | provisional |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
The Integer
type.
Synopsis
- data Integer
- integerCheck# :: Integer -> Bool#
- integerCheck :: Integer -> Bool
- integerZero :: Integer
- integerOne :: Integer
- integerFromBigNat# :: BigNat# -> Integer
- integerFromBigNatNeg# :: BigNat# -> Integer
- integerFromBigNatSign# :: Int# -> BigNat# -> Integer
- integerToBigNatSign# :: Integer -> (# Int#, BigNat# #)
- integerToBigNatClamp# :: Integer -> BigNat#
- integerFromInt# :: Int# -> Integer
- integerFromInt :: Int -> Integer
- integerToInt# :: Integer -> Int#
- integerToInt :: Integer -> Int
- integerFromWord# :: Word# -> Integer
- integerFromWord :: Word -> Integer
- integerFromWordNeg# :: Word# -> Integer
- integerFromWordSign# :: Int# -> Word# -> Integer
- integerToWord# :: Integer -> Word#
- integerToWord :: Integer -> Word
- integerFromNatural :: Natural -> Integer
- integerFromWordList :: Bool -> [Word] -> Integer
- integerToNaturalClamp :: Integer -> Natural
- integerToNatural :: Integer -> Natural
- integerToNaturalThrow :: Integer -> Natural
- integerIsNegative# :: Integer -> Bool#
- integerIsNegative :: Integer -> Bool
- integerIsZero :: Integer -> Bool
- integerIsOne :: Integer -> Bool
- integerNe :: Integer -> Integer -> Bool
- integerEq :: Integer -> Integer -> Bool
- integerLe :: Integer -> Integer -> Bool
- integerLt :: Integer -> Integer -> Bool
- integerGt :: Integer -> Integer -> Bool
- integerGe :: Integer -> Integer -> Bool
- integerEq# :: Integer -> Integer -> Bool#
- integerNe# :: Integer -> Integer -> Bool#
- integerGt# :: Integer -> Integer -> Bool#
- integerLe# :: Integer -> Integer -> Bool#
- integerLt# :: Integer -> Integer -> Bool#
- integerGe# :: Integer -> Integer -> Bool#
- integerCompare :: Integer -> Integer -> Ordering
- integerCompare' :: Integer -> Integer -> Ordering
- integerSub :: Integer -> Integer -> Integer
- integerAdd :: Integer -> Integer -> Integer
- integerMul :: Integer -> Integer -> Integer
- integerNegate :: Integer -> Integer
- integerAbs :: Integer -> Integer
- integerSignum :: Integer -> Integer
- integerSignum# :: Integer -> Int#
- integerPopCount# :: Integer -> Int#
- integerBit# :: Word# -> Integer
- integerBit :: Word -> Integer
- integerTestBit# :: Integer -> Word# -> Bool#
- integerTestBit :: Integer -> Word -> Bool
- integerShiftR# :: Integer -> Word# -> Integer
- integerShiftR :: Integer -> Word -> Integer
- integerShiftL# :: Integer -> Word# -> Integer
- integerShiftL :: Integer -> Word -> Integer
- integerOr :: Integer -> Integer -> Integer
- integerXor :: Integer -> Integer -> Integer
- integerAnd :: Integer -> Integer -> Integer
- integerComplement :: Integer -> Integer
- integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
- integerQuotRem :: Integer -> Integer -> (Integer, Integer)
- integerQuot :: Integer -> Integer -> Integer
- integerRem :: Integer -> Integer -> Integer
- integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
- integerDivMod :: Integer -> Integer -> (Integer, Integer)
- integerDiv :: Integer -> Integer -> Integer
- integerMod :: Integer -> Integer -> Integer
- integerGcd :: Integer -> Integer -> Integer
- integerLcm :: Integer -> Integer -> Integer
- integerSqr :: Integer -> Integer
- integerLog2# :: Integer -> Word#
- integerLog2 :: Integer -> Word
- integerLogBaseWord# :: Word# -> Integer -> Word#
- integerLogBaseWord :: Word -> Integer -> Word
- integerLogBase# :: Integer -> Integer -> Word#
- integerLogBase :: Integer -> Integer -> Word
- integerIsPowerOf2# :: Integer -> (# (# #) | Word# #)
- integerFromInt64# :: Int# -> Integer
- integerDecodeDouble# :: Double# -> (# Integer, Int# #)
- integerEncodeDouble# :: Integer -> Int# -> Double#
- integerEncodeDouble :: Integer -> Int -> Double
- integerEncodeFloat# :: Integer -> Int# -> Float#
- integerSizeInBase# :: Word# -> Integer -> Word#
- integerToAddr# :: Integer -> Addr# -> Bool# -> State# s -> (# State# s, Word# #)
- integerToAddr :: Integer -> Addr# -> Bool# -> IO Word
- integerFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Integer #)
- integerFromAddr :: Word# -> Addr# -> Bool# -> IO Integer
- integerToMutableByteArray# :: Integer -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #)
- integerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Bool# -> IO Word
- integerFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Integer #)
- integerFromByteArray :: Word# -> ByteArray# -> Word# -> Bool# -> Integer
- integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
- integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
- integerRecipMod# :: Integer -> Natural -> (# Natural | () #)
- integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #)
Documentation
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.
If the value is small (fit into an Int
), IS
constructor is used.
Otherwise Integer
and IN
constructors are used to store a BigNat
representing respectively the positive or the negative value magnitude.
Invariant: Integer
and IN
are used iff value doesn't fit in IS
IS !Int# | |
IP !BigNat# | iff value in |
IN !BigNat# | iff value in |
Instances
Eq Integer Source # | |
Ord Integer Source # | |
integerCheck# :: Integer -> Bool# Source #
Check Integer invariants
integerCheck :: Integer -> Bool Source #
Check Integer invariants
integerZero :: Integer Source #
Integer Zero
integerOne :: Integer Source #
Integer One
integerFromBigNat# :: BigNat# -> Integer Source #
Create a positive Integer from a BigNat
integerFromBigNatNeg# :: BigNat# -> Integer Source #
Create a negative Integer from a BigNat
integerFromBigNatSign# :: Int# -> BigNat# -> Integer Source #
Create an Integer from a sign-bit and a BigNat
integerToBigNatSign# :: Integer -> (# Int#, BigNat# #) Source #
Convert an Integer into a sign-bit and a BigNat
integerToBigNatClamp# :: Integer -> BigNat# Source #
Convert an Integer into a BigNat.
Return 0 for negative Integers.
integerFromInt# :: Int# -> Integer Source #
Create an Integer from an Int#
integerFromInt :: Int -> Integer Source #
Create an Integer from an Int
integerFromWord# :: Word# -> Integer Source #
Convert a Word# into an Integer
integerFromWord :: Word -> Integer Source #
Convert a Word into an Integer
integerFromWordNeg# :: Word# -> Integer Source #
Create a negative Integer with the given Word magnitude
integerFromWordSign# :: Int# -> Word# -> Integer Source #
Create an Integer from a sign and a Word magnitude
integerToWord# :: Integer -> Word# Source #
Truncate an Integer into a Word
integerToWord :: Integer -> Word Source #
Truncate an Integer into a Word
integerFromNatural :: Natural -> Integer Source #
Convert a Natural into an Integer
integerToNaturalClamp :: Integer -> Natural Source #
Convert an Integer into a Natural
Return 0 for negative Integers.
integerToNatural :: Integer -> Natural Source #
Convert an Integer into a Natural
Return absolute value
integerToNaturalThrow :: Integer -> Natural Source #
Convert an Integer into a Natural
Throw an Underflow exception if input is negative.
integerIsNegative# :: Integer -> Bool# Source #
Negative predicate
integerIsNegative :: Integer -> Bool Source #
Negative predicate
integerIsZero :: Integer -> Bool Source #
Zero predicate
integerIsOne :: Integer -> Bool Source #
One predicate
integerNegate :: Integer -> Integer Source #
Negate Integer
.
One edge-case issue to take into account is that Int's range is not
symmetric around 0. I.e. minBound+maxBound = -1
IP is used iff n > maxBound::Int IN is used iff n < minBound::Int
integerSignum :: Integer -> Integer Source #
Return -1
, 0
, and 1
depending on whether argument is
negative, zero, or positive, respectively
integerSignum# :: Integer -> Int# Source #
Return -1#
, 0#
, and 1#
depending on whether argument is
negative, zero, or positive, respectively
integerPopCount# :: Integer -> Int# Source #
Count number of set bits. For negative arguments returns the negated population count of the absolute value.
integerTestBit# :: Integer -> Word# -> Bool# Source #
Test if n-th bit is set.
Fake 2's complement for negative values (might be slow)
integerTestBit :: Integer -> Word -> Bool Source #
Test if n-th bit is set. For negative Integers it tests the n-th bit of the negated argument.
Fake 2's complement for negative values (might be slow)
integerShiftR# :: Integer -> Word# -> Integer Source #
Shift-right operation
Fake 2's complement for negative values (might be slow)
integerShiftR :: Integer -> Word -> Integer Source #
Shift-right operation
Fake 2's complement for negative values (might be slow)
integerShiftL :: Integer -> Word -> Integer Source #
Shift-left operation
Remember that bits are stored in sign-magnitude form, hence the behavior of negative Integers is different from negative Int's behavior.
integerOr :: Integer -> Integer -> Integer Source #
Bitwise OR operation
Fake 2's complement for negative values (might be slow)
integerXor :: Integer -> Integer -> Integer Source #
Bitwise XOR operation
Fake 2's complement for negative values (might be slow)
integerAnd :: Integer -> Integer -> Integer Source #
Bitwise AND operation
Fake 2's complement for negative values (might be slow)
integerComplement :: Integer -> Integer Source #
Binary complement of the
integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #) Source #
Simultaneous integerQuot
and integerRem
.
Divisor must be non-zero otherwise the GHC runtime will terminate with a division-by-zero fault.
integerQuotRem :: Integer -> Integer -> (Integer, Integer) Source #
Simultaneous integerQuot
and integerRem
.
Divisor must be non-zero otherwise the GHC runtime will terminate with a division-by-zero fault.
integerDivMod# :: Integer -> Integer -> (# Integer, Integer #) Source #
Simultaneous integerDiv
and integerMod
.
Divisor must be non-zero otherwise the GHC runtime will terminate with a division-by-zero fault.
integerDivMod :: Integer -> Integer -> (Integer, Integer) Source #
Simultaneous integerDiv
and integerMod
.
Divisor must be non-zero otherwise the GHC runtime will terminate with a division-by-zero fault.
integerSqr :: Integer -> Integer Source #
Square a Integer
integerLog2# :: Integer -> Word# Source #
Base 2 logarithm (floor)
For numbers <= 0, return 0
integerLog2 :: Integer -> Word Source #
Base 2 logarithm (floor)
For numbers <= 0, return 0
integerLogBaseWord# :: Word# -> Integer -> Word# Source #
Logarithm (floor) for an arbitrary base
For numbers <= 0, return 0
integerLogBaseWord :: Word -> Integer -> Word Source #
Logarithm (floor) for an arbitrary base
For numbers <= 0, return 0
integerLogBase# :: Integer -> Integer -> Word# Source #
Logarithm (floor) for an arbitrary base
For numbers <= 0, return 0
integerLogBase :: Integer -> Integer -> Word Source #
Logarithm (floor) for an arbitrary base
For numbers <= 0, return 0
integerIsPowerOf2# :: Integer -> (# (# #) | Word# #) Source #
Indicate if the value is a power of two and which one
integerFromInt64# :: Int# -> Integer Source #
Convert an Int64# into an Integer on 64-bit architectures
integerDecodeDouble# :: Double# -> (# Integer, Int# #) Source #
Decode a Double# into (# Integer mantissa, Int# exponent #)
integerEncodeDouble# :: Integer -> Int# -> Double# Source #
Encode (# Integer mantissa, Int# exponent #) into a Double#
integerEncodeDouble :: Integer -> Int -> Double Source #
Encode (Integer mantissa, Int exponent) into a Double
integerEncodeFloat# :: Integer -> Int# -> Float# Source #
Encode (# Integer mantissa, Int# exponent #) into a Float#
TODO: Not sure if it's worth to write Float
optimized versions here
integerSizeInBase# :: Word# -> Integer -> Word# Source #
Compute the number of digits of the Integer (without the sign) in the given base.
base
must be > 1
integerToAddr# :: Integer -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) Source #
Write an Integer
(without sign) to addr
in base-256 representation
and return the number of bytes written.
The endianness is selected with the Bool# parameter: write most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
integerToAddr :: Integer -> Addr# -> Bool# -> IO Word Source #
Write an Integer
(without sign) to addr
in base-256 representation
and return the number of bytes written.
The endianness is selected with the Bool# parameter: write most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
integerFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Integer #) Source #
Read an Integer
(without sign) in base-256 representation from an Addr#.
The size is given in bytes.
The endianness is selected with the Bool# parameter: most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
Null higher limbs are automatically trimed.
integerFromAddr :: Word# -> Addr# -> Bool# -> IO Integer Source #
Read an Integer
(without sign) in base-256 representation from an Addr#.
The size is given in bytes.
The endianness is selected with the Bool# parameter: most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
Null higher limbs are automatically trimed.
integerToMutableByteArray# :: Integer -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #) Source #
Write an Integer
(without sign) in base-256 representation and return the
number of bytes written.
The endianness is selected with the Bool# parameter: most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
integerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Bool# -> IO Word Source #
Write an Integer
(without sign) in base-256 representation and return the
number of bytes written.
The endianness is selected with the Bool# parameter: most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
integerFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Integer #) Source #
Read an Integer
(without sign) in base-256 representation from a ByteArray#.
The size is given in bytes.
The endianness is selected with the Bool# parameter: most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
Null higher limbs are automatically trimed.
integerFromByteArray :: Word# -> ByteArray# -> Word# -> Bool# -> Integer Source #
Read an Integer
(without sign) in base-256 representation from a ByteArray#.
The size is given in bytes.
The endianness is selected with the Bool# parameter: most significant
byte first (big-endian) if 1#
or least significant byte first
(little-endian) if 0#
.
Null higher limbs are automatically trimed.
integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #) Source #
Get the extended GCD of two integers.
`integerGcde# a b` returns (# g,x,y #) where * ax + by = g = |gcd a b|
integerGcde :: Integer -> Integer -> (Integer, Integer, Integer) Source #
Get the extended GCD of two integers.
`integerGcde a b` returns (g,x,y) where * ax + by = g = |gcd a b|
integerRecipMod# :: Integer -> Natural -> (# Natural | () #) Source #
Computes the modular inverse.
I.e. y = integerRecipMod# x m
= x^(-1) mod
m
with 0 < y < |m|
integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #) Source #
Computes the modular exponentiation.
I.e. y = integer_powmod b e m
= b^e mod
m
with 0 <= y < abs m
If e is negative, we use integerRecipMod#
to try to find a modular
multiplicative inverse (which may not exist).