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

Data.EnumSet

Description

Similar to Data.Edison.Coll.EnumSet but it allows to choose the underlying type for bit storage. This is really a low-level module for type-safe foreign function interfaces.

The integer representation of the enumeration type is the bit position of the flag within the bitvector.

Synopsis

Documentation

newtype T word index Source

Constructors

Cons 

Fields

decons :: word
 

Instances

Eq word => Eq (T word index) 
(Enum a, Bits w) => Monoid (T w a)

Since this data type is intended for constructing flags, we choose the set union as mappend. For intersection we would also not have a canonical identity element.

(Enum a, Storable w) => Storable (T w a) 

fromEnum :: (Enum a, Bits w) => a -> T w aSource

fromEnums :: (Enum a, Bits w) => [a] -> T w aSource

toEnums :: (Enum a, Bits w) => T w a -> [a]Source

intToEnums :: (Enum a, Integral w) => T w a -> [a]Source

mostSignificantPosition :: (Bits w, Storable w) => T w a -> IntSource

floor of binary logarithm - Intended for getting the position of a single set bit. This in turn is intended for implementing an Enum instance if you only know masks but no bit positions.

singletonByPosition :: Bits w => Int -> T w aSource

set a bit - Intended for implementing an Enum instance if you only know masks but no bit positions.

null :: (Enum a, Bits w) => T w a -> BoolSource

empty :: (Enum a, Bits w) => T w aSource

singleton :: (Enum a, Bits w) => a -> T w aSource

disjoint :: (Enum a, Bits w) => T w a -> T w a -> BoolSource

subset :: (Enum a, Bits w) => T w a -> T w a -> BoolSource

subset a b is True if a is a subset of b.

(.&.), xor, (.|.), (.-.) :: (Enum a, Bits w) => T w a -> T w a -> T w aSource

unions :: (Enum a, Bits w) => [T w a] -> T w aSource

get :: (Enum a, Bits w) => a -> T w a -> BoolSource

could also be named member like in Set or elem as in '[]'

put :: (Enum a, Bits w) => a -> Bool -> T w a -> T w aSource

accessor :: (Enum a, Bits w) => a -> T (T w a) BoolSource

set :: (Enum a, Bits w) => a -> T w a -> T w aSource

could also be named insert like in Set

clear :: (Enum a, Bits w) => a -> T w a -> T w aSource

could also be named delete like in Set

flip :: (Enum a, Bits w) => a -> T w a -> T w aSource

fromBool :: (Enum a, Bits w) => a -> Bool -> T w aSource