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 |
Signed integer types
Signed integer types
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.
Bounded Int # | Since: 2.1 |
Enum Int # | Since: 2.1 |
Eq Int | |
Integral Int # | Since: 2.0.1 |
Data Int # | Since: 4.0.0.0 |
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 | |
Read Int # | Since: 2.1 |
Real Int # | Since: 2.0.1 |
toRational :: Int -> Rational Source # | |
Show Int # | Since: 2.1 |
Ix Int # | Since: 2.1 |
FiniteBits Int # | Since: 4.6.0.0 |
finiteBitSize :: Int -> Int Source # countLeadingZeros :: Int -> Int Source # countTrailingZeros :: Int -> Int Source # | |
Bits Int # | Since: 2.1 |
(.&.) :: 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 # bitSize :: Int -> 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 # | |
Storable Int # | Since: 2.1 |
PrintfArg Int # | Since: 2.1 |
formatArg :: Int -> FieldFormatter Source # parseFormat :: Int -> ModifierParser Source # | |
Generic1 k (URec k Int) # | |
Functor (URec * Int) # | |
Foldable (URec * Int) # | |
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 # | |
Traversable (URec * Int) # | |
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) # | |
Ord (URec k Int p) # | |
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) # | |
Generic (URec k Int p) # | |
data URec k Int # | Used for marking occurrences of Since: 4.9.0.0 |
type Rep1 k (URec k Int) # | |
type Rep (URec k Int p) # | |
8-bit signed integer type
16-bit signed integer type
32-bit signed integer type
64-bit signed integer type
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 asInt
(see the section of the Haskell report dealing with arithmetic sequences) also hold for theEnum
instances over the variousInt
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.