haskus-binary-0.6.0.0: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.BitField

Description

Bit fields (as in C)

This module allows you to define bit fields over words. For instance, you can have a Word16 split into 3 fields X, Y and Z composed of 5, 9 and 2 bits respectively.

X Y Z w :: Word16 |0 0 0 0 0|0 0 0 0 0 0 0 0 0|0 0|

You define it as follows: @ {--}

w :: BitFields Word16 '[ BitField 5 X Word8 , BitField 9 Y Word16 , BitField 2 Z Word8 ] w = BitFields 0x0102 @

Note that each field has its own associated type (e.g. Word8 for X and Z) that must be large enough to hold the number of bits for the field.

Operations on BitFields expect that the cumulated size of the fields is equal to the whole word size: use a padding field if necessary. Otherwise you can use unsafe versions of the functions: extractField', updateField', withField'.

You can extract and update the value of a field by its name:

x = extractField X w
z = extractField Z w
w' = updateField @Y 0x16 w

Fields can also be BitSet or EnumField: @ {--}

data A = A0 | A1 | A2 | A3 deriving (Enum,CEnum)

data B = B0 | B1 deriving (Enum,CBitSet)

w :: BitFields Word16 '[ BitField 5 X (EnumField Word8 A) , BitField 9 Y Word16 , BitField 2 Z (BitSet Word8 B) ] w = BitFields 0x0102 @

Synopsis

Documentation

newtype BitFields b f Source #

Bit fields on a base type b

Constructors

BitFields b 

Instances

((~) * bs (BitFields w lt), HFoldr' Extract (bs, HList ([] *)) lt (bs, HList lt2), Eq (HList lt2), (~) [*] lt2 (BitFieldTypes lt)) => Eq (BitFields w lt) Source # 

Methods

(==) :: BitFields w lt -> BitFields w lt -> Bool #

(/=) :: BitFields w lt -> BitFields w lt -> Bool #

((~) * bs (BitFields w lt), (~) [*] ln (Replicate (Length lt) String), HFoldr' Extract (bs, HList ([] *)) lt (bs, HList (BitFieldTypes lt)), HFoldr' Name (HList ([] *)) lt (HList ln), HZipList ln (BitFieldTypes lt) lnv, Show (HList lnv)) => Show (BitFields w lt) Source #

Get field names and values in a tuple

Methods

showsPrec :: Int -> BitFields w lt -> ShowS #

show :: BitFields w lt -> String #

showList :: [BitFields w lt] -> ShowS #

Storable b => Storable (BitFields b f) Source # 

Methods

peekIO :: Ptr (BitFields b f) -> IO (BitFields b f) Source #

pokeIO :: Ptr (BitFields b f) -> BitFields b f -> IO () Source #

alignment :: BitFields b f -> Word Source #

sizeOf :: BitFields b f -> Word Source #

bitFieldsBits :: BitFields b f -> b Source #

Get backing word

newtype BitField n name s Source #

A field of n bits

Constructors

BitField s 

Instances

Storable s => Storable (BitField n name s) Source # 

Methods

peekIO :: Ptr (BitField n name s) -> IO (BitField n name s) Source #

pokeIO :: Ptr (BitField n name s) -> BitField n name s -> IO () Source #

alignment :: BitField n name s -> Word Source #

sizeOf :: BitField n name s -> Word Source #

extractField :: forall name fields b. (KnownNat (Offset name fields), KnownNat (Size name fields), WholeSize fields ~ BitSize b, Bits b, Integral b, Field (Output name fields)) => BitFields b fields -> Output name fields Source #

Get the value of a field

extractField' :: forall name fields b. (KnownNat (Offset name fields), KnownNat (Size name fields), Bits b, Integral b, Field (Output name fields)) => BitFields b fields -> Output name fields Source #

Get the value of a field (without checking sizes)

updateField :: forall name fields b. (KnownNat (Offset name fields), KnownNat (Size name fields), WholeSize fields ~ BitSize b, Bits b, Integral b, Field (Output name fields)) => Output name fields -> BitFields b fields -> BitFields b fields Source #

Set the value of a field

updateField' :: forall name fields b. (KnownNat (Offset name fields), KnownNat (Size name fields), Bits b, Integral b, Field (Output name fields)) => Output name fields -> BitFields b fields -> BitFields b fields Source #

Set the value of a field (without checking sizes)

withField :: forall name fields b f. (KnownNat (Offset name fields), KnownNat (Size name fields), WholeSize fields ~ BitSize b, Bits b, Integral b, f ~ Output name fields, Field f) => (f -> f) -> BitFields b fields -> BitFields b fields Source #

Modify the value of a field

withField' :: forall name fields b f. (KnownNat (Offset name fields), KnownNat (Size name fields), Bits b, Integral b, f ~ Output name fields, Field f) => (f -> f) -> BitFields b fields -> BitFields b fields Source #

Modify the value of a field (without checking sizes)

matchFields :: forall l l2 w bs t. (bs ~ BitFields w l, HFoldr' Extract (bs, HList '[]) l (bs, HList l2), HTuple' l2 t) => bs -> t Source #

Get values in a tuple

matchNamedFields :: forall lt lv ln lnv w bs t. (bs ~ BitFields w lt, HFoldr' Extract (bs, HList '[]) lt (bs, HList lv), HFoldr' Name (HList '[]) lt (HList ln), HZipList ln lv lnv, HTuple' lnv t) => bs -> t Source #

Get field names and values in a tuple

class Field f Source #

Minimal complete definition

fromField, toField

Instances

Field Bool Source # 

Methods

fromField :: Integral b => Bool -> b

toField :: Integral b => b -> Bool

Field Int Source # 

Methods

fromField :: Integral b => Int -> b

toField :: Integral b => b -> Int

Field Int8 Source # 

Methods

fromField :: Integral b => Int8 -> b

toField :: Integral b => b -> Int8

Field Int16 Source # 

Methods

fromField :: Integral b => Int16 -> b

toField :: Integral b => b -> Int16

Field Int32 Source # 

Methods

fromField :: Integral b => Int32 -> b

toField :: Integral b => b -> Int32

Field Int64 Source # 

Methods

fromField :: Integral b => Int64 -> b

toField :: Integral b => b -> Int64

Field Word Source # 

Methods

fromField :: Integral b => Word -> b

toField :: Integral b => b -> Word

Field Word8 Source # 

Methods

fromField :: Integral b => Word8 -> b

toField :: Integral b => b -> Word8

Field Word16 Source # 

Methods

fromField :: Integral b => Word16 -> b

toField :: Integral b => b -> Word16

Field Word32 Source # 

Methods

fromField :: Integral b => Word32 -> b

toField :: Integral b => b -> Word32

Field Word64 Source # 

Methods

fromField :: Integral b => Word64 -> b

toField :: Integral b => b -> Word64

CEnum a => Field (EnumField b a) Source # 

Methods

fromField :: Integral b => EnumField b a -> b

toField :: Integral b => b -> EnumField b a

(FiniteBits b, Integral b, CBitSet a) => Field (BitSet b a) Source # 

Methods

fromField :: Integral b => BitSet b a -> b

toField :: Integral b => b -> BitSet b a