Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | stable |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Unsigned integer types.
Synopsis
- data Word
- data Word8
- data Word16
- data Word32
- data Word64
- byteSwap16 :: Word16 -> Word16
- byteSwap32 :: Word32 -> Word32
- byteSwap64 :: Word64 -> Word64
- bitReverse8 :: Word8 -> Word8
- bitReverse16 :: Word16 -> Word16
- bitReverse32 :: Word32 -> Word32
- bitReverse64 :: Word64 -> Word64
Unsigned integral types
Instances
8-bit unsigned integer type
Instances
PrintfArg Word8 Source # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word8 -> FieldFormatter Source # parseFormat :: Word8 -> ModifierParser Source # | |
Bits Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word (.&.) :: Word8 -> Word8 -> Word8 Source # (.|.) :: Word8 -> Word8 -> Word8 Source # xor :: Word8 -> Word8 -> Word8 Source # complement :: Word8 -> Word8 Source # shift :: Word8 -> Int -> Word8 Source # rotate :: Word8 -> Int -> Word8 Source # setBit :: Word8 -> Int -> Word8 Source # clearBit :: Word8 -> Int -> Word8 Source # complementBit :: Word8 -> Int -> Word8 Source # testBit :: Word8 -> Int -> Bool Source # bitSizeMaybe :: Word8 -> Maybe Int Source # bitSize :: Word8 -> Int Source # isSigned :: Word8 -> Bool Source # shiftL :: Word8 -> Int -> Word8 Source # unsafeShiftL :: Word8 -> Int -> Word8 Source # shiftR :: Word8 -> Int -> Word8 Source # unsafeShiftR :: Word8 -> Int -> Word8 Source # rotateL :: Word8 -> Int -> Word8 Source # | |
FiniteBits Word8 Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Word finiteBitSize :: Word8 -> Int Source # countLeadingZeros :: Word8 -> Int Source # countTrailingZeros :: Word8 -> Int Source # | |
Data Word8 Source # | Since: base-4.0.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 Source # toConstr :: Word8 -> Constr Source # dataTypeOf :: Word8 -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word8) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) Source # gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 Source # | |
Bounded Word8 Source # | Since: base-2.1 |
Enum Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word succ :: Word8 -> Word8 Source # pred :: Word8 -> Word8 Source # toEnum :: Int -> Word8 Source # fromEnum :: Word8 -> Int Source # enumFrom :: Word8 -> [Word8] Source # enumFromThen :: Word8 -> Word8 -> [Word8] Source # enumFromTo :: Word8 -> Word8 -> [Word8] Source # enumFromThenTo :: Word8 -> Word8 -> Word8 -> [Word8] Source # | |
Storable Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Foreign.Storable sizeOf :: Word8 -> Int Source # alignment :: Word8 -> Int Source # peekElemOff :: Ptr Word8 -> Int -> IO Word8 Source # pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word8 Source # pokeByteOff :: Ptr b -> Int -> Word8 -> IO () Source # | |
Ix Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Num Word8 Source # | Since: base-2.1 |
Read Word8 Source # | Since: base-2.1 |
Integral Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Real Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word toRational :: Word8 -> Rational Source # | |
Show Word8 Source # | Since: base-2.1 |
Eq Word8 Source # | Since: base-2.1 |
Ord Word8 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Lift Word8 Source # | |
16-bit unsigned integer type
Instances
PrintfArg Word16 Source # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word16 -> FieldFormatter Source # parseFormat :: Word16 -> ModifierParser Source # | |
Bits Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word (.&.) :: Word16 -> Word16 -> Word16 Source # (.|.) :: Word16 -> Word16 -> Word16 Source # xor :: Word16 -> Word16 -> Word16 Source # complement :: Word16 -> Word16 Source # shift :: Word16 -> Int -> Word16 Source # rotate :: Word16 -> Int -> Word16 Source # setBit :: Word16 -> Int -> Word16 Source # clearBit :: Word16 -> Int -> Word16 Source # complementBit :: Word16 -> Int -> Word16 Source # testBit :: Word16 -> Int -> Bool Source # bitSizeMaybe :: Word16 -> Maybe Int Source # bitSize :: Word16 -> Int Source # isSigned :: Word16 -> Bool Source # shiftL :: Word16 -> Int -> Word16 Source # unsafeShiftL :: Word16 -> Int -> Word16 Source # shiftR :: Word16 -> Int -> Word16 Source # unsafeShiftR :: Word16 -> Int -> Word16 Source # rotateL :: Word16 -> Int -> Word16 Source # | |
FiniteBits Word16 Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Word finiteBitSize :: Word16 -> Int Source # countLeadingZeros :: Word16 -> Int Source # countTrailingZeros :: Word16 -> Int Source # | |
Data Word16 Source # | Since: base-4.0.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word16 -> c Word16 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word16 Source # toConstr :: Word16 -> Constr Source # dataTypeOf :: Word16 -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word16) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word16) Source # gmapT :: (forall b. Data b => b -> b) -> Word16 -> Word16 Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word16 -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word16 -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 Source # | |
Bounded Word16 Source # | Since: base-2.1 |
Enum Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word succ :: Word16 -> Word16 Source # pred :: Word16 -> Word16 Source # toEnum :: Int -> Word16 Source # fromEnum :: Word16 -> Int Source # enumFrom :: Word16 -> [Word16] Source # enumFromThen :: Word16 -> Word16 -> [Word16] Source # enumFromTo :: Word16 -> Word16 -> [Word16] Source # enumFromThenTo :: Word16 -> Word16 -> Word16 -> [Word16] Source # | |
Storable Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Foreign.Storable sizeOf :: Word16 -> Int Source # alignment :: Word16 -> Int Source # peekElemOff :: Ptr Word16 -> Int -> IO Word16 Source # pokeElemOff :: Ptr Word16 -> Int -> Word16 -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word16 Source # pokeByteOff :: Ptr b -> Int -> Word16 -> IO () Source # | |
Ix Word16 Source # | Since: base-2.1 |
Num Word16 Source # | Since: base-2.1 |
Read Word16 Source # | Since: base-2.1 |
Integral Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Real Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word toRational :: Word16 -> Rational Source # | |
Show Word16 Source # | Since: base-2.1 |
Eq Word16 Source # | Since: base-2.1 |
Ord Word16 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Lift Word16 Source # | |
32-bit unsigned integer type
Instances
PrintfArg Word32 Source # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word32 -> FieldFormatter Source # parseFormat :: Word32 -> ModifierParser Source # | |
Bits Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word (.&.) :: Word32 -> Word32 -> Word32 Source # (.|.) :: Word32 -> Word32 -> Word32 Source # xor :: Word32 -> Word32 -> Word32 Source # complement :: Word32 -> Word32 Source # shift :: Word32 -> Int -> Word32 Source # rotate :: Word32 -> Int -> Word32 Source # setBit :: Word32 -> Int -> Word32 Source # clearBit :: Word32 -> Int -> Word32 Source # complementBit :: Word32 -> Int -> Word32 Source # testBit :: Word32 -> Int -> Bool Source # bitSizeMaybe :: Word32 -> Maybe Int Source # bitSize :: Word32 -> Int Source # isSigned :: Word32 -> Bool Source # shiftL :: Word32 -> Int -> Word32 Source # unsafeShiftL :: Word32 -> Int -> Word32 Source # shiftR :: Word32 -> Int -> Word32 Source # unsafeShiftR :: Word32 -> Int -> Word32 Source # rotateL :: Word32 -> Int -> Word32 Source # | |
FiniteBits Word32 Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Word finiteBitSize :: Word32 -> Int Source # countLeadingZeros :: Word32 -> Int Source # countTrailingZeros :: Word32 -> Int Source # | |
Data Word32 Source # | Since: base-4.0.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 Source # toConstr :: Word32 -> Constr Source # dataTypeOf :: Word32 -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word32) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) Source # gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 Source # | |
Bounded Word32 Source # | Since: base-2.1 |
Enum Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word succ :: Word32 -> Word32 Source # pred :: Word32 -> Word32 Source # toEnum :: Int -> Word32 Source # fromEnum :: Word32 -> Int Source # enumFrom :: Word32 -> [Word32] Source # enumFromThen :: Word32 -> Word32 -> [Word32] Source # enumFromTo :: Word32 -> Word32 -> [Word32] Source # enumFromThenTo :: Word32 -> Word32 -> Word32 -> [Word32] Source # | |
Storable Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Foreign.Storable sizeOf :: Word32 -> Int Source # alignment :: Word32 -> Int Source # peekElemOff :: Ptr Word32 -> Int -> IO Word32 Source # pokeElemOff :: Ptr Word32 -> Int -> Word32 -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word32 Source # pokeByteOff :: Ptr b -> Int -> Word32 -> IO () Source # | |
Ix Word32 Source # | Since: base-2.1 |
Num Word32 Source # | Since: base-2.1 |
Read Word32 Source # | Since: base-2.1 |
Integral Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Real Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word toRational :: Word32 -> Rational Source # | |
Show Word32 Source # | Since: base-2.1 |
Eq Word32 Source # | Since: base-2.1 |
Ord Word32 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Lift Word32 Source # | |
64-bit unsigned integer type
Instances
PrintfArg Word64 Source # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word64 -> FieldFormatter Source # parseFormat :: Word64 -> ModifierParser Source # | |
Bits Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word (.&.) :: Word64 -> Word64 -> Word64 Source # (.|.) :: Word64 -> Word64 -> Word64 Source # xor :: Word64 -> Word64 -> Word64 Source # complement :: Word64 -> Word64 Source # shift :: Word64 -> Int -> Word64 Source # rotate :: Word64 -> Int -> Word64 Source # setBit :: Word64 -> Int -> Word64 Source # clearBit :: Word64 -> Int -> Word64 Source # complementBit :: Word64 -> Int -> Word64 Source # testBit :: Word64 -> Int -> Bool Source # bitSizeMaybe :: Word64 -> Maybe Int Source # bitSize :: Word64 -> Int Source # isSigned :: Word64 -> Bool Source # shiftL :: Word64 -> Int -> Word64 Source # unsafeShiftL :: Word64 -> Int -> Word64 Source # shiftR :: Word64 -> Int -> Word64 Source # unsafeShiftR :: Word64 -> Int -> Word64 Source # rotateL :: Word64 -> Int -> Word64 Source # | |
FiniteBits Word64 Source # | Since: base-4.6.0.0 |
Defined in GHC.Internal.Word finiteBitSize :: Word64 -> Int Source # countLeadingZeros :: Word64 -> Int Source # countTrailingZeros :: Word64 -> Int Source # | |
Data Word64 Source # | Since: base-4.0.0.0 |
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word64 -> c Word64 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word64 Source # toConstr :: Word64 -> Constr Source # dataTypeOf :: Word64 -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word64) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word64) Source # gmapT :: (forall b. Data b => b -> b) -> Word64 -> Word64 Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word64 -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word64 -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word64 -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word64 -> m Word64 Source # | |
Bounded Word64 Source # | Since: base-2.1 |
Enum Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word succ :: Word64 -> Word64 Source # pred :: Word64 -> Word64 Source # toEnum :: Int -> Word64 Source # fromEnum :: Word64 -> Int Source # enumFrom :: Word64 -> [Word64] Source # enumFromThen :: Word64 -> Word64 -> [Word64] Source # enumFromTo :: Word64 -> Word64 -> [Word64] Source # enumFromThenTo :: Word64 -> Word64 -> Word64 -> [Word64] Source # | |
Storable Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Foreign.Storable sizeOf :: Word64 -> Int Source # alignment :: Word64 -> Int Source # peekElemOff :: Ptr Word64 -> Int -> IO Word64 Source # pokeElemOff :: Ptr Word64 -> Int -> Word64 -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word64 Source # pokeByteOff :: Ptr b -> Int -> Word64 -> IO () Source # | |
Ix Word64 Source # | Since: base-2.1 |
Num Word64 Source # | Since: base-2.1 |
Read Word64 Source # | Since: base-2.1 |
Integral Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Real Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word toRational :: Word64 -> Rational Source # | |
Show Word64 Source # | Since: base-2.1 |
Eq Word64 Source # | Since: base-2.1 |
Ord Word64 Source # | Since: base-2.1 |
Defined in GHC.Internal.Word | |
Lift Word64 Source # | |
byte swapping
bit reversal
bitReverse16 :: Word16 -> Word16 Source #
Reverse the order of the bits in a Word16
.
Since: base-4.14.0.0
bitReverse32 :: Word32 -> Word32 Source #
Reverse the order of the bits in a Word32
.
Since: base-4.14.0.0
bitReverse64 :: Word64 -> Word64 Source #
Reverse the order of the bits in a Word64
.
Since: base-4.14.0.0
Notes
- All arithmetic is performed modulo 2^n, where n is the number of
bits in the type. One non-obvious consequence of this is that
negate
should not raise an error on negative arguments. - 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 to and from integer types preserves representation, not sign. - An unbounded size unsigned integer type is available with
Natural
. - 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 variousWord
types defined here. - Right and left shifts by amounts greater than or equal to the width
of the type result in a zero result. 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.