ivory-0.1.0.3: Safe embedded C programming.

Safe HaskellNone
LanguageHaskell2010

Ivory.Language.BitData.BitData

Synopsis

Documentation

class (ANat (BitSize (BitType a)), IvoryRep (BitDataRep a), BitType a ~ Bits (BitSize (BitType a))) => BitData a where Source

Class of bit data types defined by the "bitdata" quasiquoter.

Associated Types

type BitType a :: * Source

Return the base "(Bits n)" type as defined in the "bitdata" quasiquoter.

Methods

toBits :: a -> BitType a Source

Convert a bit data type to its raw bit value. This is always well defined and should be exported.

fromBits :: BitType a -> a Source

Convert a raw bit value to a bit data type. All values may not be well defined with respect to the original set of bit data constructors. For now, we allow these "junk" values to be created, but that may change in the future (perhaps by implementing a checked, Ivory run-time conversion).

Instances

(ANat n, IvoryRep (BitRep n)) => BitData (Bits n) Source

Identity instance of BitData for the base "Bits n" type.

(ANat n, ANat (ArraySize n a), BitData a, IvoryRep (BitRep (ArraySize n a))) => BitData (BitArray n a) Source 

type BitDataRep a = BitRep (BitSize (BitType a)) Source

The Ivory type that stores the actual value for a bit data type.

This is a shorthand to simplify the constraints on functions that take arguments of the BitData class.

fromRep :: BitData a => BitDataRep a -> a Source

Convert a raw Ivory type to a bit data type. If the input value is too large, the out of range upper bits will be masked off.

toRep :: BitData a => a -> BitDataRep a Source

Convert a bit data value to its Ivory representation.

data BitDataField a b Source

Description of a bit field defined by the "bitdata" quasiquoter. Each field defined in the record syntax will generate a top-level definition of BitDataField.

This constructor must remain unexported so that only fields checked by the quasiquoter are created.

Instances

(#>) :: BitDataField a b -> BitDataField b c -> BitDataField a c Source

Bit data field composition. (like Control.Category.>>>)

getBitDataField :: (BitData a, BitData b, BitCast (BitDataRep a) (BitDataRep b)) => BitDataField a b -> a -> b Source

Extract a field from a bit data definition. Returns the value as the type defined on the right hand side of the field definition in the "bitdata" quasiquoter.

(#.) :: (BitData a, BitData b, BitCast (BitDataRep a) (BitDataRep b)) => a -> BitDataField a b -> b Source

Infix operator to read a bit data field. (like Data.Lens.^.)

setBitDataField :: (BitData a, BitData b, SafeCast (BitDataRep b) (BitDataRep a)) => BitDataField a b -> a -> b -> a Source

Set a field from a bit data definition.

setBitDataBit :: BitData a => BitDataField a Bit -> a -> a Source

Set a single-bit field in a bit data value.

clearBitDataBit :: BitData a => BitDataField a Bit -> a -> a Source

Clear a single-bit field in a bit data value.

bitToBool :: Bit -> IBool Source

Convert a single bit bitdata to an Ivory boolean.

boolToBit :: IBool -> Bit Source

Convert an Ivory boolean to a single bit.