base-4.22.0.0: Core data structures and operations
Copyright(c) The University of Glasgow 1994-2002
Licensesee libraries/base/LICENSE
Maintainerghc-devs@haskell.org
Stabilityinternal
Portabilitynon-portable (GHC Extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Num

Description

The Num class and the Integer type.

Synopsis

Documentation

class Num a where Source #

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 + x
fromInteger 0 is the additive identity
x + fromInteger 0 = x
negate gives the additive inverse
x + negate x = fromInteger 0
Associativity of (*)
(x * y) * z = x * (y * z)
fromInteger 1 is the multiplicative identity
x * fromInteger 1 = x and fromInteger 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, then fromInteger is a left inverse for toInteger, 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.

Minimal complete definition

(+), (*), abs, signum, fromInteger, (negate | (-))

Methods

(+) :: a -> a -> a infixl 6 Source #

(-) :: a -> a -> a infixl 6 Source #

(*) :: a -> a -> a infixl 7 Source #

negate :: a -> a Source #

Unary negation.

abs :: a -> a Source #

Absolute value.

signum :: a -> a Source #

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

Instances details
Num Unique Source #

Since: base-4.4.0.0

Instance details

Defined in GHC.Internal.Event.Unique

Methods

(+) :: Unique -> Unique -> Unique Source #

(-) :: Unique -> Unique -> Unique Source #

(*) :: Unique -> Unique -> Unique Source #

negate :: Unique -> Unique Source #

abs :: Unique -> Unique Source #

signum :: Unique -> Unique Source #

fromInteger :: Integer -> Unique Source #

Num CBool Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CClock Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CDouble Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CFloat Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CLLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CPtrdiff Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSigAtomic Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CSize Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CTime Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUChar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUInt Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUIntMax Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUIntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CULLong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CULong Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUSeconds Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CUShort Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num CWchar Source # 
Instance details

Defined in GHC.Internal.Foreign.C.Types

Num IntPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num WordPtr Source # 
Instance details

Defined in GHC.Internal.Foreign.Ptr

Num HalfWord Source # 
Instance details

Defined in GHC.Internal.Heap.InfoTable.Types

Num Int16 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num Int32 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num Int64 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num Int8 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Int

Num ByteOffset Source # 
Instance details

Defined in GHC.Internal.Stack.Constants

Num WordOffset Source # 
Instance details

Defined in GHC.Internal.Stack.Constants

Num ByteOffset Source # 
Instance details

Defined in GHC.Internal.Stack.ConstantsProf

Num WordOffset Source # 
Instance details

Defined in GHC.Internal.Stack.ConstantsProf

Num CBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CBlkSize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CCc Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CClockId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CDev Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsBlkCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CFsFilCnt Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CGid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CId Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CIno Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CKey Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CMode Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CNfds Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CNlink Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num COff Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CPid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CRLim Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSocklen Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSpeed Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CSsize Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CTcflag Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num CUid Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Num Fd Source # 
Instance details

Defined in GHC.Internal.System.Posix.Types

Methods

(+) :: Fd -> Fd -> Fd Source #

(-) :: Fd -> Fd -> Fd Source #

(*) :: Fd -> Fd -> Fd Source #

negate :: Fd -> Fd Source #

abs :: Fd -> Fd Source #

signum :: Fd -> Fd Source #

fromInteger :: Integer -> Fd Source #

Num Word16 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Num Word32 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Num Word64 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Num Word8 Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Word

Num Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Num

Num Natural Source #

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Num

Num Double Source #

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1) + 0.4 == 0.1 + (0.1 + 0.4)
False
>>> (0.1 + 0.2) * 0.3 == 0.1 * 0.3 + 0.2 * 0.3
False
>>> (0.1 * 0.1) * 0.3 == 0.1 * (0.1 * 0.3)
False

Since: base-2.1

Instance details

Defined in GHC.Internal.Float

Num Float Source #

This instance implements IEEE 754 standard with all its usual pitfalls about NaN, infinities and negative zero. Neither addition nor multiplication are associative or distributive:

