base-4.8.2.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Int

Contents

Description

Signed integer types

Synopsis

Signed integer types

data Int :: *

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Instances

Bounded Int Source 
Enum Int Source 
Eq Int 

Methods

(==) :: Int -> Int -> Bool

(/=) :: Int -> Int -> Bool

Integral Int Source 

Methods

quot :: Int -> Int -> Int Source

rem :: Int -> Int -> Int Source

div :: Int -> Int -> Int Source

mod :: Int -> Int -> Int Source

quotRem :: Int -> Int -> (Int, Int) Source

divMod :: Int -> Int -> (Int, Int) Source

toInteger :: Int -> Integer Source

Data Int Source 

Methods

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

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

toConstr :: Int -> Constr Source

dataTypeOf :: Int -> DataType Source

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

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

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

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

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

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

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

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

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

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

Num Int Source 
Ord Int 

Methods

compare :: Int -> Int -> Ordering

(<) :: Int -> Int -> Bool

(<=) :: Int -> Int -> Bool

(>) :: Int -> Int -> Bool

(>=) :: Int -> Int -> Bool

max :: Int -> Int -> Int

min :: Int -> Int -> Int

Read Int Source 
Real Int Source 
Show Int Source 
Ix Int Source 

Methods

range :: (Int, Int) -> [Int] Source

index :: (Int, Int) -> Int -> Int Source

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool Source

rangeSize :: (Int, Int) -> Int Source

unsafeRangeSize :: (Int, Int) -> Int

Generic Int Source 

Associated Types

type Rep Int :: * -> * Source

Methods

from :: Int -> Rep Int x Source

to :: Rep Int x -> Int Source

FiniteBits Int Source 
Bits Int Source 
Storable Int Source 
PrintfArg Int Source 
type Rep Int Source 

data Int8 Source

8-bit signed integer type

Instances

Bounded Int8 Source 
Enum Int8 Source 
Eq Int8 Source 

Methods

(==) :: Int8 -> Int8 -> Bool

(/=) :: Int8 -> Int8 -> Bool

Integral Int8 Source 
Data Int8 Source 

Methods

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

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

toConstr :: Int8 -> Constr Source

dataTypeOf :: Int8 -> DataType Source

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

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

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

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

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

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

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

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

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

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

Num Int8 Source 
Ord Int8 Source 

Methods

compare :: Int8 -> Int8 -> Ordering

(<) :: Int8 -> Int8 -> Bool

(<=) :: Int8 -> Int8 -> Bool

(>) :: Int8 -> Int8 -> Bool

(>=) :: Int8 -> Int8 -> Bool

max :: Int8 -> Int8 -> Int8

min :: Int8 -> Int8 -> Int8

Read Int8 Source 
Real Int8 Source 
Show Int8 Source 
Ix Int8 Source 
FiniteBits Int8 Source 
Bits Int8 Source 
Storable Int8 Source 
PrintfArg Int8 Source 

data Int16 Source

16-bit signed integer type

Instances

Bounded Int16 Source 
Enum Int16 Source 
Eq Int16 Source 

Methods

(==) :: Int16 -> Int16 -> Bool

(/=) :: Int16 -> Int16 -> Bool

Integral Int16 Source 
Data Int16 Source 

Methods

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

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

toConstr :: Int16 -> Constr Source

dataTypeOf :: Int16 -> DataType Source

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

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

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

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

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

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

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

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

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

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

Num Int16 Source 
Ord Int16 Source 

Methods

compare :: Int16 -> Int16 -> Ordering

(<) :: Int16 -> Int16 -> Bool

(<=) :: Int16 -> Int16 -> Bool

(>) :: Int16 -> Int16 -> Bool

(>=) :: Int16 -> Int16 -> Bool

max :: Int16 -> Int16 -> Int16

min :: Int16 -> Int16 -> Int16

Read Int16 Source 
Real Int16 Source 
Show Int16 Source 
Ix Int16 Source 
FiniteBits Int16 Source 
Bits Int16 Source 
Storable Int16 Source 
PrintfArg Int16 Source 

data Int32 Source

32-bit signed integer type

Instances

Bounded Int32 Source 
Enum Int32 Source 
Eq Int32 Source 

Methods

(==) :: Int32 -> Int32 -> Bool

(/=) :: Int32 -> Int32 -> Bool

Integral Int32 Source 
Data Int32 Source 

Methods

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

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

toConstr :: Int32 -> Constr Source

dataTypeOf :: Int32 -> DataType Source

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

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

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

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

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

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

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

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

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

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

Num Int32 Source 
Ord Int32 Source 

Methods

compare :: Int32 -> Int32 -> Ordering

(<) :: Int32 -> Int32 -> Bool

(<=) :: Int32 -> Int32 -> Bool

(>) :: Int32 -> Int32 -> Bool

(>=) :: Int32 -> Int32 -> Bool

max :: Int32 -> Int32 -> Int32

min :: Int32 -> Int32 -> Int32

Read Int32 Source 
Real Int32 Source 
Show Int32 Source 
Ix Int32 Source 
FiniteBits Int32 Source 
Bits Int32 Source 
Storable Int32 Source 
PrintfArg Int32 Source 

data Int64 Source

64-bit signed integer type

Instances

Bounded Int64 Source 
Enum Int64 Source 
Eq Int64 Source 

Methods

(==) :: Int64 -> Int64 -> Bool

(/=) :: Int64 -> Int64 -> Bool

Integral Int64 Source 
Data Int64 Source 

Methods

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

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

toConstr :: Int64 -> Constr Source

dataTypeOf :: Int64 -> DataType Source

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

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

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

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

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

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

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

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

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

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

Num Int64 Source 
Ord Int64 Source 

Methods

compare :: Int64 -> Int64 -> Ordering

(<) :: Int64 -> Int64 -> Bool

(<=) :: Int64 -> Int64 -> Bool

(>) :: Int64 -> Int64 -> Bool

(>=) :: Int64 -> Int64 -> Bool

max :: Int64 -> Int64 -> Int64

min :: Int64 -> Int64 -> Int64

Read Int64 Source 
Real Int64 Source 
Show Int64 Source 
Ix Int64 Source 
FiniteBits Int64 Source 
Bits Int64 Source 
Storable Int64 Source 
PrintfArg Int64 Source 

Notes

  • All arithmetic is performed modulo 2^n, where n is the number of bits in the type.
  • For coercing between any two integer types, use fromIntegral, which is specialized for all the common cases so should be fast enough. Coercing word types (see Data.Word) to and from integer types preserves representation, not sign.
  • The rules that hold for Enum instances over a bounded type such as Int (see the section of the Haskell report dealing with arithmetic sequences) also hold for the Enum instances over the various Int types defined here.
  • Right and left shifts by amounts greater than or equal to the width of the type result in either zero or -1, depending on the sign of the value being shifted. This is contrary to the behaviour in C, which is undefined; a common interpretation is to truncate the shift count to the width of the type, for example 1 << 32 == 1 in some C implementations.