| Copyright | (c) The University of Glasgow 2001 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Int
Contents
Description
Signed integer types
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
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
Methods
toRational :: Int -> Rational Source
Methods
finiteBitSize :: Int -> Int Source
countLeadingZeros :: Int -> Int Source
countTrailingZeros :: Int -> Int Source
Methods
(.&.) :: Int -> Int -> Int Source
(.|.) :: Int -> Int -> Int Source
xor :: Int -> Int -> Int Source
complement :: Int -> Int Source
shift :: Int -> Int -> Int Source
rotate :: Int -> Int -> Int Source
setBit :: Int -> Int -> Int Source
clearBit :: Int -> Int -> Int Source
complementBit :: Int -> Int -> Int Source
testBit :: Int -> Int -> Bool Source
bitSizeMaybe :: Int -> Maybe Int Source
isSigned :: Int -> Bool Source
shiftL :: Int -> Int -> Int Source
unsafeShiftL :: Int -> Int -> Int Source
shiftR :: Int -> Int -> Int Source
unsafeShiftR :: Int -> Int -> Int Source
rotateL :: Int -> Int -> Int Source
8-bit signed integer type
Instances
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
Methods
toRational :: Int8 -> Rational Source
Methods
finiteBitSize :: Int8 -> Int Source
countLeadingZeros :: Int8 -> Int Source
countTrailingZeros :: Int8 -> Int Source
Methods
(.&.) :: Int8 -> Int8 -> Int8 Source
(.|.) :: Int8 -> Int8 -> Int8 Source
xor :: Int8 -> Int8 -> Int8 Source
complement :: Int8 -> Int8 Source
shift :: Int8 -> Int -> Int8 Source
rotate :: Int8 -> Int -> Int8 Source
setBit :: Int8 -> Int -> Int8 Source
clearBit :: Int8 -> Int -> Int8 Source
complementBit :: Int8 -> Int -> Int8 Source
testBit :: Int8 -> Int -> Bool Source
bitSizeMaybe :: Int8 -> Maybe Int Source
isSigned :: Int8 -> Bool Source
shiftL :: Int8 -> Int -> Int8 Source
unsafeShiftL :: Int8 -> Int -> Int8 Source
shiftR :: Int8 -> Int -> Int8 Source
unsafeShiftR :: Int8 -> Int -> Int8 Source
rotateL :: Int8 -> Int -> Int8 Source
16-bit signed integer type
Instances
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
Methods
toRational :: Int16 -> Rational Source
Methods
finiteBitSize :: Int16 -> Int Source
countLeadingZeros :: Int16 -> Int Source
countTrailingZeros :: Int16 -> Int Source
Methods
(.&.) :: Int16 -> Int16 -> Int16 Source
(.|.) :: Int16 -> Int16 -> Int16 Source
xor :: Int16 -> Int16 -> Int16 Source
complement :: Int16 -> Int16 Source
shift :: Int16 -> Int -> Int16 Source
rotate :: Int16 -> Int -> Int16 Source
setBit :: Int16 -> Int -> Int16 Source
clearBit :: Int16 -> Int -> Int16 Source
complementBit :: Int16 -> Int -> Int16 Source
testBit :: Int16 -> Int -> Bool Source
bitSizeMaybe :: Int16 -> Maybe Int Source
bitSize :: Int16 -> Int Source
isSigned :: Int16 -> Bool Source
shiftL :: Int16 -> Int -> Int16 Source
unsafeShiftL :: Int16 -> Int -> Int16 Source
shiftR :: Int16 -> Int -> Int16 Source
unsafeShiftR :: Int16 -> Int -> Int16 Source
rotateL :: Int16 -> Int -> Int16 Source
32-bit signed integer type
Instances
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
Methods
toRational :: Int32 -> Rational Source
Methods
finiteBitSize :: Int32 -> Int Source
countLeadingZeros :: Int32 -> Int Source
countTrailingZeros :: Int32 -> Int Source
Methods
(.&.) :: Int32 -> Int32 -> Int32 Source
(.|.) :: Int32 -> Int32 -> Int32 Source
xor :: Int32 -> Int32 -> Int32 Source
complement :: Int32 -> Int32 Source
shift :: Int32 -> Int -> Int32 Source
rotate :: Int32 -> Int -> Int32 Source
setBit :: Int32 -> Int -> Int32 Source
clearBit :: Int32 -> Int -> Int32 Source
complementBit :: Int32 -> Int -> Int32 Source
testBit :: Int32 -> Int -> Bool Source
bitSizeMaybe :: Int32 -> Maybe Int Source
bitSize :: Int32 -> Int Source
isSigned :: Int32 -> Bool Source
shiftL :: Int32 -> Int -> Int32 Source
unsafeShiftL :: Int32 -> Int -> Int32 Source
shiftR :: Int32 -> Int -> Int32 Source
unsafeShiftR :: Int32 -> Int -> Int32 Source
rotateL :: Int32 -> Int -> Int32 Source
64-bit signed integer type
Instances
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
Methods
toRational :: Int64 -> Rational Source
Methods
finiteBitSize :: Int64 -> Int Source
countLeadingZeros :: Int64 -> Int Source
countTrailingZeros :: Int64 -> Int Source
Methods
(.&.) :: Int64 -> Int64 -> Int64 Source
(.|.) :: Int64 -> Int64 -> Int64 Source
xor :: Int64 -> Int64 -> Int64 Source
complement :: Int64 -> Int64 Source
shift :: Int64 -> Int -> Int64 Source
rotate :: Int64 -> Int -> Int64 Source
setBit :: Int64 -> Int -> Int64 Source
clearBit :: Int64 -> Int -> Int64 Source
complementBit :: Int64 -> Int -> Int64 Source
testBit :: Int64 -> Int -> Bool Source
bitSizeMaybe :: Int64 -> Maybe Int Source
bitSize :: Int64 -> Int Source
isSigned :: Int64 -> Bool Source
shiftL :: Int64 -> Int -> Int64 Source
unsafeShiftL :: Int64 -> Int -> Int64 Source
shiftR :: Int64 -> Int -> Int64 Source
unsafeShiftR :: Int64 -> Int -> Int64 Source
rotateL :: Int64 -> Int -> Int64 Source
Notes
- All arithmetic is performed modulo 2^n, where
nis 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
Enuminstances over a bounded type such asInt(see the section of the Haskell report dealing with arithmetic sequences) also hold for theEnuminstances over the variousInttypes 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 == 1in some C implementations.