Safe Haskell | None |
---|---|
Language | Haskell2010 |
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,BitOffset) w :: BitFields Word16 '[ BitField 5 X (EnumField Word8 A) , BitField 9 Y Word16 , BitField 2 Z (BitSet Word8 B) ] w = BitFields 0x0102
Synopsis
- newtype BitFields b (f :: [*]) = BitFields b
- bitFieldsBits :: BitFields b f -> b
- newtype BitField (n :: Nat) (name :: Symbol) s = BitField s
- extractField :: forall (name :: Symbol) 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
- extractField' :: forall (name :: Symbol) fields b. (KnownNat (Offset name fields), KnownNat (Size name fields), Bits b, Integral b, Field (Output name fields)) => BitFields b fields -> Output name fields
- 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
- 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
- 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
- withField' :: forall (name :: Symbol) 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
- matchFields :: forall l l2 w bs t. (bs ~ BitFields w l, HFoldr' Extract (bs, HList '[]) l (bs, HList l2), HTuple l2, t ~ Tuple l2) => bs -> t
- 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 ~ Tuple lnv) => bs -> t
- class Field f
Documentation
newtype BitFields b (f :: [*]) Source #
Bit fields on a base type b
Instances
(bs ~ BitFields w lt, HFoldr' Extract (bs, HList ([] :: [Type])) lt (bs, HList lt2), Eq (HList lt2), lt2 ~ BitFieldTypes lt) => Eq (BitFields w lt) Source # | |
(bs ~ BitFields w lt, ln ~ Replicate (Length lt) String, HFoldr' Extract (bs, HList ([] :: [Type])) lt (bs, HList (BitFieldTypes lt)), HFoldr' Name (HList ([] :: [Type])) lt (HList ln), HZipList ln (BitFieldTypes lt) lnv, Show (HList lnv)) => Show (BitFields w lt) Source # | Get field names and values in a tuple |
Storable b => Storable (BitFields b f) Source # | |
bitFieldsBits :: BitFields b f -> b Source #
Get backing word
newtype BitField (n :: Nat) (name :: Symbol) s Source #
A field of n bits
BitField s |
extractField :: forall (name :: Symbol) 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 :: Symbol) 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 :: Symbol) 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 ~ Tuple l2) => 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 ~ Tuple lnv) => bs -> t Source #
Get field names and values in a tuple
fromField, toField
Instances
Field Bool Source # | |
Field Int Source # | |
Field Int8 Source # | |
Field Int16 Source # | |
Field Int32 Source # | |
Field Int64 Source # | |
Field Word Source # | |
Field Word8 Source # | |
Field Word16 Source # | |
Field Word32 Source # | |
Field Word64 Source # | |
(Integral b, CEnum a) => Field (EnumField b a) Source # | |
(FiniteBits b, Integral b, BitOffset a) => Field (BitSet b a) Source # | |