Copyright | (c) The University of Glasgow 1997-2002 |
---|---|
License | see libraries/base/LICENSE |
Maintainer | ghc-devs@haskell.org |
Stability | internal |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Safe |
Language | Haskell2010 |
GHC.Int
Contents
Synopsis
- data Int = I# Int#
- data Int8 = I8# Int8#
- data Int16 = I16# Int16#
- data Int32 = I32# Int32#
- data Int64 = I64# Int64#
- uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
- uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
- shiftRLInt8# :: Int8# -> Int# -> Int8#
- shiftRLInt16# :: Int16# -> Int# -> Int16#
- shiftRLInt32# :: Int32# -> Int# -> Int32#
- eqInt :: Int -> Int -> Bool
- neInt :: Int -> Int -> Bool
- gtInt :: Int -> Int -> Bool
- geInt :: Int -> Int -> Bool
- ltInt :: Int -> Int -> Bool
- leInt :: Int -> Int -> Bool
- eqInt8 :: Int8 -> Int8 -> Bool
- neInt8 :: Int8 -> Int8 -> Bool
- gtInt8 :: Int8 -> Int8 -> Bool
- geInt8 :: Int8 -> Int8 -> Bool
- ltInt8 :: Int8 -> Int8 -> Bool
- leInt8 :: Int8 -> Int8 -> Bool
- eqInt16 :: Int16 -> Int16 -> Bool
- neInt16 :: Int16 -> Int16 -> Bool
- gtInt16 :: Int16 -> Int16 -> Bool
- geInt16 :: Int16 -> Int16 -> Bool
- ltInt16 :: Int16 -> Int16 -> Bool
- leInt16 :: Int16 -> Int16 -> Bool
- eqInt32 :: Int32 -> Int32 -> Bool
- neInt32 :: Int32 -> Int32 -> Bool
- gtInt32 :: Int32 -> Int32 -> Bool
- geInt32 :: Int32 -> Int32 -> Bool
- ltInt32 :: Int32 -> Int32 -> Bool
- leInt32 :: Int32 -> Int32 -> Bool
- eqInt64 :: Int64 -> Int64 -> Bool
- neInt64 :: Int64 -> Int64 -> Bool
- gtInt64 :: Int64 -> Int64 -> Bool
- geInt64 :: Int64 -> Int64 -> Bool
- ltInt64 :: Int64 -> Int64 -> Bool
- leInt64 :: Int64 -> Int64 -> Bool
Documentation
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
Instance details
Defined in Text.Printf
Instance details
Defined in GHC.Internal.Bits
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 #
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 #
Instance details
Defined in GHC.Internal.Bits
Methods
finiteBitSize :: Int -> Int Source #
countLeadingZeros :: Int -> Int Source #
countTrailingZeros :: Int -> Int Source #
Instance details
Defined in GHC.Internal.Data.Data
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 :: 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 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 #
Instance details
Defined in GHC.Internal.Foreign.Storable
Instance details
Defined in GHC.Internal.Ix
Instance details
Defined in GHC.Internal.Real
Instance details
Defined in GHC.Internal.Generics
Associated Types
Instance details
Defined in GHC.Internal.Generics
Since: base-4.21.0.0
Instance details
Defined in Data.Functor.Classes
Since: base-4.21.0.0
Instance details
Defined in Data.Functor.Classes
Since: base-4.21.0.0
Instance details
Defined in Data.Functor.Classes
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.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 -> Bool Source #
length :: UInt a -> Int Source #
elem :: Eq a => a -> UInt a -> Bool Source #
maximum :: Ord a => UInt a -> a Source #
minimum :: Ord a => UInt a -> a Source #
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Data.Traversable
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Generics
Instance details
Defined in GHC.Internal.Generics
Associated Types
Instance details
Defined in GHC.Internal.Generics
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Generics
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Generics
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Generics
Methods
compare :: URec Int p -> URec Int p -> Ordering Source #
(<) :: URec Int p -> URec Int p -> Bool Source #
(<=) :: URec Int p -> URec Int p -> Bool Source #
(>) :: URec Int p -> URec Int p -> Bool Source #
(>=) :: URec Int p -> URec Int p -> Bool Source #
Used for marking occurrences of Int#
Since: base-4.9.0.0
type Rep1 (URec Int :: k -> Type) Source #Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Generics
Since: base-4.9.0.0
Instance details
Defined in GHC.Internal.Generics
8-bit signed integer type
Instances
Instances details
Instance details
Defined in Text.Printf
Instance details
Defined in GHC.Internal.Int
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 #
bitSize :: Int8 -> 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 #
Instance details
Defined in GHC.Internal.Int
Methods
finiteBitSize :: Int8 -> Int Source #
countLeadingZeros :: Int8 -> Int Source #
countTrailingZeros :: Int8 -> Int Source #
Instance details
Defined in GHC.Internal.Data.Data
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 :: 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 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 #
Instance details
Defined in GHC.Internal.Foreign.Storable
Methods
sizeOf :: Int8 -> Int Source #
alignment :: Int8 -> Int Source #
peekElemOff :: Ptr Int8 -> Int -> IO Int8 Source #
pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () Source #
peekByteOff :: Ptr b -> Int -> IO Int8 Source #
pokeByteOff :: Ptr b -> Int -> Int8 -> IO () Source #
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
16-bit signed integer type
Instances
Instances details
Instance details
Defined in Text.Printf
Methods
formatArg :: Int16 -> FieldFormatter Source #
parseFormat :: Int16 -> ModifierParser Source #
Instance details
Defined in GHC.Internal.Int
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 #
Instance details
Defined in GHC.Internal.Int
Methods
finiteBitSize :: Int16 -> Int Source #
countLeadingZeros :: Int16 -> Int Source #
countTrailingZeros :: Int16 -> Int Source #
Instance details
Defined in GHC.Internal.Data.Data
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 :: 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 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 #
Instance details
Defined in GHC.Internal.Int
Methods
succ :: Int16 -> Int16 Source #
pred :: Int16 -> Int16 Source #
toEnum :: Int -> Int16 Source #
fromEnum :: Int16 -> Int Source #
enumFrom :: Int16 -> [Int16] Source #
enumFromThen :: Int16 -> Int16 -> [Int16] Source #
enumFromTo :: Int16 -> Int16 -> [Int16] Source #
enumFromThenTo :: Int16 -> Int16 -> Int16 -> [Int16] Source #
Instance details
Defined in GHC.Internal.Foreign.Storable
Methods
sizeOf :: Int16 -> Int Source #
alignment :: Int16 -> Int Source #
peekElemOff :: Ptr Int16 -> Int -> IO Int16 Source #
pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () Source #
peekByteOff :: Ptr b -> Int -> IO Int16 Source #
pokeByteOff :: Ptr b -> Int -> Int16 -> IO () Source #
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
32-bit signed integer type
Instances
Instances details
Instance details
Defined in Text.Printf
Methods
formatArg :: Int32 -> FieldFormatter Source #
parseFormat :: Int32 -> ModifierParser Source #
Instance details
Defined in GHC.Internal.Int
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 #
Instance details
Defined in GHC.Internal.Int
Methods
finiteBitSize :: Int32 -> Int Source #
countLeadingZeros :: Int32 -> Int Source #
countTrailingZeros :: Int32 -> Int Source #
Instance details
Defined in GHC.Internal.Data.Data
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 :: 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 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 #
Instance details
Defined in GHC.Internal.Int
Methods
succ :: Int32 -> Int32 Source #
pred :: Int32 -> Int32 Source #
toEnum :: Int -> Int32 Source #
fromEnum :: Int32 -> Int Source #
enumFrom :: Int32 -> [Int32] Source #
enumFromThen :: Int32 -> Int32 -> [Int32] Source #
enumFromTo :: Int32 -> Int32 -> [Int32] Source #
enumFromThenTo :: Int32 -> Int32 -> Int32 -> [Int32] Source #
Instance details
Defined in GHC.Internal.Foreign.Storable
Methods
sizeOf :: Int32 -> Int Source #
alignment :: Int32 -> Int Source #
peekElemOff :: Ptr Int32 -> Int -> IO Int32 Source #
pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () Source #
peekByteOff :: Ptr b -> Int -> IO Int32 Source #
pokeByteOff :: Ptr b -> Int -> Int32 -> IO () Source #
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
64-bit signed integer type
Instances
Instances details
Instance details
Defined in Text.Printf
Methods
formatArg :: Int64 -> FieldFormatter Source #
parseFormat :: Int64 -> ModifierParser Source #
Instance details
Defined in GHC.Internal.Int
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 #
Instance details
Defined in GHC.Internal.Int
Methods
finiteBitSize :: Int64 -> Int Source #
countLeadingZeros :: Int64 -> Int Source #
countTrailingZeros :: Int64 -> Int Source #
Instance details
Defined in GHC.Internal.Data.Data
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 :: 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 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 #
Instance details
Defined in GHC.Internal.Int
Methods
succ :: Int64 -> Int64 Source #
pred :: Int64 -> Int64 Source #
toEnum :: Int -> Int64 Source #
fromEnum :: Int64 -> Int Source #
enumFrom :: Int64 -> [Int64] Source #
enumFromThen :: Int64 -> Int64 -> [Int64] Source #
enumFromTo :: Int64 -> Int64 -> [Int64] Source #
enumFromThenTo :: Int64 -> Int64 -> Int64 -> [Int64] Source #
Instance details
Defined in GHC.Internal.Foreign.Storable
Methods
sizeOf :: Int64 -> Int Source #
alignment :: Int64 -> Int Source #
peekElemOff :: Ptr Int64 -> Int -> IO Int64 Source #
pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () Source #
peekByteOff :: Ptr b -> Int -> IO Int64 Source #
pokeByteOff :: Ptr b -> Int -> Int64 -> IO () Source #
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
Instance details
Defined in GHC.Internal.Int
Equality operators
See GHC.Classes#matching_overloaded_methods_in_rules