base-4.17.0.0: Basic libraries
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Integer

Description

Compatibility module for pre ghc-bignum code.

Synopsis

Documentation

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 (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

Instances

Instances details
Data Integer Source #

Since: base-4.0.0.0

Instance details

Defined in 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 #

Bits Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Bits

Enum Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Enum

Ix Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Ix

Num Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Num

Read Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Integer Source #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Real Integer Source #

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show Integer Source #

Since: base-2.1

Instance details

Defined in GHC.Show

PrintfArg Integer Source #

Since: base-2.1

Instance details

Defined in Text.Printf

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Construct Integers

Conversion to other integral types

Helpers for RealFloat type-class operations

Arithmetic operations

plusInteger :: Integer -> Integer -> Integer Source #

Used to implement (+) for the Num typeclass. This gives the sum of two integers.

Example

Expand
>>> plusInteger 3 2
5
>>> (+) 3 2
5

minusInteger :: Integer -> Integer -> Integer Source #

Used to implement (-) for the Num typeclass. This gives the difference of two integers.

Example

Expand
>>> minusInteger 3 2
1
>>> (-) 3 2
1

timesInteger :: Integer -> Integer -> Integer Source #

Used to implement (*) for the Num typeclass. This gives the product of two integers.

Example

Expand
>>> timesInteger 3 2
6
>>> (*) 3 2
6

negateInteger :: Integer -> Integer Source #

Used to implement negate for the Num typeclass. This changes the sign of whatever integer is passed into it.

Example

Expand
>>> negateInteger (-6)
6
>>> negate (-6)
6

absInteger :: Integer -> Integer Source #

Used to implement abs for the Num typeclass. This gives the absolute value of whatever integer is passed into it.

Example

Expand
>>> absInteger (-6)
6
>>> abs (-6)
6

signumInteger :: Integer -> Integer Source #

Used to implement signum for the Num typeclass. This gives 1 for a positive integer, and -1 for a negative integer.

Example

Expand
>>> signumInteger 5
1
>>> signum 5
1

divModInteger :: Integer -> Integer -> (# Integer, Integer #) Source #

Used to implement divMod for the Integral typeclass. This gives a tuple equivalent to

(div x y, mod x y)

Example

Expand
>>> divModInteger 10 2
(5,0)
>>> divMod 10 2
(5,0)

divInteger :: Integer -> Integer -> Integer Source #

Used to implement div for the Integral typeclass. This performs integer division on its two parameters, truncated towards negative infinity.

Example

Expand
>>> 10 `divInteger` 2
5
>>> 10 `div` 2

modInteger :: Integer -> Integer -> Integer Source #

Used to implement mod for the Integral typeclass. This performs the modulo operation, satisfying

((x `div` y) * y) + (x `mod` y) == x

Example

Expand
>>> 7 `modInteger` 3
1
>>> 7 `mod` 3
1

quotRemInteger :: Integer -> Integer -> (# Integer, Integer #) Source #

Used to implement quotRem for the Integral typeclass. This gives a tuple equivalent to

(quot x y, mod x y)

Example

Expand
>>> quotRemInteger 10 2
(5,0)
>>> quotRem 10 2
(5,0)

quotInteger :: Integer -> Integer -> Integer Source #

Used to implement quot for the Integral typeclass. This performs integer division on its two parameters, truncated towards zero.

Example

Expand
>>> quotInteger 10 2
5
>>> quot 10 2
5

remInteger :: Integer -> Integer -> Integer Source #

Used to implement rem for the Integral typeclass. This gives the remainder after integer division of its two parameters, satisfying

((x `quot` y) * y) + (x `rem` y) == x

Example

Expand
>>> remInteger 3 2
1
>>> rem 3 2
1

Comparison predicates

eqInteger :: Integer -> Integer -> Bool Source #

Used to implement (==) for the Eq typeclass. Outputs True if two integers are equal to each other.

Example

Expand
>>> 6 `eqInteger` 6
True
>>> 6 == 6
True

neqInteger :: Integer -> Integer -> Bool Source #

Used to implement (/=) for the Eq typeclass. Outputs True if two integers are not equal to each other.

Example

Expand
>>> 6 `neqInteger` 7
True
>>> 6 /= 7
True

leInteger :: Integer -> Integer -> Bool Source #

Used to implement (<=) for the Ord typeclass. Outputs True if the first argument is less than or equal to the second.

Example

Expand
>>> 3 `leInteger` 5
True
>>> 3 <= 5
True

gtInteger :: Integer -> Integer -> Bool Source #

Used to implement (>) for the Ord typeclass. Outputs True if the first argument is greater than the second.

Example

Expand
>>> 5 `gtInteger` 3
True
>>> 5 > 3
True

ltInteger :: Integer -> Integer -> Bool Source #

Used to implement (<) for the Ord typeclass. Outputs True if the first argument is less than the second.

Example

Expand
>>> 3 `ltInteger` 5
True
>>> 3 < 5
True

geInteger :: Integer -> Integer -> Bool Source #

Used to implement (>=) for the Ord typeclass. Outputs True if the first argument is greater than or equal to the second.

Example

Expand
>>> 5 `geInteger` 3
True
>>> 5 >= 3
True

compareInteger :: Integer -> Integer -> Ordering Source #

Used to implement compare for the Integral typeclass. This takes two integers, and outputs whether the first is less than, equal to, or greater than the second.

Example

Expand
>>> compareInteger 2 10
LT
>>> compare 2 10
LT

Int#-boolean valued versions of comparison predicates

These operations return 0# and 1# instead of False and True respectively. See PrimBool wiki-page for more details

Bit-operations

Hashing