>>> (0.1 + 0.1 :: Float) + 0.5 == 0.1 + (0.1 + 0.5)
False
>>> (0.1 + 0.2 :: Float) * 0.9 == 0.1 * 0.9 + 0.2 * 0.9
False
>>> (0.1 * 0.1 :: Float) * 0.9 == 0.1 * (0.1 * 0.9)
False

Since: base-2.1

Instance details

Defined in GHC.Internal.Float

Num Int Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Num

Num Word Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Num

RealFloat a => Num (Complex a) Source #

Since: base-2.1

Instance details

Defined in Data.Complex

Num a => Num (Max a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(+) :: Max a -> Max a -> Max a Source #

(-) :: Max a -> Max a -> Max a Source #

(*) :: Max a -> Max a -> Max a Source #

negate :: Max a -> Max a Source #

abs :: Max a -> Max a Source #

signum :: Max a -> Max a Source #

fromInteger :: Integer -> Max a Source #

Num a => Num (Min a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(+) :: Min a -> Min a -> Min a Source #

(-) :: Min a -> Min a -> Min a Source #

(*) :: Min a -> Min a -> Min a Source #

negate :: Min a -> Min a Source #

abs :: Min a -> Min a Source #

signum :: Min a -> Min a Source #

fromInteger :: Integer -> Min a Source #

Num a => Num (Identity a) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Identity

Num a => Num (Down a) Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.Data.Ord

Methods

(+) :: Down a -> Down a -> Down a Source #

(-) :: Down a -> Down a -> Down a Source #

(*) :: Down a -> Down a -> Down a Source #

negate :: Down a -> Down a Source #

abs :: Down a -> Down a Source #

signum :: Down a -> Down a Source #

fromInteger :: Integer -> Down a Source #

Num a => Num (Product a) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Num a => Num (Sum a) Source #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a Source #

(-) :: Sum a -> Sum a -> Sum a Source #

(*) :: Sum a -> Sum a -> Sum a Source #

negate :: Sum a -> Sum a Source #

abs :: Sum a -> Sum a Source #

signum :: Sum a -> Sum a Source #

fromInteger :: Integer -> Sum a Source #

Integral a => Num (Ratio a) Source #

Since: base-2.0.1

Instance details

Defined in GHC.Internal.Real

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

(-) :: Ratio a -> Ratio a -> Ratio a Source #

(*) :: Ratio a -> Ratio a -> Ratio a Source #

negate :: Ratio a -> Ratio a Source #

abs :: Ratio a -> Ratio a Source #

signum :: Ratio a -> Ratio a Source #

fromInteger :: Integer -> Ratio a Source #

HasResolution a => Num (Fixed a) Source #

Multiplication is not associative or distributive:

>>> (0.2 * 0.6 :: Deci) * 0.9 == 0.2 * (0.6 * 0.9)
False
>>> (0.1 + 0.1 :: Deci) * 0.5 == 0.1 * 0.5 + 0.1 * 0.5
False

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

(+) :: Fixed a -> Fixed a -> Fixed a Source #

(-) :: Fixed a -> Fixed a -> Fixed a Source #

(*) :: Fixed a -> Fixed a -> Fixed a Source #

negate :: Fixed a -> Fixed a Source #

abs :: Fixed a -> Fixed a Source #

signum :: Fixed a -> Fixed a Source #

fromInteger :: Integer -> Fixed a Source #

Num a => Num (Op a b) Source # 
Instance details

Defined in Data.Functor.Contravariant

Methods

(+) :: Op a b -> Op a b -> Op a b Source #

(-) :: Op a b -> Op a b -> Op a b Source #

(*) :: Op a b -> Op a b -> Op a b Source #

negate :: Op a b -> Op a b Source #

abs :: Op a b -> Op a b Source #

signum :: Op a b -> Op a b Source #

fromInteger :: Integer -> Op a b Source #

Num a => Num (Const a b) Source #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Functor.Const

Methods

(+) :: Const a b -> Const a b -> Const a b Source #

(-) :: Const a b -> Const a b -> Const a b Source #

(*) :: Const a b -> Const a b -> Const a b Source #

negate :: Const a b -> Const a b Source #

abs :: Const a b -> Const a b Source #

signum :: Const a b -> Const a b Source #

fromInteger :: Integer -> Const a b Source #

(Applicative f, Num a) => Num (Ap f a) Source #

Note that even if the underlying Num and Applicative instances are lawful, for most Applicatives, this instance will not be lawful. If you use this instance with the list Applicative, the following customary laws will not hold:

Commutativity:

>>> Ap [10,20] + Ap [1,2]
Ap {getAp = [11,12,21,22]}
>>> Ap [1,2] + Ap [10,20]
Ap {getAp = [11,21,12,22]}

Additive inverse:

>>> Ap [] + negate (Ap [])
Ap {getAp = []}
>>> fromInteger 0 :: Ap [] Int
Ap {getAp = [0]}

Distributivity:

>>> Ap [1,2] * (3 + 4)
Ap {getAp = [7,14]}
>>> (Ap [1,2] * 3) + (Ap [1,2] * 4)
Ap {getAp = [7,11,10,14]}

Since: base-4.12.0.0

Instance details

Defined in GHC.Internal.Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a Source #

(-) :: Ap f a -> Ap f a -> Ap f a Source #

(*) :: Ap f a -> Ap f a -> Ap f a Source #

negate :: Ap f a -> Ap f a Source #

abs :: Ap f a -> Ap f a Source #

signum :: Ap f a -> Ap f a Source #

fromInteger :: Integer -> Ap f a Source #

Num (f a) => Num (Alt f a) Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Semigroup.Internal

Methods

(+) :: Alt f a -> Alt f a -> Alt f a Source #

(-) :: Alt f a -> Alt f a -> Alt f a Source #

(*) :: Alt f a -> Alt f a -> Alt f a Source #

negate :: Alt f a -> Alt f a Source #

abs :: Alt f a -> Alt f a Source #

signum :: Alt f a -> Alt f a Source #

fromInteger :: Integer -> Alt f a Source #

Num (f (g a)) => Num (Compose f g a) Source #

Since: base-4.19.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(+) :: Compose f g a -> Compose f g a -> Compose f g a Source #

(-) :: Compose f g a -> Compose f g a -> Compose f g a Source #

(*) :: Compose f g a -> Compose f g a -> Compose f g a Source #

negate :: Compose f g a -> Compose f g a Source #

abs :: Compose f g a -> Compose f g a Source #

signum :: Compose f g a -> Compose f g a Source #

fromInteger :: Integer -> Compose f g a Source #

subtract :: Num a => a -> a -> a Source #

the same as flip (-).

Because - is treated specially in the Haskell grammar, (- e) is not a section, but an application of prefix negation. However, (subtract exp) is equivalent to the disallowed section.

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

integerToInt# :: Integer -> Int# Source #

Truncates Integer to least-significant Int#

integerToWord64# :: Integer -> Word64# Source #

Convert an Integer into a Word64#

integerToInt64# :: Integer -> Int64# Source #

Convert an Integer into an Int64#

integerSub :: Integer -> Integer -> Integer Source #

Subtract one Integer from another.

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

integerAbs :: Integer -> Integer Source #

Compute absolute value of an Integer

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#

integerGcd :: Integer -> Integer -> Integer Source #

Compute greatest common divisor.

integerLcm :: Integer -> Integer -> Integer Source #

Compute least common multiple.

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

integerBit# :: Word# -> Integer Source #

Positive Integer for which only n-th bit is set

integerTestBit# :: Integer -> Word# -> Bool# Source #

Test if n-th bit is set.

Fake 2's complement for negative values (might be slow)

integerShiftL# :: Integer -> Word# -> Integer Source #

Shift-left operation

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

data Integer Source #

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#

iff value in [minBound::Int, maxBound::Int] range

IP ByteArray#

iff value in ]maxBound::Int, +inf[ range

IN ByteArray#

iff value in ]-inf, minBound::Int[ range

Instances

Instances details
PrintfArg Integer Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Bits Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Bits

Eq Integer Source # 
Instance details

Defined in GHC.Internal.Bignum.Integer

Ord Integer Source # 
Instance details

Defined in GHC.Internal.Bignum.Integer

Data Integer Source #

Since: base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer Source #

toConstr :: Integer -> Constr Source #

dataTypeOf :: Integer -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) Source #

gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

Enum Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Enum

Ix Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Ix

Num Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Num

Read Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Read

Integral Integer Source #

Since: base-2.0.1

Instance details

Defined in GHC.Internal.Real

Real Integer Source #

Since: base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Internal.Show

Lift Integer Source # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Integer -> m Exp Source #

liftTyped :: Quote m => Integer -> Code m Integer Source #

integerBit :: Word -> Integer Source #

Integer for which only n-th bit is set

integerCheck :: Integer -> Bool Source #

Check Integer invariants

integerCheck# :: Integer -> Bool# Source #

Check Integer invariants

integerCompare :: Integer -> Integer -> Ordering Source #

Compare two Integer

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

integerEq :: Integer -> Integer -> Bool Source #

Equal predicate.

integerEq# :: Integer -> Integer -> Bool# Source #

Equal predicate.

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

integerFromWordList :: Bool -> [Word] -> Integer Source #

Convert a list of 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|

integerGe :: Integer -> Integer -> Bool Source #

Greater-or-equal predicate.

integerGe# :: Integer -> Integer -> Bool# Source #

Greater-or-equal predicate.

integerGt :: Integer -> Integer -> Bool Source #

Greater predicate.

integerGt# :: Integer -> Integer -> Bool# Source #

Greater predicate.

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

integerLe :: Integer -> Integer -> Bool Source #

Lower-or-equal predicate.

integerLe# :: Integer -> Integer -> Bool# Source #

Lower-or-equal 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

integerLt :: Integer -> Integer -> Bool Source #

Lower predicate.

integerLt# :: Integer -> Integer -> Bool# Source #

Lower predicate.

integerNe :: Integer -> Integer -> Bool Source #

Not-equal predicate.

integerNe# :: Integer -> Integer -> Bool# Source #

Not-equal predicate.

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 0 for 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 0 for 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

integerToInt :: Integer -> Int Source #

Truncates Integer to least-significant Int#

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

naturalShiftR# :: Natural -> Word# -> Natural Source #

Right shift for Natural

naturalAdd :: Natural -> Natural -> Natural Source #

Add two naturals

naturalSub :: Natural -> Natural -> (# (# #) | Natural #) Source #

Sub two naturals

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

naturalMul :: Natural -> Natural -> Natural Source #

Multiplication

naturalQuotRem# :: Natural -> Natural -> (# Natural, Natural #) Source #

Return division quotient and remainder

Division by zero is handled by BigNat

naturalQuot :: Natural -> Natural -> Natural Source #

Return division quotient

naturalRem :: Natural -> Natural -> Natural Source #

Return division remainder

naturalGcd :: Natural -> Natural -> Natural Source #

Compute greatest common divisor.

naturalLcm :: Natural -> Natural -> Natural Source #

Compute least common multiple.

naturalLog2# :: Natural -> Word# Source #

Base 2 logarithm

naturalLogBaseWord# :: Word# -> Natural -> Word# Source #

Logarithm for an arbitrary base

naturalLogBase# :: Natural -> Natural -> Word# Source #

Logarithm for an arbitrary base

naturalPowMod :: Natural -> Natural -> Natural -> Natural Source #

"naturalPowMod b e m" computes base b 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

data Natural Source #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Constructors

NS Word# 
NB ByteArray# 

Instances

Instances details
PrintfArg Natural Source #

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Bits Natural Source #

Since: base-4.8.0

Instance details

Defined in GHC.Internal.Bits

Eq Natural Source # 
Instance details

Defined in GHC.Internal.Bignum.Natural

Ord Natural Source # 
Instance details

Defined in GHC.Internal.Bignum.Natural

Data Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural Source #

toConstr :: Natural -> Constr Source #

dataTypeOf :: Natural -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Natural) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) Source #

gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural Source #

Enum Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Enum

Ix Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Ix

Num Natural Source #

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Num

Read Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Read

Integral Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Real Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Real

Show Natural Source #

Since: base-4.8.0.0

Instance details

Defined in GHC.Internal.Show

KnownNat n => HasResolution (n :: Nat) Source #

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution :: p n -> Integer Source #

TestCoercion SNat Source #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

testCoercion :: SNat a -> SNat b -> Maybe (Coercion a b) Source #

TestEquality SNat Source #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeNats

Methods

testEquality :: SNat a -> SNat b -> Maybe (a :~: b) Source #

Lift Natural Source # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Natural -> m Exp Source #

liftTyped :: Quote m => Natural -> Code m Natural Source #

type Compare (a :: Natural) (b :: Natural) Source # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

type Compare (a :: Natural) (b :: Natural) = CmpNat a b

naturalCheck :: Natural -> Bool Source #

Check Natural invariants

naturalCheck# :: Natural -> Bool# Source #

Check Natural invariants

naturalClearBit :: Natural -> Word -> Natural Source #

Since: ghc-internal-1.3

naturalClearBit# :: Natural -> Word# -> Natural Source #

Since: ghc-internal-1.3

naturalCompare :: Natural -> Natural -> Ordering Source #

Compare two Natural

