Copyright | (c) Jannis Overesch 2022-2022 |
---|---|
License | MIT |
Maintainer | overesch.jannis@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Generic and easy to use bitfields. Pack and unpack records into compact representations.
The implementation is generic over the representation and the record, however it is
assumed that the representation is some integral type and that the record has an instance of
Generic
.
Due to possible overlap with the method names, it is recommended to use this module with a qualified import.
import Data.Bitfield data Example = Example { one :: Bool, two :: Bool, three :: Bool, four :: Word8 } deriving (Show, Generic) x :: Bitfield Word16 Example x = pack $ Example True False True 4 >>> x Example { one = True, two = False, three = True, four = 4 } >>> get @"two" x False >>> set @"three" x False Example { one = True, two = False, three = False, four = 4 }
The values in the bitfield will be in whatever order the Generic
instance defines them in.
This is usually the order in which they are defined.
Access with OverloadedRecordDot
is also supported:
{-# LANGUAGE OverloadedRecordDot #-} import Data.Bitfield data Example = Example { one :: Bool, two :: Bool, three :: Bool } deriving (Show, Generic) x :: Bitfield Word8 Example x = pack $ Example True False True >>> x.one True
Bitfield
supports a variety of field types as long as those implement HasFixedBitSize
and AsRep
.
These instances are usually derived via GenericEnum
or ViaIntegral
.
data AEnum = A1 | A2 | A3 deriving stock (Generic, Enum) deriving (HasFixedBitSize, AsRep r) via (GenericEnum AEnum) newtype SmallInt = SmallInt Int deriving (HasFixedBitSize, AsRep r) via (ViaIntegral 5 Int) data Example = Example { a :: AEnum, b :: SmallInt } x :: Bitfield Word8 Example x = pack $ Example A2 (SmallInt 3)
It is also possible to nest Bitfield
s, but they are not unpacked, the representation of the nested field is used directly.
data Nested = Nested { a :: Bool, b :: Bool } data Example = Example { one :: Bitfield Word8 Nested, other :: Bool } -- This bitfield requires at least 9 bits because the field "one" requires 8 bits. x :: Bitfield Word16 Example x = Pack $ Example (pack $ Nested True True) False
Synopsis
- newtype Bitfield (rep :: Type) (a :: Type) = Bitfield rep
- unwrap :: Bitfield rep a -> rep
- get :: forall name x rep a. (Fits rep a, HasField name (Bitfield rep a) x) => Bitfield rep a -> x
- set :: forall name x rep a. (Fits rep a, HasField name (Bitfield rep a) x, GOffset name (Rep a), Bits rep, AsRep rep x) => Bitfield rep a -> x -> Bitfield rep a
- pack :: forall rep a. (Fits rep a, Generic a, Bits rep, GPackBitfield rep (Rep a)) => a -> Bitfield rep a
- unpack :: forall rep a. (Fits rep a, Generic a, GPackBitfield rep (Rep a)) => Bitfield rep a -> a
- class KnownNat (BitSize a) => HasFixedBitSize (a :: Type) where
- class HasFixedBitSize a => AsRep rep a where
- newtype ViaIntegral (sz :: Nat) a = ViaIntegral a
- newtype GenericEnum a = GenericEnum a
Bitfield
newtype Bitfield (rep :: Type) (a :: Type) Source #
A generic Bitfield
Represents type a
with type rep
.
Technically this allows any representation and any type to represent, however all methods
are written with the implicit assumption of a representation with an Integral
and Bits
instance.
The type to represent is also assumed to have a Generic
instance and be a single constructor with named fields.
a
's fields are also required to have an instance of AsRep
and FiniteBits
. This is provided for the most common
types (Int
/Word
(and variants) and Bool
).
Bitfield rep |
Instances
General use
get :: forall name x rep a. (Fits rep a, HasField name (Bitfield rep a) x) => Bitfield rep a -> x Source #
Access a single field
set :: forall name x rep a. (Fits rep a, HasField name (Bitfield rep a) x, GOffset name (Rep a), Bits rep, AsRep rep x) => Bitfield rep a -> x -> Bitfield rep a Source #
Change a single field
pack :: forall rep a. (Fits rep a, Generic a, Bits rep, GPackBitfield rep (Rep a)) => a -> Bitfield rep a Source #
unpack :: forall rep a. (Fits rep a, Generic a, GPackBitfield rep (Rep a)) => Bitfield rep a -> a Source #
Unpack the Bitfield
and return the full datatype
Custom fields
class KnownNat (BitSize a) => HasFixedBitSize (a :: Type) Source #
Types with a fixed bitsize. This could be a type family as well, but having it as a typeclass provides nicer error messages when one forgets to write an instance for it.
Instances
HasFixedBitSize Int16 Source # | |
HasFixedBitSize Int32 Source # | |
HasFixedBitSize Int64 Source # | |
HasFixedBitSize Int8 Source # | |
HasFixedBitSize Word16 Source # | |
HasFixedBitSize Word32 Source # | |
HasFixedBitSize Word64 Source # | |
HasFixedBitSize Word8 Source # | |
HasFixedBitSize Bool Source # | |
HasFixedBitSize Int Source # | |
HasFixedBitSize Word Source # | |
KnownNat (RoundUpLog2 (EnumSz (Rep a))) => HasFixedBitSize (GenericEnum a) Source # | |
Defined in Data.Bitfield.Internal type BitSize (GenericEnum a) :: Nat Source # | |
KnownNat (BitSize r2) => HasFixedBitSize (Bitfield r2 a) Source # | |
KnownNat sz => HasFixedBitSize (ViaIntegral sz n) Source # | |
Defined in Data.Bitfield.Internal type BitSize (ViaIntegral sz n) :: Nat Source # |
class HasFixedBitSize a => AsRep rep a where Source #
Typeclass which converts rep
and a
into each other (at specified offsets).
Instances
newtype ViaIntegral (sz :: Nat) a Source #
Newtype wrapper with an AsRep
instance for Integral
representations and types.
The example below shows how to derive a 5 bit int field via a newtype:
newtype SmallInt = SmallInt Int deriving (HasFixedBitSize, AsRep r) via (ViaIntegral 5 Int)
Instances
newtype GenericEnum a Source #
Deriving via helper for Enum
types. Requires that type to also have an instance of Generic
.
data AEnum = A1 | A2 | A3 deriving stock (Enum, Generic) deriving (HasFixedBitSize, AsRep r) via (GenericEnum AEnum)
Instances
(Generic a, Enum a, Bits rep, Integral rep, KnownNat (RoundUpLog2 (EnumSz (Rep a)))) => AsRep rep (GenericEnum a) Source # | |
Defined in Data.Bitfield.Internal fromRep :: rep -> Int -> GenericEnum a Source # toRep :: rep -> GenericEnum a -> Int -> rep Source # | |
KnownNat (RoundUpLog2 (EnumSz (Rep a))) => HasFixedBitSize (GenericEnum a) Source # | |
Defined in Data.Bitfield.Internal type BitSize (GenericEnum a) :: Nat Source # | |
Eq a => Eq (GenericEnum a) Source # | |
Defined in Data.Bitfield.Internal (==) :: GenericEnum a -> GenericEnum a -> Bool # (/=) :: GenericEnum a -> GenericEnum a -> Bool # | |
type BitSize (GenericEnum a) Source # | |
Defined in Data.Bitfield.Internal |