| Copyright | (c) The University of Glasgow 1994-2002 |
|---|---|
| License | see libraries/base/LICENSE |
| Maintainer | ghc-devs@haskell.org |
| Stability | internal |
| Portability | non-portable (GHC Extensions) |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
GHC.Num
Synopsis
- class Num a where
- subtract :: Num a => a -> a -> a
- quotRemInteger :: Integer -> Integer -> (# Integer, Integer #)
- integerFromNatural :: Natural -> Integer
- integerToNaturalClamp :: Integer -> Natural
- integerToNaturalThrow :: Integer -> Natural
- integerToNatural :: Integer -> Natural
- integerToWord# :: Integer -> Word#
- integerToInt# :: Integer -> Int#
- integerToWord64# :: Integer -> Word64#
- integerToInt64# :: Integer -> Int64#
- integerAdd :: Integer -> Integer -> Integer
- integerMul :: Integer -> Integer -> Integer
- integerSub :: Integer -> Integer -> Integer
- integerNegate :: Integer -> Integer
- integerAbs :: Integer -> Integer
- integerPopCount# :: Integer -> Int#
- integerQuot :: Integer -> Integer -> Integer
- integerRem :: Integer -> Integer -> Integer
- integerDiv :: Integer -> Integer -> Integer
- integerMod :: Integer -> Integer -> Integer
- integerDivMod# :: Integer -> Integer -> (# Integer, Integer #)
- integerQuotRem# :: Integer -> Integer -> (# Integer, Integer #)
- integerEncodeFloat# :: Integer -> Int# -> Float#
- integerEncodeDouble# :: Integer -> Int# -> Double#
- integerGcd :: Integer -> Integer -> Integer
- integerLcm :: Integer -> Integer -> Integer
- integerAnd :: Integer -> Integer -> Integer
- integerOr :: Integer -> Integer -> Integer
- integerXor :: Integer -> Integer -> Integer
- integerComplement :: Integer -> Integer
- integerBit# :: Word# -> Integer
- integerTestBit# :: Integer -> Word# -> Bool#
- integerShiftL# :: Integer -> Word# -> Integer
- integerShiftR# :: Integer -> Word# -> Integer
- integerFromWord# :: Word# -> Integer
- integerFromWord64# :: Word64# -> Integer
- integerFromInt64# :: Int64# -> Integer
- data Integer
- = IS Int#
- | IP ByteArray#
- | IN ByteArray#
- integerBit :: Word -> Integer
- integerCheck :: Integer -> Bool
- integerCheck# :: Integer -> Bool#
- integerCompare :: Integer -> Integer -> Ordering
- integerDecodeDouble# :: Double# -> (# Integer, Int# #)
- integerDivMod :: Integer -> Integer -> (Integer, Integer)
- integerEncodeDouble :: Integer -> Int -> Double
- integerEq :: Integer -> Integer -> Bool
- integerEq# :: Integer -> Integer -> Bool#
- integerFromAddr :: Word# -> Addr# -> Bool# -> IO Integer
- integerFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Integer #)
- integerFromBigNat# :: BigNat# -> Integer
- integerFromBigNatNeg# :: BigNat# -> Integer
- integerFromBigNatSign# :: Int# -> BigNat# -> Integer
- integerFromByteArray :: Word# -> ByteArray# -> Word# -> Bool# -> Integer
- integerFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Integer #)
- integerFromInt :: Int -> Integer
- integerFromInt# :: Int# -> Integer
- integerFromWord :: Word -> Integer
- integerFromWordList :: Bool -> [Word] -> Integer
- integerFromWordNeg# :: Word# -> Integer
- integerFromWordSign# :: Int# -> Word# -> Integer
- integerGcde :: Integer -> Integer -> (Integer, Integer, Integer)
- integerGcde# :: Integer -> Integer -> (# Integer, Integer, Integer #)
- integerGe :: Integer -> Integer -> Bool
- integerGe# :: Integer -> Integer -> Bool#
- integerGt :: Integer -> Integer -> Bool
- integerGt# :: Integer -> Integer -> Bool#
- integerIsNegative :: Integer -> Bool
- integerIsNegative# :: Integer -> Bool#
- integerIsOne :: Integer -> Bool
- integerIsPowerOf2# :: Integer -> (# (# #) | Word# #)
- integerIsZero :: Integer -> Bool
- integerLe :: Integer -> Integer -> Bool
- integerLe# :: Integer -> Integer -> Bool#
- integerLog2 :: Integer -> Word
- integerLog2# :: Integer -> Word#
- integerLogBase :: Integer -> Integer -> Word
- integerLogBase# :: Integer -> Integer -> Word#
- integerLogBaseWord :: Word -> Integer -> Word
- integerLogBaseWord# :: Word# -> Integer -> Word#
- integerLt :: Integer -> Integer -> Bool
- integerLt# :: Integer -> Integer -> Bool#
- integerNe :: Integer -> Integer -> Bool
- integerNe# :: Integer -> Integer -> Bool#
- integerOne :: Integer
- integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #)
- integerQuotRem :: Integer -> Integer -> (Integer, Integer)
- integerRecipMod# :: Integer -> Natural -> (# Natural | () #)
- integerShiftL :: Integer -> Word -> Integer
- integerShiftR :: Integer -> Word -> Integer
- integerSignum :: Integer -> Integer
- integerSignum# :: Integer -> Int#
- integerSizeInBase# :: Word# -> Integer -> Word#
- integerSqr :: Integer -> Integer
- integerTestBit :: Integer -> Word -> Bool
- integerToAddr :: Integer -> Addr# -> Bool# -> IO Word
- integerToAddr# :: Integer -> Addr# -> Bool# -> State# s -> (# State# s, Word# #)
- integerToBigNatClamp# :: Integer -> BigNat#
- integerToBigNatSign# :: Integer -> (# Int#, BigNat# #)
- integerToInt :: Integer -> Int
- integerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Bool# -> IO Word
- integerToMutableByteArray# :: Integer -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #)
- integerToWord :: Integer -> Word
- integerZero :: Integer
- naturalToWord# :: Natural -> Word#
- naturalPopCount# :: Natural -> Word#
- naturalShiftR# :: Natural -> Word# -> Natural
- naturalShiftL# :: Natural -> Word# -> Natural
- naturalAdd :: Natural -> Natural -> Natural
- naturalSub :: Natural -> Natural -> (# (# #) | Natural #)
- naturalSubThrow :: Natural -> Natural -> Natural
- naturalSubUnsafe :: Natural -> Natural -> Natural
- naturalMul :: Natural -> Natural -> Natural
- naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #)
- naturalQuot :: Natural -> Natural -> Natural
- naturalRem :: Natural -> Natural -> Natural
- naturalAnd :: Natural -> Natural -> Natural
- naturalAndNot :: Natural -> Natural -> Natural
- naturalOr :: Natural -> Natural -> Natural
- naturalXor :: Natural -> Natural -> Natural
- naturalTestBit# :: Natural -> Word# -> Bool#
- naturalBit# :: Word# -> Natural
- naturalGcd :: Natural -> Natural -> Natural
- naturalLcm :: Natural -> Natural -> Natural
- naturalLog2# :: Natural -> Word#
- naturalLogBaseWord# :: Word# -> Natural -> Word#
- naturalLogBase# :: Natural -> Natural -> Word#
- naturalPowMod :: Natural -> Natural -> Natural -> Natural
- naturalSizeInBase# :: Word# -> Natural -> Word#
- data Natural
- = NS Word#
- | NB ByteArray#
- naturalBit :: Word -> Natural
- naturalCheck :: Natural -> Bool
- naturalCheck# :: Natural -> Bool#
- naturalClearBit :: Natural -> Word -> Natural
- naturalClearBit# :: Natural -> Word# -> Natural
- naturalCompare :: Natural -> Natural -> Ordering
- naturalComplementBit :: Natural -> Word -> Natural
- naturalComplementBit# :: Natural -> Word# -> Natural
- naturalEncodeDouble# :: Natural -> Int# -> Double#
- naturalEncodeFloat# :: Natural -> Int# -> Float#
- naturalEq :: Natural -> Natural -> Bool
- naturalEq# :: Natural -> Natural -> Bool#
- naturalFromAddr :: Word# -> Addr# -> Bool# -> IO Natural
- naturalFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Natural #)
- naturalFromBigNat# :: BigNat# -> Natural
- naturalFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Natural #)
- naturalFromWord :: Word -> Natural
- naturalFromWord# :: Word# -> Natural
- naturalFromWord2# :: Word# -> Word# -> Natural
- naturalFromWordList :: [Word] -> Natural
- naturalGe :: Natural -> Natural -> Bool
- naturalGe# :: Natural -> Natural -> Bool#
- naturalGt :: Natural -> Natural -> Bool
- naturalGt# :: Natural -> Natural -> Bool#
- naturalIsOne :: Natural -> Bool
- naturalIsPowerOf2# :: Natural -> (# (# #) | Word# #)
- naturalIsZero :: Natural -> Bool
- naturalLe :: Natural -> Natural -> Bool
- naturalLe# :: Natural -> Natural -> Bool#
- naturalLog2 :: Natural -> Word
- naturalLogBase :: Natural -> Natural -> Word
- naturalLogBaseWord :: Word -> Natural -> Word
- naturalLt :: Natural -> Natural -> Bool
- naturalLt# :: Natural -> Natural -> Bool#
- naturalNe :: Natural -> Natural -> Bool
- naturalNe# :: Natural -> Natural -> Bool#
- naturalNegate :: Natural -> Natural
- naturalOne :: Natural
- naturalPopCount :: Natural -> Word
- naturalQuotRem :: Natural -> Natural -> (Natural, Natural)
- naturalSetBit :: Natural -> Word -> Natural
- naturalSetBit# :: Natural -> Word# -> Natural
- naturalShiftL :: Natural -> Word -> Natural
- naturalShiftR :: Natural -> Word -> Natural
- naturalSignum :: Natural -> Natural
- naturalSqr :: Natural -> Natural
- naturalTestBit :: Natural -> Word -> Bool
- naturalToAddr :: Natural -> Addr# -> Bool# -> IO Word
- naturalToAddr# :: Natural -> Addr# -> Bool# -> State# s -> (# State# s, Word# #)
- naturalToBigNat# :: Natural -> BigNat#
- naturalToMutableByteArray# :: Natural -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #)
- naturalToWord :: Natural -> Word
- naturalToWordClamp :: Natural -> Word
- naturalToWordClamp# :: Natural -> Word#
- naturalToWordMaybe# :: Natural -> (# (# #) | Word# #)
- naturalZero :: Natural
Documentation
Basic numeric class.
The Haskell Report defines no laws for Num. However, ( and +)( are
customarily expected to define a ring and have the following properties:*)
- Associativity of
(+) (x + y) + z=x + (y + z)- Commutativity of
(+) x + y=y + xis the additive identityfromInteger0x + fromInteger 0=xnegategives the additive inversex + negate x=fromInteger 0- Associativity of
(*) (x * y) * z=x * (y * z)is the multiplicative identityfromInteger1x * fromInteger 1=xandfromInteger 1 * x=x- Distributivity of
(with respect to*)(+) a * (b + c)=(a * b) + (a * c)and(b + c) * a=(b * a) + (c * a)- Coherence with
toInteger - if the type also implements
Integral, thenfromIntegeris a left inverse fortoInteger, i.e.fromInteger (toInteger i) == i
Note that it isn't customarily expected that a type instance of both Num
and Ord implement an ordered ring. Indeed, in base only Integer and
Rational do.
Methods
(+) :: a -> a -> a infixl 6 Source #
(-) :: a -> a -> a infixl 6 Source #
(*) :: a -> a -> a infixl 7 Source #
Unary negation.
Absolute value.
Sign of a number.
The functions abs and signum should satisfy the law:
abs x * signum x == x
For real numbers, the signum is either -1 (negative), 0 (zero)
or 1 (positive).
fromInteger :: Integer -> a Source #
Conversion from an Integer.
An integer literal represents the application of the function
fromInteger to the appropriate value of type Integer,
so such literals have type (.Num a) => a
Instances
quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) Source #
Deprecated: Use integerQuotRem# instead
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.
integerToNaturalThrow :: Integer -> Natural Source #
Convert an Integer into a Natural
Throw an Underflow exception if input is negative.
integerToNatural :: Integer -> Natural Source #
Convert an Integer into a Natural
Return absolute value
integerToWord# :: Integer -> Word# Source #
Truncate an Integer into a Word
integerToWord64# :: Integer -> Word64# Source #
Convert an Integer into a Word64#
integerToInt64# :: Integer -> Int64# Source #
Convert an Integer into an Int64#
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
integerPopCount# :: Integer -> Int# Source #
Count number of set bits. For negative arguments returns the negated population count of the absolute value.
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.
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.
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
integerEncodeDouble# :: Integer -> Int# -> Double# Source #
Encode (# Integer mantissa, Int# exponent #) into a Double#
integerAnd :: Integer -> Integer -> Integer Source #
Bitwise AND operation
Fake 2's complement for negative values (might be slow)
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)
integerComplement :: Integer -> Integer Source #
Binary complement of the
integerTestBit# :: Integer -> Word# -> Bool# Source #
Test if n-th bit is set.
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)
integerFromWord# :: Word# -> Integer Source #
Convert a Word# into an Integer
integerFromWord64# :: Word64# -> Integer Source #
Convert a Word64# into an Integer
integerFromInt64# :: Int64# -> Integer Source #
Convert an Int64# into an Integer
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 (i.e., fits into an Int), the IS constructor is
used. Otherwise IP and IN constructors are used to store a BigNat
representing the positive or the negative value magnitude, respectively.
Invariant: IP and IN are used iff the value does not fit in IS.
Constructors
| IS Int# | |
| IP ByteArray# | iff value in |
| IN ByteArray# | iff value in |
Instances
integerCheck :: Integer -> Bool Source #
Check Integer invariants
integerCheck# :: Integer -> Bool# Source #
Check Integer invariants
integerDecodeDouble# :: Double# -> (# Integer, Int# #) Source #
Decode a Double# into (# Integer mantissa, Int# exponent #)
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.
integerEncodeDouble :: Integer -> Int -> Double Source #
Encode (Integer mantissa, Int exponent) into a Double
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.
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.
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
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.
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.
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
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
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|
integerIsNegative :: Integer -> Bool Source #
Negative predicate
integerIsNegative# :: Integer -> Bool# Source #
Negative predicate
integerIsOne :: Integer -> Bool Source #
One predicate
integerIsPowerOf2# :: Integer -> (# (# #) | Word# #) Source #
Indicate if the value is a power of two and which one
integerIsZero :: Integer -> Bool Source #
Zero predicate
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
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
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
integerOne :: Integer Source #
Integer One
integerPowMod# :: Integer -> Integer -> Natural -> (# Natural | () #) Source #
Computes the modular exponentiation.
integerPowMod# b e m behaves as follows:
- If m > 1 and e >= 0, it returns an integer y with 0 <= y < m and y congruent to b^e modulo m.
- If m > 1 and e < 0, it uses
integerRecipMod#to try to find a modular multiplicative inverse b' (which only exists if gcd b m = 1) and then caculates (b')^(-e) modulo m (note that -e > 0); if the inverse does not exist then it fails. - If m = 1, it returns
0for all b and e. - If m = 0, it fails.
NB. Successful evaluation returns a value of the form (# n | #); failure is
indicated by returning (# | () #).
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.
integerRecipMod# :: Integer -> Natural -> (# Natural | () #) Source #
Computes the modular inverse.
integerRecipMod# x m behaves as follows:
- If m > 1 and gcd x m = 1, it returns an integer y with 0 < y < m such that x*y is congruent to 1 modulo m.
- If m > 1 and gcd x m > 1, it fails.
- If m = 1, it returns
0for all x. The computation effectively takes place in the zero ring, which has a single element 0 with 0+0 = 0*0 = 0: the element 0 is the multiplicative identity element and is its own multiplicative inverse. - If m = 0, it fails.
NB. Successful evaluation returns a value of the form (# n | #); failure is
indicated by returning (# | () #).
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.
integerShiftR :: Integer -> Word -> Integer Source #
Shift-right operation
Fake 2's complement for negative values (might be slow)
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
integerSizeInBase# :: Word# -> Integer -> Word# Source #
Compute the number of digits of the Integer (without the sign) in the given base.
base must be > 1
integerSqr :: Integer -> Integer Source #
Square a Integer
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)
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#.
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#.
integerToBigNatClamp# :: Integer -> BigNat# Source #
Convert an Integer into a BigNat.
Return 0 for negative Integers.
integerToBigNatSign# :: Integer -> (# Int#, BigNat# #) Source #
Convert an Integer into a sign-bit and a BigNat
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#.
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#.
integerToWord :: Integer -> Word Source #
Truncate an Integer into a Word
integerZero :: Integer Source #
Integer Zero
naturalToWord# :: Natural -> Word# Source #
Convert the lower bits of a Natural into a Word#
naturalPopCount# :: Natural -> Word# Source #
PopCount for Natural
naturalSubThrow :: Natural -> Natural -> Natural Source #
Sub two naturals
Throw an Underflow exception if x < y
naturalSubUnsafe :: Natural -> Natural -> Natural Source #
Sub two naturals
Unsafe: don't check that x >= y Undefined results if it happens
naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) Source #
Return division quotient and remainder
Division by zero is handled by BigNat
naturalBit# :: Word# -> Natural Source #
naturalLog2# :: Natural -> Word# Source #
Base 2 logarithm
naturalPowMod :: Natural -> Natural -> Natural -> Natural Source #
"" computes base naturalPowMod b e mb raised to
exponent e modulo m.
naturalSizeInBase# :: Word# -> Natural -> Word# Source #
Compute the number of digits of the Natural in the given base.
base must be > 1
Natural number
Invariant: numbers <= 0xffffffffffffffff use the NS constructor
Constructors
| NS Word# | |
| NB ByteArray# |
Instances
naturalBit :: Word -> Natural Source #
naturalCheck :: Natural -> Bool Source #
Check Natural invariants
naturalCheck# :: Natural -> Bool# Source #
Check Natural invariants
naturalEncodeDouble# :: Natural -> Int# -> Double# Source #
Encode (# Natural mantissa, Int# exponent #) into a Double#
naturalEncodeFloat# :: Natural -> Int# -> Float# Source #
Encode (# Natural mantissa, Int# exponent #) into a Float#
TODO: Not sure if it's worth to write Float optimized versions here
naturalFromAddr :: Word# -> Addr# -> Bool# -> IO Natural Source #
Read a Natural 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.
naturalFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Natural #) Source #
Read a Natural 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.
naturalFromBigNat# :: BigNat# -> Natural Source #
Create a Natural from a BigNat# (respect the invariants)
naturalFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> State# s -> (# State# s, Natural #) Source #
Read a Natural 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.
naturalFromWord :: Word -> Natural Source #
Create a Natural from a Word
naturalFromWord# :: Word# -> Natural Source #
Create a Natural from a Word#
naturalFromWord2# :: Word# -> Word# -> Natural Source #
Convert two Word# (most-significant first) into a Natural
naturalFromWordList :: [Word] -> Natural Source #
Create a Natural from a list of Word
naturalIsOne :: Natural -> Bool Source #
Test One Natural
naturalIsPowerOf2# :: Natural -> (# (# #) | Word# #) Source #
Indicate if the value is a power of two and which one
naturalIsZero :: Natural -> Bool Source #
Test Zero Natural
naturalLog2 :: Natural -> Word Source #
Base 2 logarithm
naturalNegate :: Natural -> Natural Source #
Negate for Natural
naturalOne :: Natural Source #
One Natural
naturalPopCount :: Natural -> Word Source #
PopCount for Natural
naturalQuotRem :: Natural -> Natural -> (Natural, Natural) Source #
Return division quotient and remainder
naturalSignum :: Natural -> Natural Source #
Signum for Natural
naturalSqr :: Natural -> Natural Source #
Square a Natural
naturalToAddr :: Natural -> Addr# -> Bool# -> IO Word Source #
Write a Natural 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#.
naturalToAddr# :: Natural -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) Source #
Write a Natural 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#.
naturalToBigNat# :: Natural -> BigNat# Source #
Convert a Natural into a BigNat#
naturalToMutableByteArray# :: Natural -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #) Source #
Write a Natural 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#.
naturalToWord :: Natural -> Word Source #
Convert the lower bits of a Natural into a Word
naturalToWordClamp :: Natural -> Word Source #
Convert a Natural into a Word# clamping to (maxBound :: Word).
naturalToWordClamp# :: Natural -> Word# Source #
Convert a Natural into a Word# clamping to (maxBound :: Word#).
naturalToWordMaybe# :: Natural -> (# (# #) | Word# #) Source #
naturalZero :: Natural Source #
Zero Natural