base-4.10.1.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 :: * Source #

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 #

Since: 2.1

Enum Int #

Since: 2.1

Eq Int 

Methods

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

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

Integral Int #

Since: 2.0.1

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 #

Since: 4.0.0.0

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 #

Since: 2.1

Ord Int 

Methods

compare :: Int -> Int -> Ordering Source #

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

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

(>) :: Int -> Int -> Bool Source #

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

max :: Int -> Int -> Int Source #

min :: Int -> Int -> Int Source #

Read Int #

Since: 2.1

Real Int #

Since: 2.0.1

Show Int #

Since: 2.1

Ix Int #

Since: 2.1

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

FiniteBits Int #

Since: 4.6.0.0

Bits Int #

Since: 2.1

Storable Int #

Since: 2.1

PrintfArg Int #

Since: 2.1

Generic1 k (URec k Int) # 

Associated Types

type Rep1 (URec k Int) (f :: URec k Int -> *) :: k -> * Source #

Methods

from1 :: f a -> Rep1 (URec k Int) f a Source #

to1 :: Rep1 (URec k Int) f a -> f a Source #

Functor (URec * Int) # 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b Source #

(<$) :: a -> URec * Int b -> URec * Int a Source #

Foldable (URec * Int) # 

Methods

fold :: Monoid m => URec * Int m -> m Source #

foldMap :: Monoid m => (a -> m) -> URec * Int a -> m Source #

foldr :: (a -> b -> b) -> b -> URec * Int a -> b Source #

foldr' :: (a -> b -> b) -> b -> URec * Int a -> b Source #

foldl :: (b -> a -> b) -> b -> URec * Int a -> b Source #

foldl' :: (b -> a -> b) -> b -> URec * Int a -> b Source #

foldr1 :: (a -> a -> a) -> URec * Int a -> a Source #

foldl1 :: (a -> a -> a) -> URec * Int a -> a Source #

toList :: URec * Int a -> [a] Source #

null :: URec * Int a -> Bool Source #

length :: URec * Int a -> Int Source #

elem :: Eq a => a -> URec * Int a -> Bool Source #

maximum :: Ord a => URec * Int a -> a Source #

minimum :: Ord a => URec * Int a -> a Source #

sum :: Num a => URec * Int a -> a Source #

product :: Num a => URec * Int a -> a Source #

Traversable (URec * Int) # 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Int a -> f (URec * Int b) Source #

sequenceA :: Applicative f => URec * Int (f a) -> f (URec * Int a) Source #

mapM :: Monad m => (a -> m b) -> URec * Int a -> m (URec * Int b) Source #

sequence :: Monad m => URec * Int (m a) -> m (URec * Int a) Source #

Eq (URec k Int p) # 

Methods

(==) :: URec k Int p -> URec k Int p -> Bool Source #

(/=) :: URec k Int p -> URec k Int p -> Bool Source #

Ord (URec k Int p) # 

Methods

compare :: URec k Int p -> URec k Int p -> Ordering Source #

(<) :: URec k Int p -> URec k Int p -> Bool Source #

(<=) :: URec k Int p -> URec k Int p -> Bool Source #

(>) :: URec k Int p -> URec k Int p -> Bool Source #

(>=) :: URec k Int p -> URec k Int p -> Bool Source #

max :: URec k Int p -> URec k Int p -> URec k Int p Source #

min :: URec k Int p -> URec k Int p -> URec k Int p Source #

Show (URec k Int p) # 

Methods

showsPrec :: Int -> URec k Int p -> ShowS Source #

show :: URec k Int p -> String Source #

showList :: [URec k Int p] -> ShowS Source #

Generic (URec k Int p) # 

Associated Types

type Rep (URec k Int p) :: * -> * Source #

Methods

from :: URec k Int p -> Rep (URec k Int p) x Source #

to :: Rep (URec k Int p) x -> URec k Int p Source #

data URec k Int #

Used for marking occurrences of Int#

Since: 4.9.0.0

data URec k Int = UInt {}
type Rep1 k (URec k Int) # 
type Rep1 k (URec k Int) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UInt" PrefixI True) (S1 k (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt k)))
type Rep (URec k Int p) # 
type Rep (URec k Int p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UInt" PrefixI True) (S1 * (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt *)))

data Int8 Source #

8-bit signed integer type

Instances

Bounded Int8 #

Since: 2.1

Enum Int8 #

Since: 2.1

Eq Int8 #

Since: 2.1

Methods

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

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

Integral Int8 #

Since: 2.1

Data Int8 #

Since: 4.0.0.0

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 #

Since: 2.1

Ord Int8 #

Since: 2.1

Read Int8 #

Since: 2.1

Real Int8 #

Since: 2.1

Show Int8 #

Since: 2.1

Ix Int8 #

Since: 2.1

FiniteBits Int8 #

Since: 4.6.0.0

Bits Int8 #

Since: 2.1

Storable Int8 #

Since: 2.1

PrintfArg Int8 #

Since: 2.1

data Int16 Source #

16-bit signed integer type

Instances

Bounded Int16 #

Since: 2.1

Enum Int16 #

Since: 2.1

Eq Int16 #

Since: 2.1

Methods

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

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

Integral Int16 #

Since: 2.1

Data Int16 #

Since: 4.0.0.0

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 #

Since: 2.1

Ord Int16 #

Since: 2.1

Read Int16 #

Since: 2.1

Real Int16 #

Since: 2.1

Show Int16 #

Since: 2.1

Ix Int16 #

Since: 2.1

FiniteBits Int16 #

Since: 4.6.0.0

Bits Int16 #

Since: 2.1

Storable Int16 #

Since: 2.1

PrintfArg Int16 #

Since: 2.1

data Int32 Source #

32-bit signed integer type

Instances

Bounded Int32 #

Since: 2.1

Enum Int32 #

Since: 2.1

Eq Int32 #

Since: 2.1

Methods

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

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

Integral Int32 #

Since: 2.1

Data Int32 #

Since: 4.0.0.0

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 #

Since: 2.1

Ord Int32 #

Since: 2.1

Read Int32 #

Since: 2.1

Real Int32 #

Since: 2.1

Show Int32 #

Since: 2.1

Ix Int32 #

Since: 2.1

FiniteBits Int32 #

Since: 4.6.0.0

Bits Int32 #

Since: 2.1

Storable Int32 #

Since: 2.1

PrintfArg Int32 #

Since: 2.1

data Int64 Source #

64-bit signed integer type

Instances

Bounded Int64 #

Since: 2.1

Enum Int64 #

Since: 2.1

Eq Int64 #

Since: 2.1

Methods

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

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

Integral Int64 #

Since: 2.1

Data Int64 #

Since: 4.0.0.0

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 #

Since: 2.1

Ord Int64 #

Since: 2.1

Read Int64 #

Since: 2.1

Real Int64 #

Since: 2.1

Show Int64 #

Since: 2.1

Ix Int64 #

Since: 2.1

FiniteBits Int64 #

Since: 4.6.0.0

Bits Int64 #

Since: 2.1

Storable Int64 #

Since: 2.1

PrintfArg Int64 #

Since: 2.1

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.