enumset-0.1: Sets of enumeration values represented by machine words
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.EnumBitSet

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

Instances

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

Defined in Data.EnumBitSet

Methods

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

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

(Enum a, Bits w) => Semigroup (T w a) Source # 
Instance details

Defined in Data.EnumBitSet

Methods

(<>) :: T w a -> T w a -> T w a #

sconcat :: NonEmpty (T w a) -> T w a #

stimes :: Integral b => b -> T w a -> T w a #

(Enum a, Bits w) => Monoid (T w a) Source #

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.

Instance details

Defined in Data.EnumBitSet

Methods

mempty :: T w a #

mappend :: T w a -> T w a -> T w a #

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

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

Defined in Data.EnumBitSet

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

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

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

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 -> Int Source #

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 a Source #

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 -> Bool Source #

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

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

disjoint :: (Enum a, Bits w) => T w a -> T w a -> Bool Source #

subset :: (Enum a, Bits w) => T w a -> T w a -> Bool Source #

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

(.&.) :: (Enum a, Bits w) => T w a -> T w a -> T w a infixl 7 Source #

(.-.) :: (Enum a, Bits w) => T w a -> T w a -> T w a infixl 7 Source #

(.|.) :: (Enum a, Bits w) => T w a -> T w a -> T w a infixl 5 Source #

xor :: (Enum a, Bits w) => T w a -> T w a -> T w a Source #

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

get :: (Enum a, Bits w) => a -> T w a -> Bool Source #

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

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

accessor :: (Enum a, Bits w) => a -> T (T w a) Bool Source #

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

could also be named insert like in Set

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

could also be named delete like in Set

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

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