enumset-0.0.5: Sets of enumeration values represented by machine words

Safe HaskellSafe
LanguageHaskell98

Data.FlagSet

Description

A bit vector that represents a record in a bit-packed way.

Synopsis

Documentation

newtype T word a Source #

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.

Constructors

Cons 

Fields

Instances
Eq word => Eq (T word a) Source # 
Instance details

Defined in Data.FlagSet

Methods

(==) :: T word a -> T word a -> Bool #

(/=) :: T word a -> T word a -> Bool #

Storable w => Storable (T w a) Source # 
Instance details

Defined in Data.FlagSet

Methods

sizeOf :: T w a -> Int #

alignment :: T w a -> Int #

peekElemOff :: Ptr (T w a) -> Int -> IO (T w a) #

pokeElemOff :: Ptr (T w a) -> Int -> T w a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (T w a) #

pokeByteOff :: Ptr b -> Int -> T w a -> IO () #

peek :: Ptr (T w a) -> IO (T w a) #

poke :: Ptr (T w a) -> T w a -> IO () #

match :: Bits w => T w a -> MaskedValue w a -> Bool Source #

class Enum a where Source #

Methods

fromEnum :: Bits w => a -> MaskedValue w a Source #

fromEnum should return an integer that represents the position of the a value in the list of all enumeration items. In contrast to that, fromEnum must return the according bit pattern.

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

decompose :: (Bounded a, Enum a, Enum a, Bits w) => T w a -> [a] Source #

Decompose a flag set into flags. The flags are generated using the Bounded and Enum instance. We do not recommend to use the result list for further processing, since testing of flags is much faster using match. However you may find it useful to show the list.

newtype Mask w a b Source #

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

Constructors

Mask 

Fields

Instances
Eq w => Eq (Mask w a b) Source # 
Instance details

Defined in Data.FlagSet

Methods

(==) :: Mask w a b -> Mask w a b -> Bool #

(/=) :: Mask w a b -> Mask w a b -> Bool #

Show w => Show (Mask w a b) Source # 
Instance details

Defined in Data.FlagSet

Methods

showsPrec :: Int -> Mask w a b -> ShowS #

show :: Mask w a b -> String #

showList :: [Mask w a b] -> ShowS #

maskValue :: Mask w a b -> Value w b -> MaskedValue w a Source #

newtype Value w b Source #

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.

Constructors

Value 

Fields

Instances
Eq w => Eq (Value w b) Source # 
Instance details

Defined in Data.FlagSet

Methods

(==) :: Value w b -> Value w b -> Bool #

(/=) :: Value w b -> Value w b -> Bool #

Show w => Show (Value w b) Source # 
Instance details

Defined in Data.FlagSet

Methods

showsPrec :: Int -> Value w b -> ShowS #

show :: Value w b -> String #

showList :: [Value w b] -> ShowS #

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.

Constructors

MaskedValue w w 
Instances
Eq w => Eq (MaskedValue w a) Source # 
Instance details

Defined in Data.FlagSet

Methods

(==) :: MaskedValue w a -> MaskedValue w a -> Bool #

(/=) :: MaskedValue w a -> MaskedValue w a -> Bool #

Show w => Show (MaskedValue w a) Source # 
Instance details

Defined in Data.FlagSet

Methods

showsPrec :: Int -> MaskedValue w a -> ShowS #

show :: MaskedValue w a -> String #

showList :: [MaskedValue w a] -> ShowS #

Bits w => Semigroup (MaskedValue w a) Source # 
Instance details

Defined in Data.FlagSet

Methods

(<>) :: 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 #

mappend a b means that values stored in b overwrite corresponding values in a.

Instance details

Defined in Data.FlagSet

Methods

mempty :: MaskedValue w a #

mappend :: MaskedValue w a -> MaskedValue w a -> MaskedValue w a #

mconcat :: [MaskedValue w a] -> MaskedValue w a #

get :: (Enum a, Bits w) => Mask w a b -> T w a -> Value w b Source #

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.

accessor :: (Enum a, Bits w) => Mask w a b -> T (T w a) (Value w b) Source #