base-4.16.3.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

Description

Signed integer types

Synopsis

Signed integer types

dataIntSource#

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

Instances details
DataIntSource#

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) -> Int -> c IntSource#

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

toConstr :: Int -> ConstrSource#

dataTypeOf :: Int -> DataTypeSource#

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 -> IntSource#

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

gmapQr :: forall r r'. (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 IntSource#

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

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

StorableIntSource#

Since: base-2.1

Instance details

Defined in Foreign.Storable

BitsIntSource#

Since: base-2.1

Instance details

Defined in GHC.Bits

FiniteBitsIntSource#

Since: base-4.6.0.0

Instance details

Defined in GHC.Bits

BoundedIntSource#

Since: base-2.1

Instance details

Defined in GHC.Enum

EnumIntSource#

Since: base-2.1

Instance details

Defined in GHC.Enum

IxIntSource#

Since: base-2.1

Instance details

Defined in GHC.Ix

NumIntSource#

Since: base-2.1

Instance details

Defined in GHC.Num

ReadIntSource#

Since: base-2.1

Instance details

Defined in GHC.Read

IntegralIntSource#

Since: base-2.0.1

Instance details

Defined in GHC.Real

RealIntSource#

Since: base-2.0.1

Instance details

Defined in GHC.Real

ShowIntSource#

Since: base-2.1

Instance details

Defined in GHC.Show

PrintfArgIntSource#

Since: base-2.1

Instance details

Defined in Text.Printf

EqInt 
Instance details

Defined in GHC.Classes

Methods

(==) :: Int -> Int -> BoolSource#

(/=) :: Int -> Int -> BoolSource#

OrdInt 
Instance details

Defined in GHC.Classes

Generic1 (URecInt :: k -> Type)Source# 
Instance details

Defined in GHC.Generics

Associated Types

typeRep1 (URecInt) :: k -> TypeSource#

Methods

from1 :: forall (a :: k0). URecInt a -> Rep1 (URecInt) a Source#

to1 :: forall (a :: k0). Rep1 (URecInt) a -> URecInt a Source#

Foldable (UInt :: TYPELiftedRep -> Type)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UInt m -> m Source#

foldMap :: Monoid m => (a -> m) -> UInt a -> m Source#

foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source#

foldr :: (a -> b -> b) -> b -> UInt a -> b Source#

foldr' :: (a -> b -> b) -> b -> UInt a -> b Source#

foldl :: (b -> a -> b) -> b -> UInt a -> b Source#

foldl' :: (b -> a -> b) -> b -> UInt a -> b Source#

foldr1 :: (a -> a -> a) -> UInt a -> a Source#

foldl1 :: (a -> a -> a) -> UInt a -> a Source#

toList :: UInt a -> [a] Source#

null :: UInt a -> BoolSource#

length :: UInt a -> IntSource#

elem :: Eq a => a -> UInt a -> BoolSource#

maximum :: Ord a => UInt a -> a Source#

minimum :: Ord a => UInt a -> a Source#

sum :: Num a => UInt a -> a Source#

product :: Num a => UInt a -> a Source#

Traversable (UInt :: Type -> Type)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UInt a -> f (UInt b) Source#

sequenceA :: Applicative f => UInt (f a) -> f (UInt a) Source#

mapM :: Monad m => (a -> m b) -> UInt a -> m (UInt b) Source#

sequence :: Monad m => UInt (m a) -> m (UInt a) Source#

Functor (URecInt :: TYPELiftedRep -> Type)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URecInt a -> URecInt b Source#

(<$) :: a -> URecInt b -> URecInt a Source#

Generic (URecInt p)Source# 
Instance details

Defined in GHC.Generics

Associated Types

typeRep (URecInt p) :: Type -> TypeSource#

Methods

from :: URecInt p -> Rep (URecInt p) x Source#

to :: Rep (URecInt p) x -> URecInt p Source#

Show (URecInt p)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq (URecInt p)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URecInt p -> URecInt p -> BoolSource#

(/=) :: URecInt p -> URecInt p -> BoolSource#

Ord (URecInt p)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

dataURecInt (p :: k)Source#

Used for marking occurrences of Int#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

dataURecInt (p :: k) = UInt {}
typeRep1 (URecInt :: k -> Type)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

typeRep1 (URecInt :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: k -> Type)))
typeRep (URecInt p)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

typeRep (URecInt p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

dataInt8Source#

8-bit signed integer type

Instances

Instances details
DataInt8Source#

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) -> Int8 -> c Int8Source#

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

toConstr :: Int8 -> ConstrSource#

dataTypeOf :: Int8 -> DataTypeSource#

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 -> Int8Source#

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

gmapQr :: forall r r'. (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 Int8Source#

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

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

StorableInt8Source#

Since: base-2.1

Instance details

Defined in Foreign.Storable

BitsInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBitsInt8Source#

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

BoundedInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

EnumInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IxInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

NumInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ReadInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IntegralInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

RealInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ShowInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArgInt8Source#

Since: base-2.1

Instance details

Defined in Text.Printf

EqInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int8 -> Int8 -> BoolSource#

(/=) :: Int8 -> Int8 -> BoolSource#

OrdInt8Source#

Since: base-2.1

Instance details

Defined in GHC.Int

dataInt16Source#

16-bit signed integer type

Instances

Instances details
DataInt16Source#

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) -> Int16 -> c Int16Source#

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

toConstr :: Int16 -> ConstrSource#

dataTypeOf :: Int16 -> DataTypeSource#

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 -> Int16Source#

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

gmapQr :: forall r r'. (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 Int16Source#

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

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

StorableInt16Source#

Since: base-2.1

Instance details

Defined in Foreign.Storable

BitsInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBitsInt16Source#

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

BoundedInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

EnumInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IxInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

NumInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ReadInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IntegralInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

RealInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ShowInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArgInt16Source#

Since: base-2.1

Instance details

Defined in Text.Printf

EqInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

OrdInt16Source#

Since: base-2.1

Instance details

Defined in GHC.Int

dataInt32Source#

32-bit signed integer type

Instances

Instances details
DataInt32Source#

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) -> Int32 -> c Int32Source#

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

toConstr :: Int32 -> ConstrSource#

dataTypeOf :: Int32 -> DataTypeSource#

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 -> Int32Source#

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

gmapQr :: forall r r'. (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 Int32Source#

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

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

StorableInt32Source#

Since: base-2.1

Instance details

Defined in Foreign.Storable

BitsInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBitsInt32Source#

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

BoundedInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

EnumInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IxInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

NumInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ReadInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IntegralInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

RealInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ShowInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArgInt32Source#

Since: base-2.1

Instance details

Defined in Text.Printf

EqInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

OrdInt32Source#

Since: base-2.1

Instance details

Defined in GHC.Int

dataInt64Source#

64-bit signed integer type

Instances

Instances details
DataInt64Source#

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) -> Int64 -> c Int64Source#

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

toConstr :: Int64 -> ConstrSource#

dataTypeOf :: Int64 -> DataTypeSource#

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 -> Int64Source#

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

gmapQr :: forall r r'. (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 Int64Source#

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

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

StorableInt64Source#

Since: base-2.1

Instance details

Defined in Foreign.Storable

BitsInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBitsInt64Source#

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

BoundedInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

EnumInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IxInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

NumInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ReadInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

IntegralInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

RealInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

ShowInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArgInt64Source#

Since: base-2.1

Instance details

Defined in Text.Printf

EqInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

OrdInt64Source#

Since: base-2.1

Instance details

Defined in GHC.Int

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.
close