naturalComplementBit :: Natural -> Word -> Natural Source #

Since: ghc-internal-1.3

naturalComplementBit# :: Natural -> Word# -> Natural Source #

Since: ghc-internal-1.3

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

naturalEq :: Natural -> Natural -> Bool Source #

Equality test for Natural

naturalEq# :: Natural -> Natural -> Bool# Source #

Equality test for Natural

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

naturalGe :: Natural -> Natural -> Bool Source #

Greater or equal test for Natural

naturalGe# :: Natural -> Natural -> Bool# Source #

Greater or equal test for Natural

naturalGt :: Natural -> Natural -> Bool Source #

Greater test for Natural

naturalGt# :: Natural -> Natural -> Bool# Source #

Greater test for Natural

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

naturalLe :: Natural -> Natural -> Bool Source #

Lower or equal test for Natural

naturalLe# :: Natural -> Natural -> Bool# Source #

Lower or equal test for Natural

naturalLog2 :: Natural -> Word Source #

Base 2 logarithm

naturalLogBase :: Natural -> Natural -> Word Source #

Logarithm for an arbitrary base

naturalLogBaseWord :: Word -> Natural -> Word Source #

Logarithm for an arbitrary base

naturalLt :: Natural -> Natural -> Bool Source #

Lower test for Natural

naturalLt# :: Natural -> Natural -> Bool# Source #

Lower test for Natural

naturalNe :: Natural -> Natural -> Bool Source #

Inequality test for Natural

naturalNe# :: Natural -> Natural -> Bool# Source #

Inequality test for Natural

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

naturalSetBit :: Natural -> Word -> Natural Source #

Since: ghc-internal-1.3

naturalSetBit# :: Natural -> Word# -> Natural Source #

Since: ghc-internal-1.3

naturalShiftR :: Natural -> Word -> Natural Source #

Right shift for Natural

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 #

Try downcasting Natural to Word value. Returns (##) if value doesn't fit in Word.

naturalZero :: Natural Source #

Zero Natural