bitfield-0.0.0.0: Generic and easy to use haskell bitfields
Copyright(c) Jannis Overesch 2022-2022
LicenseMIT
Maintaineroveresch.jannis@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bitfield

Description

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 Bitfields, 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

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).

Constructors

Bitfield rep 

Instances

Instances details
(HasField name a x, GOffset name (Rep a), AsRep rep x) => HasField (name :: Symbol) (Bitfield rep a) x Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

getField :: Bitfield rep a -> x #

AsRep r1 r2 => AsRep r1 (Bitfield r2 a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r1 -> Int -> Bitfield r2 a Source #

toRep :: r1 -> Bitfield r2 a -> Int -> r1 Source #

Storable rep => Storable (Bitfield rep a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

sizeOf :: Bitfield rep a -> Int #

alignment :: Bitfield rep a -> Int #

peekElemOff :: Ptr (Bitfield rep a) -> Int -> IO (Bitfield rep a) #

pokeElemOff :: Ptr (Bitfield rep a) -> Int -> Bitfield rep a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Bitfield rep a) #

pokeByteOff :: Ptr b -> Int -> Bitfield rep a -> IO () #

peek :: Ptr (Bitfield rep a) -> IO (Bitfield rep a) #

poke :: Ptr (Bitfield rep a) -> Bitfield rep a -> IO () #

(Fits rep a, Generic a, GPackBitfield rep (Rep a), Show a) => Show (Bitfield rep a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

showsPrec :: Int -> Bitfield rep a -> ShowS #

show :: Bitfield rep a -> String #

showList :: [Bitfield rep a] -> ShowS #

KnownNat (BitSize r2) => HasFixedBitSize (Bitfield r2 a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize (Bitfield r2 a) :: Nat Source #

Eq rep => Eq (Bitfield rep a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

(==) :: Bitfield rep a -> Bitfield rep a -> Bool #

(/=) :: Bitfield rep a -> Bitfield rep a -> Bool #

type BitSize (Bitfield r2 a) Source # 
Instance details

Defined in Data.Bitfield.Internal

type BitSize (Bitfield r2 a) = BitSize r2

unwrap :: Bitfield rep a -> rep Source #

Access the underlying representation of the Bitfield

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 #

Pack a datatype into a bitfield

Beware that updates should be done with set, as pack will recreate the entire Bitfield from scratch. The following will most likely *not* be optimised: pack $ (unpack bitfield) { example = True }

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.

Associated Types

type BitSize a :: Nat Source #

Instances

Instances details
HasFixedBitSize Int16 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Int16 :: Nat Source #

HasFixedBitSize Int32 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Int32 :: Nat Source #

HasFixedBitSize Int64 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Int64 :: Nat Source #

HasFixedBitSize Int8 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Int8 :: Nat Source #

HasFixedBitSize Word16 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Word16 :: Nat Source #

HasFixedBitSize Word32 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Word32 :: Nat Source #

HasFixedBitSize Word64 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Word64 :: Nat Source #

HasFixedBitSize Word8 Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Word8 :: Nat Source #

HasFixedBitSize Bool Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Bool :: Nat Source #

HasFixedBitSize Int Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Int :: Nat Source #

HasFixedBitSize Word Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize Word :: Nat Source #

KnownNat (RoundUpLog2 (EnumSz (Rep a))) => HasFixedBitSize (GenericEnum a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize (GenericEnum a) :: Nat Source #

KnownNat (BitSize r2) => HasFixedBitSize (Bitfield r2 a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize (Bitfield r2 a) :: Nat Source #

KnownNat sz => HasFixedBitSize (ViaIntegral sz n) Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

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).

Methods

fromRep :: rep -> Int -> a Source #

toRep :: rep -> a -> Int -> rep Source #

Instances

Instances details
Bits a => AsRep a Bool Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: a -> Int -> Bool Source #

toRep :: a -> Bool -> Int -> a Source #

(Bits r, Integral r) => AsRep r Int16 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Int16 Source #

toRep :: r -> Int16 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Int32 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Int32 Source #

toRep :: r -> Int32 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Int64 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Int64 Source #

toRep :: r -> Int64 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Int8 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Int8 Source #

toRep :: r -> Int8 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Word16 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Word16 Source #

toRep :: r -> Word16 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Word32 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Word32 Source #

toRep :: r -> Word32 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Word64 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Word64 Source #

toRep :: r -> Word64 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Word8 Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Word8 Source #

toRep :: r -> Word8 -> Int -> r Source #

(Bits r, Integral r) => AsRep r Int Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Int Source #

toRep :: r -> Int -> Int -> r Source #

(Bits r, Integral r) => AsRep r Word Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r -> Int -> Word Source #

toRep :: r -> Word -> Int -> r Source #

(Generic a, Enum a, Bits rep, Integral rep, KnownNat (RoundUpLog2 (EnumSz (Rep a)))) => AsRep rep (GenericEnum a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: rep -> Int -> GenericEnum a Source #

toRep :: rep -> GenericEnum a -> Int -> rep Source #

(Bits a, Integral a, Integral n, KnownNat sz) => AsRep a (ViaIntegral sz n) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: a -> Int -> ViaIntegral sz n Source #

toRep :: a -> ViaIntegral sz n -> Int -> a Source #

AsRep r1 r2 => AsRep r1 (Bitfield r2 a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: r1 -> Int -> Bitfield r2 a Source #

toRep :: r1 -> Bitfield r2 a -> Int -> r1 Source #

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)

Constructors

ViaIntegral a 

Instances

Instances details
(Bits a, Integral a, Integral n, KnownNat sz) => AsRep a (ViaIntegral sz n) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: a -> Int -> ViaIntegral sz n Source #

toRep :: a -> ViaIntegral sz n -> Int -> a Source #

Bits a => Bits (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

(.&.) :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

(.|.) :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

xor :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

complement :: ViaIntegral sz a -> ViaIntegral sz a #

shift :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

rotate :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

zeroBits :: ViaIntegral sz a #

bit :: Int -> ViaIntegral sz a #

setBit :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

clearBit :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

complementBit :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

testBit :: ViaIntegral sz a -> Int -> Bool #

bitSizeMaybe :: ViaIntegral sz a -> Maybe Int #

bitSize :: ViaIntegral sz a -> Int #

isSigned :: ViaIntegral sz a -> Bool #

shiftL :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

unsafeShiftL :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

shiftR :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

unsafeShiftR :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

rotateL :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

rotateR :: ViaIntegral sz a -> Int -> ViaIntegral sz a #

popCount :: ViaIntegral sz a -> Int #

Enum a => Enum (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

succ :: ViaIntegral sz a -> ViaIntegral sz a #

pred :: ViaIntegral sz a -> ViaIntegral sz a #

toEnum :: Int -> ViaIntegral sz a #

fromEnum :: ViaIntegral sz a -> Int #

enumFrom :: ViaIntegral sz a -> [ViaIntegral sz a] #

enumFromThen :: ViaIntegral sz a -> ViaIntegral sz a -> [ViaIntegral sz a] #

enumFromTo :: ViaIntegral sz a -> ViaIntegral sz a -> [ViaIntegral sz a] #

enumFromThenTo :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a -> [ViaIntegral sz a] #

Num a => Num (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

(+) :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

(-) :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

(*) :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

negate :: ViaIntegral sz a -> ViaIntegral sz a #

abs :: ViaIntegral sz a -> ViaIntegral sz a #

signum :: ViaIntegral sz a -> ViaIntegral sz a #

fromInteger :: Integer -> ViaIntegral sz a #

Integral a => Integral (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

quot :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

rem :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

div :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

mod :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

quotRem :: ViaIntegral sz a -> ViaIntegral sz a -> (ViaIntegral sz a, ViaIntegral sz a) #

divMod :: ViaIntegral sz a -> ViaIntegral sz a -> (ViaIntegral sz a, ViaIntegral sz a) #

toInteger :: ViaIntegral sz a -> Integer #

Real a => Real (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

toRational :: ViaIntegral sz a -> Rational #

KnownNat sz => HasFixedBitSize (ViaIntegral sz n) Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize (ViaIntegral sz n) :: Nat Source #

Eq a => Eq (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

(==) :: ViaIntegral sz a -> ViaIntegral sz a -> Bool #

(/=) :: ViaIntegral sz a -> ViaIntegral sz a -> Bool #

Ord a => Ord (ViaIntegral sz a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

compare :: ViaIntegral sz a -> ViaIntegral sz a -> Ordering #

(<) :: ViaIntegral sz a -> ViaIntegral sz a -> Bool #

(<=) :: ViaIntegral sz a -> ViaIntegral sz a -> Bool #

(>) :: ViaIntegral sz a -> ViaIntegral sz a -> Bool #

(>=) :: ViaIntegral sz a -> ViaIntegral sz a -> Bool #

max :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

min :: ViaIntegral sz a -> ViaIntegral sz a -> ViaIntegral sz a #

type BitSize (ViaIntegral sz n) Source # 
Instance details

Defined in Data.Bitfield.Internal

type BitSize (ViaIntegral sz n) = sz

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)

Constructors

GenericEnum a 

Instances

Instances details
(Generic a, Enum a, Bits rep, Integral rep, KnownNat (RoundUpLog2 (EnumSz (Rep a)))) => AsRep rep (GenericEnum a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Methods

fromRep :: rep -> Int -> GenericEnum a Source #

toRep :: rep -> GenericEnum a -> Int -> rep Source #

KnownNat (RoundUpLog2 (EnumSz (Rep a))) => HasFixedBitSize (GenericEnum a) Source # 
Instance details

Defined in Data.Bitfield.Internal

Associated Types

type BitSize (GenericEnum a) :: Nat Source #

Eq a => Eq (GenericEnum a) Source # 
Instance details

Defined in Data.Bitfield.Internal

type BitSize (GenericEnum a) Source # 
Instance details

Defined in Data.Bitfield.Internal