Safe Haskell | Safe |
---|---|
Language | Haskell98 |
A bit vector that represents a record in a bit-packed way.
Synopsis
- newtype T word a = Cons {
- decons :: word
- fromMaskedValue :: MaskedValue w a -> T w a
- match :: Bits w => T w a -> MaskedValue w a -> Bool
- class Enum a where
- fromEnum :: Bits w => a -> MaskedValue w a
- compose :: (Enum a, Enum a, Bits w) => [a] -> T w a
- decompose :: (Bounded a, Enum a, Enum a, Bits w) => T w a -> [a]
- newtype Mask w a b = Mask {
- unmask :: w
- maskValue :: Mask w a b -> Value w b -> MaskedValue w a
- newtype Value w b = Value {
- unvalue :: w
- data MaskedValue w a = MaskedValue w w
- get :: (Enum a, Bits w) => Mask w a b -> T w a -> Value w b
- put :: (Enum a, Bits w) => Mask w a b -> Value w b -> T w a -> T w a
- accessor :: (Enum a, Bits w) => Mask w a b -> T (T w a) (Value w b)
Documentation
The basic bit vector data type. It does not provide a lot of functionality, since that could not be done in a safe way.
The type a
identifies the maintained flags.
It may be an empty type
but it may also be an enumeration
of record fields with concrete values.
In the latter case you are encouraged to define an Enum
instance
for this enumeration.
Be aware that it is different from Enum
of Prelude.
Instances
Eq word => Eq (T word a) Source # | |
Storable w => Storable (T w a) Source # | |
fromMaskedValue :: MaskedValue w a -> T w a Source #
compose :: (Enum a, Enum a, Bits w) => [a] -> T w a Source #
Compose a flag set from a list of flags.
However you may prefer to assemble flags
using mconcat
or mappend
on MaskedValue
s.
Mask w a b
describes a field of a T w a
that has type Value w b
.
On the machine level a Mask
value is a vector of bits,
where set bits represent the bits belonging to one record field.
There must be only one mask value for every pair of types (a,b)
.
The type parameter w
is the type of the underlying bit vector.
The type parameter b
is a phantom type,
that is specific for a certain range of bits.
data MaskedValue w a Source #
Combines a mask with a value, that matches this mask.
In MaskedValue mask value
, value
must be a subset of mask
.
MaskedValue w w |
Instances
Eq w => Eq (MaskedValue w a) Source # | |
Defined in Data.FlagSet (==) :: MaskedValue w a -> MaskedValue w a -> Bool # (/=) :: MaskedValue w a -> MaskedValue w a -> Bool # | |
Show w => Show (MaskedValue w a) Source # | |
Defined in Data.FlagSet showsPrec :: Int -> MaskedValue w a -> ShowS # show :: MaskedValue w a -> String # showList :: [MaskedValue w a] -> ShowS # | |
Bits w => Semigroup (MaskedValue w a) Source # | |
Defined in Data.FlagSet (<>) :: MaskedValue w a -> MaskedValue w a -> MaskedValue w a # sconcat :: NonEmpty (MaskedValue w a) -> MaskedValue w a # stimes :: Integral b => b -> MaskedValue w a -> MaskedValue w a # | |
Bits w => Monoid (MaskedValue w a) Source # |
|
Defined in Data.FlagSet mempty :: MaskedValue w a # mappend :: MaskedValue w a -> MaskedValue w a -> MaskedValue w a # mconcat :: [MaskedValue w a] -> MaskedValue w a # |
put :: (Enum a, Bits w) => Mask w a b -> Value w b -> T w a -> T w a Source #
All bits in Value must be contained in the mask.
This condition is not checked by put
.
According to names in Data.Accessor it should be called set
,
but in Data.Bits and thus Data.EnumSet
this is already used in the pair set
/clear
.
put
/get
resembles the pair in Control.Monad.State in the mtl
package.