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
Data Word Source # | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word Source # toConstr :: Word -> Constr Source # dataTypeOf :: Word -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) Source # gmapT :: (forall b. Data b => b -> b) -> Word -> Word Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word Source # | |
Storable Word Source # | Since: base-2.1 |
Defined in Foreign.Storable sizeOf :: Word -> Int Source # alignment :: Word -> Int Source # peekElemOff :: Ptr Word -> Int -> IO Word Source # pokeElemOff :: Ptr Word -> Int -> Word -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Word Source # pokeByteOff :: Ptr b -> Int -> Word -> IO () Source # | |
Bits Word Source # | Since: base-2.1 |
Defined in GHC.Bits (.&.) :: Word -> Word -> Word Source # (.|.) :: Word -> Word -> Word Source # xor :: Word -> Word -> Word Source # complement :: Word -> Word Source # shift :: Word -> Int -> Word Source # rotate :: Word -> Int -> Word Source # setBit :: Word -> Int -> Word Source # clearBit :: Word -> Int -> Word Source # complementBit :: Word -> Int -> Word Source # testBit :: Word -> Int -> Bool Source # bitSizeMaybe :: Word -> Maybe Int Source # bitSize :: Word -> Int Source # isSigned :: Word -> Bool Source # shiftL :: Word -> Int -> Word Source # unsafeShiftL :: Word -> Int -> Word Source # shiftR :: Word -> Int -> Word Source # unsafeShiftR :: Word -> Int -> Word Source # rotateL :: Word -> Int -> Word Source # | |
FiniteBits Word Source # | Since: base-4.6.0.0 |
Bounded Word Source # | Since: base-2.1 |
Enum Word Source # | Since: base-2.1 |
Ix Word Source # | Since: base-4.6.0.0 |
Num Word Source # | Since: base-2.1 |
Read Word Source # | Since: base-4.5.0.0 |
Integral Word Source # | Since: base-2.1 |
Real Word Source # | Since: base-2.1 |
Show Word Source # | Since: base-2.1 |
PrintfArg Word Source # | Since: base-2.1 |
Defined in Text.Printf formatArg :: Word -> FieldFormatter Source # parseFormat :: Word -> ModifierParser Source # | |
Eq Word | |
Ord Word | |
Generic1 (URec Word :: k -> Type) Source # | |
Foldable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UWord m -> m Source # foldMap :: Monoid m => (a -> m) -> UWord a -> m Source # foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source # foldr :: (a -> b -> b) -> b -> UWord a -> b Source # foldr' :: (a -> b -> b) -> b -> UWord a -> b Source # foldl :: (b -> a -> b) -> b -> UWord a -> b Source # foldl' :: (b -> a -> b) -> b -> UWord a -> b Source # foldr1 :: (a -> a -> a) -> UWord a -> a Source # foldl1 :: (a -> a -> a) -> UWord a -> a Source # toList :: UWord a -> [a] Source # null :: UWord a -> Bool Source # length :: UWord a -> Int Source # elem :: Eq a => a -> UWord a -> Bool Source # maximum :: Ord a => UWord a -> a Source # minimum :: Ord a => UWord a -> a Source # | |
Traversable (UWord :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Word :: Type -> Type) Source # | Since: base-4.9.0.0 |
Generic (URec Word p) Source # | |
Show (URec Word p) Source # | Since: base-4.9.0.0 |
Eq (URec Word p) Source # | Since: base-4.9.0.0 |
Ord (URec Word p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics compare :: URec Word p -> URec Word p -> Ordering Source # (<) :: URec Word p -> URec Word p -> Bool Source # (<=) :: URec Word p -> URec Word p -> Bool Source # (>) :: URec Word p -> URec Word p -> Bool Source # (>=) :: URec Word p -> URec Word p -> Bool Source # | |
data URec Word (p :: k) Source # | Used for marking occurrences of Since: base-4.9.0.0 |
type Rep1 (URec Word :: k -> Type) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Rep (URec Word p) Source # | Since: base-4.9.0.0 |
Defined in GHC.Generics |
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
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.