base-4.9.0.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Word

Contents

Description

Unsigned integer types.

Synopsis

Unsigned integral types

data Word :: TYPE Lifted Source

A Word is an unsigned integral type, with the same size as Int.

Instances

Bounded Word 
Enum Word 
Eq Word 

Methods

(==) :: Word -> Word -> Bool Source

(/=) :: Word -> Word -> Bool Source

Integral Word 
Data Word 

Methods

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Word) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

Num Word 
Ord Word 
Read Word 
Real Word 
Show Word 
Ix Word 
FiniteBits Word 
Bits Word 
Storable Word 
PrintfArg Word 
Eq (URec Word p) 

Methods

(==) :: URec Word p -> URec Word p -> Bool Source

(/=) :: URec Word p -> URec Word p -> Bool Source

Ord (URec Word p) 
Show (URec Word p) 
Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * Source

Methods

from :: URec Word p -> Rep (URec Word p) x Source

to :: Rep (URec Word p) x -> URec Word p Source

data URec Word = UWord {}

Used for marking occurrences of Word#

type Rep (URec Word p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just Symbol "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) UWord)) 

data Word8 Source

8-bit unsigned integer type

Instances

Bounded Word8 
Enum Word8 
Eq Word8 

Methods

(==) :: Word8 -> Word8 -> Bool Source

(/=) :: Word8 -> Word8 -> Bool Source

Integral Word8 
Data Word8 

Methods

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Word8) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

Num Word8 
Ord Word8 
Read Word8 
Real Word8 
Show Word8 
Ix Word8 
FiniteBits Word8 
Bits Word8 
Storable Word8 
PrintfArg Word8 

data Word16 Source

16-bit unsigned integer type

Instances

Bounded Word16 
Enum Word16 
Eq Word16 
Integral Word16 
Data Word16 

Methods

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Word16) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

Num Word16 
Ord Word16 
Read Word16 
Real Word16 
Show Word16 
Ix Word16 
FiniteBits Word16 
Bits Word16 
Storable Word16 
PrintfArg Word16 

data Word32 Source

32-bit unsigned integer type

Instances

Bounded Word32 
Enum Word32 
Eq Word32 
Integral Word32 
Data Word32 

Methods

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Word32) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

Num Word32 
Ord Word32 
Read Word32 
Real Word32 
Show Word32 
Ix Word32 
FiniteBits Word32 
Bits Word32 
Storable Word32 
PrintfArg Word32 

data Word64 Source

64-bit unsigned integer type

Instances

Bounded Word64 
Enum Word64 
Eq Word64 
Integral Word64 
Data Word64 

Methods

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Word64) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

Num Word64 
Ord Word64 
Read Word64 
Real Word64 
Show Word64 
Ix Word64 
FiniteBits Word64 
Bits Word64 
Storable Word64 
PrintfArg Word64 

byte swapping

byteSwap16 :: Word16 -> Word16 Source

Swap bytes in Word16.

Since: 4.7.0.0

byteSwap32 :: Word32 -> Word32 Source

Reverse order of bytes in Word32.

Since: 4.7.0.0

byteSwap64 :: Word64 -> Word64 Source

Reverse order of bytes in Word64.

Since: 4.7.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 as Int (see the section of the Haskell report dealing with arithmetic sequences) also hold for the Enum instances over the various Word 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.