ghc-bignum-1.2: GHC BigNum library
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Num.BigNat

Description

Multi-precision natural

Synopsis

Documentation

type BigNat# = WordArray# Source #

A BigNat

Represented as an array of limbs (Word#) stored in little-endian order (Word# themselves use machine order).

Invariant (canonical representation): higher Word# is non-zero.

As a consequence, zero is represented with a WordArray# whose size is 0.

data BigNat Source #

A lifted BigNat

Represented as an array of limbs (Word#) stored in little-endian order (Word# themselves use machine order).

Invariant (canonical representation): higher Word# is non-zero.

As a consequence, zero is represented with a WordArray# whose size is 0.

Constructors

BN# 

Fields

Instances

Instances details
Eq BigNat Source # 
Instance details

Defined in GHC.Num.BigNat

Ord BigNat Source # 
Instance details

Defined in GHC.Num.BigNat

bigNatCheck# :: BigNat# -> Bool# Source #

Check that the BigNat is valid

bigNatCheck :: BigNat# -> Bool Source #

Check that the BigNat is valid

bigNatSize :: BigNat# -> Word Source #

Number of words in the BigNat

bigNatSize# :: BigNat# -> Int# Source #

Number of words in the BigNat

bigNatZero# :: (# #) -> BigNat# Source #

BigNat Zero

bigNatOne# :: (# #) -> BigNat# Source #

BigNat one

bigNatIsZero :: BigNat# -> Bool Source #

Indicate if a bigNat is zero

bigNatIsZero# :: BigNat# -> Bool# Source #

Indicate if a bigNat is zero

bigNatIsOne :: BigNat# -> Bool Source #

Indicate if a bigNat is one

bigNatIsOne# :: BigNat# -> Bool# Source #

Indicate if a bigNat is one

bigNatIsTwo :: BigNat# -> Bool Source #

Indicate if a bigNat is two

bigNatIsTwo# :: BigNat# -> Bool# Source #

Indicate if a bigNat is two

bigNatIsPowerOf2# :: BigNat# -> (# (# #) | Word# #) Source #

Indicate if the value is a power of two and which one

bigNatIndex# :: BigNat# -> Int# -> Word# Source #

Return the Word# at the given index

bigNatIndex :: BigNat# -> Int# -> Word Source #

Return the Word# at the given index

bigNatFromWord :: Word -> BigNat# Source #

Create a BigNat from a Word

bigNatFromWord# :: Word# -> BigNat# Source #

Create a BigNat from a Word

bigNatFromWordList :: [Word] -> BigNat# Source #

Convert a list of non-zero Words (most-significant first) into a BigNat

bigNatFromWordList# :: [Word] -> WordArray# Source #

Convert a list of non-zero Words (most-significant first) into a BigNat

bigNatFromAbsInt# :: Int# -> BigNat# Source #

Return the absolute value of the Int# in a BigNat

bigNatFromWordListUnsafe :: [Word] -> BigNat# Source #

Convert a list of non-zero Words (most-significant first) into a BigNat. Don't remove most-significant zero words

bigNatToWordList :: BigNat# -> [Word] Source #

Convert a BigNat into a list of non-zero Words (most-significant first)

bigNatFromWord2# :: Word# -> Word# -> BigNat# Source #

Convert two Word# (most-significant first) into a BigNat

bigNatToWord# :: BigNat# -> Word# Source #

Convert a BigNat into a Word#

bigNatToWordMaybe# :: BigNat# -> (# (# #) | Word# #) Source #

Convert a BigNat into a Word# if it fits

bigNatToWord :: BigNat# -> Word Source #

Convert a BigNat into a Word

bigNatToInt# :: BigNat# -> Int# Source #

Convert a BigNat into a Int#

bigNatToInt :: BigNat# -> Int Source #

Convert a BigNat into a Int

bigNatEncodeDouble# :: BigNat# -> Int# -> Double# Source #

Encode (# BigNat mantissa, Int# exponent #) into a Double#

bigNatGtWord# :: BigNat# -> Word# -> Bool# Source #

Test if a BigNat is greater than a Word

bigNatEqWord# :: BigNat# -> Word# -> Bool# Source #

Test if a BigNat is equal to a Word

bigNatGtWord :: BigNat# -> Word -> Bool Source #

Test if a BigNat is greater than a Word

bigNatLeWord# :: BigNat# -> Word# -> Bool# Source #

Test if a BigNat is lower than or equal to a Word

bigNatLeWord :: BigNat# -> Word -> Bool Source #

Test if a BigNat is lower than or equal to a Word

bigNatEq# :: BigNat# -> BigNat# -> Bool# Source #

Equality test for BigNat

bigNatEq :: BigNat# -> BigNat# -> Bool Source #

Equality test for BigNat

bigNatNe# :: BigNat# -> BigNat# -> Bool# Source #

Inequality test for BigNat

bigNatNe :: BigNat# -> BigNat# -> Bool Source #

Equality test for BigNat

bigNatCompareWord# :: BigNat# -> Word# -> Ordering Source #

Compare a BigNat and a Word#

bigNatCompareWord :: BigNat# -> Word -> Ordering Source #

Compare a BigNat and a Word

bigNatCompare :: BigNat# -> BigNat# -> Ordering Source #

Compare two BigNat

bigNatLt# :: BigNat# -> BigNat# -> Bool# Source #

Predicate: a < b

bigNatLt :: BigNat# -> BigNat# -> Bool Source #

Predicate: a < b

bigNatLe# :: BigNat# -> BigNat# -> Bool# Source #

Predicate: a <= b

bigNatLe :: BigNat# -> BigNat# -> Bool Source #

Predicate: a <= b

bigNatGt# :: BigNat# -> BigNat# -> Bool# Source #

Predicate: a > b

bigNatGt :: BigNat# -> BigNat# -> Bool Source #

Predicate: a > b

bigNatGe# :: BigNat# -> BigNat# -> Bool# Source #

Predicate: a >= b

bigNatGe :: BigNat# -> BigNat# -> Bool Source #

Predicate: a >= b

bigNatAddWord# :: BigNat# -> Word# -> BigNat# Source #

Add a bigNat and a Word#

bigNatAddWord :: BigNat# -> Word -> BigNat# Source #

Add a bigNat and a Word

bigNatAdd :: BigNat# -> BigNat# -> BigNat# Source #

Add two bigNats

bigNatMulWord# :: BigNat# -> Word# -> BigNat# Source #

Multiply a BigNat by a Word#

bigNatMulWord :: BigNat# -> Word -> BigNat# Source #

Multiply a BigNAt by a Word

bigNatSqr :: BigNat# -> BigNat# Source #

Square a BigNat

bigNatMul :: BigNat# -> BigNat# -> BigNat# Source #

Multiplication (classical algorithm)

bigNatSubWordUnsafe# :: BigNat# -> Word# -> BigNat# Source #

Subtract a Word# from a BigNat

The BigNat must be bigger than the Word#.

bigNatSubWordUnsafe :: BigNat# -> Word -> BigNat# Source #

Subtract a Word# from a BigNat

The BigNat must be bigger than the Word#.

bigNatSubWord# :: BigNat# -> Word# -> (# (# #) | BigNat# #) Source #

Subtract a Word# from a BigNat

bigNatSubUnsafe :: BigNat# -> BigNat# -> BigNat# Source #

Subtract two BigNat (don't check if a >= b)

bigNatSub :: BigNat# -> BigNat# -> (# (# #) | BigNat# #) Source #

Subtract two BigNat

bigNatQuotWord# :: BigNat# -> Word# -> BigNat# Source #

Divide a BigNat by a Word, return the quotient

Require: b /= 0

bigNatQuotWord :: BigNat# -> Word -> BigNat# Source #

Divide a BigNat by a Word, return the quotient

Require: b /= 0

bigNatRemWord# :: BigNat# -> Word# -> Word# Source #

Divide a BigNat by a Word, return the remainder

Require: b /= 0

bigNatRemWord :: BigNat# -> Word -> Word Source #

Divide a BigNat by a Word, return the remainder

Require: b /= 0

bigNatQuotRemWord# :: BigNat# -> Word# -> (# BigNat#, Word# #) Source #

QuotRem a BigNat by a Word

Require: b /= 0

bigNatQuotRem# :: BigNat# -> BigNat# -> (# BigNat#, BigNat# #) Source #

BigNat division returning (quotient,remainder)

bigNatQuot :: BigNat# -> BigNat# -> BigNat# Source #

BigNat division returning quotient

bigNatRem :: BigNat# -> BigNat# -> BigNat# Source #

BigNat division returning remainder

gcdWord# :: Word# -> Word# -> Word# Source #

Greatest common divisor between two Word#

gcdWord :: Word -> Word -> Word Source #

Greatest common divisor between two Word

gcdInt# :: Int# -> Int# -> Int# Source #

Greatest common divisor between two Int#

Warning: result may become negative if (at least) one argument is minBound

gcdInt :: Int -> Int -> Int Source #

Greatest common divisor between two Int

Warning: result may become negative if (at least) one argument is minBound

bigNatGcd :: BigNat# -> BigNat# -> BigNat# Source #

Greatest common divisor

bigNatGcdWord# :: BigNat# -> Word# -> Word# Source #

Greatest common divisor

bigNatLcm :: BigNat# -> BigNat# -> BigNat# Source #

Least common multiple

bigNatLcmWord# :: BigNat# -> Word# -> BigNat# Source #

Least common multiple with a Word#

bigNatLcmWordWord# :: Word# -> Word# -> BigNat# Source #

Least common multiple between two Word#

bigNatOr :: BigNat# -> BigNat# -> BigNat# Source #

Bitwise OR

bigNatOrWord# :: BigNat# -> Word# -> BigNat# Source #

Bitwise OR with Word#

bigNatAnd :: BigNat# -> BigNat# -> BigNat# Source #

Bitwise AND

bigNatAndNot :: BigNat# -> BigNat# -> BigNat# Source #

Bitwise ANDNOT

bigNatAndWord# :: BigNat# -> Word# -> BigNat# Source #

Bitwise AND with Word#

bigNatAndNotWord# :: BigNat# -> Word# -> BigNat# Source #

Bitwise ANDNOT with Word#

bigNatAndInt# :: BigNat# -> Int# -> BigNat# Source #

Bitwise AND with Int#

bigNatXor :: BigNat# -> BigNat# -> BigNat# Source #

Bitwise XOR

bigNatXorWord# :: BigNat# -> Word# -> BigNat# Source #

Bitwise XOR with Word#

bigNatPopCount :: BigNat# -> Word Source #

PopCount for BigNat

bigNatPopCount# :: BigNat# -> Word# Source #

PopCount for BigNat

bigNatShiftR# :: BigNat# -> Word# -> BigNat# Source #

Bit shift right

bigNatShiftRNeg# :: BigNat# -> Word# -> BigNat# Source #

Bit shift right (two's complement)

bigNatShiftR :: BigNat# -> Word -> BigNat# Source #

Bit shift right

bigNatShiftL :: BigNat# -> Word -> BigNat# Source #

Bit shift left

bigNatShiftL# :: BigNat# -> Word# -> BigNat# Source #

Bit shift left

bigNatTestBit# :: BigNat# -> Word# -> Bool# Source #

BigNat bit test

bigNatTestBit :: BigNat# -> Word -> Bool Source #

BigNat bit test

bigNatBit# :: Word# -> BigNat# Source #

Return a BigNat whose bit i is the only one set.

Specialized version of `bigNatShiftL (bigNatFromWord# 1##)`

bigNatBit :: Word -> BigNat# Source #

Return a BigNat whose bit i is the only one set.

Specialized version of `bigNatShiftL (bigNatFromWord# 1##)`

bigNatClearBit# :: BigNat# -> Word# -> BigNat# Source #

BigNat clear bit

bigNatSetBit# :: BigNat# -> Word# -> BigNat# Source #

BigNat set bit

bigNatComplementBit# :: BigNat# -> Word# -> BigNat# Source #

Reverse the given bit

bigNatLog2# :: BigNat# -> Word# Source #

Base 2 logarithm

bigNatLog2 :: BigNat# -> Word Source #

Base 2 logarithm

bigNatLogBase# :: BigNat# -> BigNat# -> Word# Source #

Logarithm for an arbitrary base

bigNatLogBase :: BigNat# -> BigNat# -> Word Source #

Logarithm for an arbitrary base

bigNatLogBaseWord# :: Word# -> BigNat# -> Word# Source #

Logarithm for an arbitrary base

bigNatLogBaseWord :: Word -> BigNat# -> Word Source #

Logarithm for an arbitrary base

bigNatSizeInBase# :: Word# -> BigNat# -> Word# Source #

Compute the number of digits of the BigNat in the given base.

base must be > 1

bigNatSizeInBase :: Word -> BigNat# -> Word Source #

Compute the number of digits of the BigNat in the given base.

base must be > 1

bigNatPowModWord# :: BigNat# -> BigNat# -> Word# -> Word# Source #

"bigNatPowModWord# b e m" computes base b raised to exponent e modulo m.

bigNatPowMod :: BigNat# -> BigNat# -> BigNat# -> BigNat# Source #

"bigNatPowMod b e m" computes base b raised to exponent e modulo m.

bigNatCtz# :: BigNat# -> Word# Source #

Return count of trailing zero bits

Return 0 for zero BigNat

bigNatCtz :: BigNat# -> Word Source #

Return count of trailing zero bits

Return 0 for zero BigNat

bigNatCtzWord# :: BigNat# -> Word# Source #

Return count of trailing zero words

Return 0 for zero BigNat

bigNatCtzWord :: BigNat# -> Word Source #

Return count of trailing zero words

Return 0 for zero BigNat

bigNatToAddrLE# :: BigNat# -> Addr# -> State# s -> (# State# s, Word# #) Source #

Write a BigNat in base-256 little-endian representation and return the number of bytes written.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatToAddrBE# :: BigNat# -> Addr# -> State# s -> (# State# s, Word# #) Source #

Write a BigNat in base-256 big-endian representation and return the number of bytes written.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatToAddr# :: BigNat# -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) Source #

Write a BigNat 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#.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatToAddr :: BigNat# -> Addr# -> Bool# -> IO Word Source #

Write a BigNat 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#.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatFromAddrLE# :: Word# -> Addr# -> State# s -> (# State# s, BigNat# #) Source #

Read a BigNat in base-256 little-endian representation from an Addr#.

The size is given in bytes.

Higher limbs equal to 0 are automatically trimed.

bigNatFromAddrBE# :: Word# -> Addr# -> State# s -> (# State# s, BigNat# #) Source #

Read a BigNat in base-256 big-endian representation from an Addr#.

The size is given in bytes.

Null higher limbs are automatically trimed.

bigNatFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, BigNat# #) Source #

Read a BigNat 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.

bigNatToMutableByteArrayLE# :: BigNat# -> MutableByteArray# s -> Word# -> State# s -> (# State# s, Word# #) Source #

Write a BigNat in base-256 little-endian representation and return the number of bytes written.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatToMutableByteArrayBE# :: BigNat# -> MutableByteArray# s -> Word# -> State# s -> (# State# s, Word# #) Source #

Write a BigNat in base-256 big-endian representation and return the number of bytes written.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatToMutableByteArray# :: BigNat# -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #) Source #

Write a BigNat 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#.

Use "bigNatSizeInBase 256# i" to compute the exact number of bytes written in advance. In case of i == 0, the function will write and report zero bytes written.

bigNatFromByteArrayLE# :: Word# -> ByteArray# -> Word# -> State# s -> (# State# s, BigNat# #) Source #

Read a BigNat in base-256 little-endian representation from a ByteArray#.

The size is given in bytes.

Null higher limbs are automatically trimed.

bigNatFromByteArrayBE# :: Word# -> ByteArray# -> Word# -> State# s -> (# State# s, BigNat# #) Source #

Read a BigNat in base-256 big-endian representation from a ByteArray#.

The size is given in bytes.

Null higher limbs are automatically trimed.

bigNatFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, BigNat# #) Source #

Read a BigNat 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.

bigNatFromWordArray# :: WordArray# -> Word# -> BigNat# Source #

Create a BigNat# from a WordArray# containing n limbs in least-significant-first order.

If possible WordArray#, will be used directly (i.e. shared without cloning the WordArray# into a newly allocated one)

bigNatFromWordArray :: WordArray# -> Word# -> BigNat Source #

Create a BigNat from a WordArray# containing n limbs in least-significant-first order.

If possible WordArray#, will be used directly (i.e. shared without cloning the WordArray# into a newly allocated one)