bitwise-enum-1.0.0.1: Bitwise operations on bounded enumerations

Safe HaskellNone
LanguageHaskell2010

Data.Enum.Set.Base

Contents

Description

Efficient sets over bounded enumerations, using bitwise operations based on containers and EdisonCore. In many cases, EnumSets may be optimised away entirely by constant folding at compile-time. For example, in the following code:

import Data.Enum.Set.Base as E

data Foo = A | B | C | D | E | F | G | H deriving (Bounded, Enum, Eq, Ord, Show)

addFoos :: E.EnumSet Word Foo -> E.EnumSet Word Foo
addFoos = E.delete A . E.insert B

bar :: E.EnumSet Word Foo
bar = addFoos $ E.fromFoldable [A, C, E]

barHasB :: Bool
barHasB = E.member A bar

With -O or -O2, bar will compile to GHC.Types.W# 22## and barHasA will compile to GHC.Types.False.

For type EnumSet W E, W should be a Word-like type that implements Bits and Num, and E should be a type that implements Eq and Enum equivalently and is a bijection to Int. EnumSet W E can only store a value of E if the result of applying fromEnum to the value is positive and less than the number of bits in W. For this reason, it is preferable for E to be a type that derives Eq and Enum, and for W to have more bits than the number of constructors of E.

For type EnumSet W E, if the highest fromEnum value of E is 29, W should be Word, because it always has at least 30 bits. Otherwise, options include Word32, Word64, and the wide-word package's Data.WideWord.Word128. Foreign types may also be used.

Data.Enum.Set provides an alternate type alias that moves the underlying representation to an associated type token, so that e.g. EnumSet Word64 MyEnum is replaced by EnumSet MyEnum, and reexports this module with adjusted type signatures.

Note: complexity calculations assume that W implements Bits with constant-time functions, as is the case with Word etc. If this is not the case, the complexity of those operations should be added to the complexity of EnumSet functions.

Synopsis

Set type

data EnumSet word a Source #

A set of values a with representation word, implemented as bitwise operations.

Instances
Prim word => Vector Vector (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (EnumSet word a) -> m (Vector (EnumSet word a)) #

basicUnsafeThaw :: PrimMonad m => Vector (EnumSet word a) -> m (Mutable Vector (PrimState m) (EnumSet word a)) #

basicLength :: Vector (EnumSet word a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (EnumSet word a) -> Vector (EnumSet word a) #

basicUnsafeIndexM :: Monad m => Vector (EnumSet word a) -> Int -> m (EnumSet word a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (EnumSet word a) -> Vector (EnumSet word a) -> m () #

elemseq :: Vector (EnumSet word a) -> EnumSet word a -> b -> b #

Prim word => MVector MVector (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

basicLength :: MVector s (EnumSet word a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (EnumSet word a) -> MVector s (EnumSet word a) #

basicOverlaps :: MVector s (EnumSet word a) -> MVector s (EnumSet word a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (EnumSet word a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> EnumSet word a -> m (MVector (PrimState m) (EnumSet word a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> Int -> m (EnumSet word a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> Int -> EnumSet word a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> EnumSet word a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> MVector (PrimState m) (EnumSet word a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> MVector (PrimState m) (EnumSet word a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (EnumSet word a) -> Int -> m (MVector (PrimState m) (EnumSet word a)) #

(FiniteBits w, Num w, Enum a) => IsList (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Associated Types

type Item (EnumSet w a) :: Type #

Methods

fromList :: [Item (EnumSet w a)] -> EnumSet w a #

fromListN :: Int -> [Item (EnumSet w a)] -> EnumSet w a #

toList :: EnumSet w a -> [Item (EnumSet w a)] #

Eq word => Eq (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

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

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

(Typeable a, Typeable k, Data word) => Data (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumSet word a -> c (EnumSet word a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EnumSet word a) #

toConstr :: EnumSet word a -> Constr #

dataTypeOf :: EnumSet word a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EnumSet word a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EnumSet word a)) #

gmapT :: (forall b. Data b => b -> b) -> EnumSet word a -> EnumSet word a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumSet word a -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnumSet word a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumSet word a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumSet word a -> m (EnumSet word a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumSet word a -> m (EnumSet word a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumSet word a -> m (EnumSet word a) #

Ord word => Ord (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

compare :: EnumSet word a -> EnumSet word a -> Ordering #

(<) :: EnumSet word a -> EnumSet word a -> Bool #

(<=) :: EnumSet word a -> EnumSet word a -> Bool #

(>) :: EnumSet word a -> EnumSet word a -> Bool #

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

max :: EnumSet word a -> EnumSet word a -> EnumSet word a #

min :: EnumSet word a -> EnumSet word a -> EnumSet word a #

(Bits w, Num w, Enum x, Read x) => Read (EnumSet w x) Source # 
Instance details

Defined in Data.Enum.Set.Base

(FiniteBits w, Num w, Enum x, Show x) => Show (EnumSet w x) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

showsPrec :: Int -> EnumSet w x -> ShowS #

show :: EnumSet w x -> String #

showList :: [EnumSet w x] -> ShowS #

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

Defined in Data.Enum.Set.Base

Methods

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

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

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

Bits w => Monoid (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

mempty :: EnumSet w a #

mappend :: EnumSet w a -> EnumSet w a -> EnumSet w a #

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

(FiniteBits w, Num w, Enum a, ToJSON a) => ToJSON (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Storable word => Storable (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

sizeOf :: EnumSet word a -> Int #

alignment :: EnumSet word a -> Int #

peekElemOff :: Ptr (EnumSet word a) -> Int -> IO (EnumSet word a) #

pokeElemOff :: Ptr (EnumSet word a) -> Int -> EnumSet word a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (EnumSet word a) #

pokeByteOff :: Ptr b -> Int -> EnumSet word a -> IO () #

peek :: Ptr (EnumSet word a) -> IO (EnumSet word a) #

poke :: Ptr (EnumSet word a) -> EnumSet word a -> IO () #

NFData word => NFData (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

rnf :: EnumSet word a -> () #

(FiniteBits w, Num w, Eq a, Enum a) => SetContainer (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Associated Types

type ContainerKey (EnumSet w a) :: Type #

Methods

member :: ContainerKey (EnumSet w a) -> EnumSet w a -> Bool #

notMember :: ContainerKey (EnumSet w a) -> EnumSet w a -> Bool #

union :: EnumSet w a -> EnumSet w a -> EnumSet w a #

unions :: (MonoFoldable mono, Element mono ~ EnumSet w a) => mono -> EnumSet w a #

difference :: EnumSet w a -> EnumSet w a -> EnumSet w a #

intersection :: EnumSet w a -> EnumSet w a -> EnumSet w a #

keys :: EnumSet w a -> [ContainerKey (EnumSet w a)] #

(FiniteBits w, Num w, Eq a, Enum a) => IsSet (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

insertSet :: Element (EnumSet w a) -> EnumSet w a -> EnumSet w a #

deleteSet :: Element (EnumSet w a) -> EnumSet w a -> EnumSet w a #

singletonSet :: Element (EnumSet w a) -> EnumSet w a #

setFromList :: [Element (EnumSet w a)] -> EnumSet w a #

setToList :: EnumSet w a -> [Element (EnumSet w a)] #

filterSet :: (Element (EnumSet w a) -> Bool) -> EnumSet w a -> EnumSet w a #

(FiniteBits w, Num w, Enum a) => MonoFunctor (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

omap :: (Element (EnumSet w a) -> Element (EnumSet w a)) -> EnumSet w a -> EnumSet w a #

(FiniteBits w, Num w, Enum a) => MonoFoldable (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

ofoldMap :: Monoid m => (Element (EnumSet w a) -> m) -> EnumSet w a -> m #

ofoldr :: (Element (EnumSet w a) -> b -> b) -> b -> EnumSet w a -> b #

ofoldl' :: (a0 -> Element (EnumSet w a) -> a0) -> a0 -> EnumSet w a -> a0 #

otoList :: EnumSet w a -> [Element (EnumSet w a)] #

oall :: (Element (EnumSet w a) -> Bool) -> EnumSet w a -> Bool #

oany :: (Element (EnumSet w a) -> Bool) -> EnumSet w a -> Bool #

onull :: EnumSet w a -> Bool #

olength :: EnumSet w a -> Int #

olength64 :: EnumSet w a -> Int64 #

ocompareLength :: Integral i => EnumSet w a -> i -> Ordering #

otraverse_ :: Applicative f => (Element (EnumSet w a) -> f b) -> EnumSet w a -> f () #

ofor_ :: Applicative f => EnumSet w a -> (Element (EnumSet w a) -> f b) -> f () #

omapM_ :: Applicative m => (Element (EnumSet w a) -> m ()) -> EnumSet w a -> m () #

oforM_ :: Applicative m => EnumSet w a -> (Element (EnumSet w a) -> m ()) -> m () #

ofoldlM :: Monad m => (a0 -> Element (EnumSet w a) -> m a0) -> a0 -> EnumSet w a -> m a0 #

ofoldMap1Ex :: Semigroup m => (Element (EnumSet w a) -> m) -> EnumSet w a -> m #

ofoldr1Ex :: (Element (EnumSet w a) -> Element (EnumSet w a) -> Element (EnumSet w a)) -> EnumSet w a -> Element (EnumSet w a) #

ofoldl1Ex' :: (Element (EnumSet w a) -> Element (EnumSet w a) -> Element (EnumSet w a)) -> EnumSet w a -> Element (EnumSet w a) #

headEx :: EnumSet w a -> Element (EnumSet w a) #

lastEx :: EnumSet w a -> Element (EnumSet w a) #

unsafeHead :: EnumSet w a -> Element (EnumSet w a) #

unsafeLast :: EnumSet w a -> Element (EnumSet w a) #

maximumByEx :: (Element (EnumSet w a) -> Element (EnumSet w a) -> Ordering) -> EnumSet w a -> Element (EnumSet w a) #

minimumByEx :: (Element (EnumSet w a) -> Element (EnumSet w a) -> Ordering) -> EnumSet w a -> Element (EnumSet w a) #

oelem :: Element (EnumSet w a) -> EnumSet w a -> Bool #

onotElem :: Element (EnumSet w a) -> EnumSet w a -> Bool #

(FiniteBits w, Num w, Enum a) => MonoTraversable (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

otraverse :: Applicative f => (Element (EnumSet w a) -> f (Element (EnumSet w a))) -> EnumSet w a -> f (EnumSet w a) #

omapM :: Applicative m => (Element (EnumSet w a) -> m (Element (EnumSet w a))) -> EnumSet w a -> m (EnumSet w a) #

(Bits w, Enum a) => MonoPointed (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

opoint :: Element (EnumSet w a) -> EnumSet w a #

(FiniteBits w, Num w, Enum a) => GrowingAppend (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Prim word => Prim (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

Methods

sizeOf# :: EnumSet word a -> Int# #

alignment# :: EnumSet word a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> EnumSet word a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, EnumSet word a#) #

writeByteArray# :: MutableByteArray# s -> Int# -> EnumSet word a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> EnumSet word a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> EnumSet word a #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, EnumSet word a#) #

writeOffAddr# :: Addr# -> Int# -> EnumSet word a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> EnumSet word a -> State# s -> State# s #

Prim word => Unbox (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

newtype MVector s (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

newtype MVector s (EnumSet word a) = MV_EnumSet (MVector s (EnumSet word a))
type Item (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

type Item (EnumSet w a) = a
type ContainerKey (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

type ContainerKey (EnumSet w a) = a
type Element (EnumSet w a) Source # 
Instance details

Defined in Data.Enum.Set.Base

type Element (EnumSet w a) = a
newtype Vector (EnumSet word a) Source # 
Instance details

Defined in Data.Enum.Set.Base

newtype Vector (EnumSet word a) = V_EnumSet (Vector (EnumSet word a))

Construction

empty :: forall w a. Bits w => EnumSet w a Source #

O(1). The empty set.

singleton :: forall w a. (Bits w, Enum a) => a -> EnumSet w a Source #

O(1). A set of one element.

fromFoldable :: forall f w a. (Foldable f, Bits w, Enum a) => f a -> EnumSet w a Source #

O(n). Create a set from a finite foldable data structure.

Insertion

insert :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> EnumSet w a Source #

O(1). Add a value to the set.

Deletion

delete :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> EnumSet w a Source #

O(1). Delete a value in the set.

Query

member :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool Source #

O(1). Is the value a member of the set?

notMember :: forall w a. (Bits w, Enum a) => a -> EnumSet w a -> Bool Source #

O(1). Is the value not in the set?

null :: forall w a. Bits w => EnumSet w a -> Bool Source #

O(1). Is this the empty set?

size :: forall w a. (Bits w, Num w) => EnumSet w a -> Int Source #

O(1). The number of elements in the set.

isSubsetOf :: forall w a. Bits w => EnumSet w a -> EnumSet w a -> Bool Source #

O(1). Is this a subset? (s1 isSubsetOf s2) tells whether s1 is a subset of s2.

Combine

union :: forall w a. Bits w => EnumSet w a -> EnumSet w a -> EnumSet w a Source #

O(1). The union of two sets.

difference :: forall w a. Bits w => EnumSet w a -> EnumSet w a -> EnumSet w a Source #

O(1). Difference between two sets.

(\\) :: forall w a. Bits w => EnumSet w a -> EnumSet w a -> EnumSet w a infixl 9 Source #

O(1). See difference.

symmetricDifference :: forall w a. Bits w => EnumSet w a -> EnumSet w a -> EnumSet w a Source #

O(1). Elements which are in either set, but not both.

intersection :: forall w a. Bits w => EnumSet w a -> EnumSet w a -> EnumSet w a Source #

O(1). The intersection of two sets.

Filter

filter :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> Bool) -> EnumSet w a -> EnumSet w a Source #

O(n). Filter all elements that satisfy some predicate.

partition :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> Bool) -> EnumSet w a -> (EnumSet w a, EnumSet w a) Source #

O(n). Partition the set according to some predicate. The first set contains all elements that satisfy the predicate, the second all elements that fail the predicate.

Map

map :: forall w a b. (FiniteBits w, Num w, Enum a, Enum b) => (a -> b) -> EnumSet w a -> EnumSet w b Source #

O(n). map f s is the set obtained by applying f to each element of s.

It's worth noting that the size of the result may be smaller if, for some (x,y), x /= y && f x == f y.

map' :: forall v w a b. (FiniteBits v, FiniteBits w, Num v, Num w, Enum a, Enum b) => (a -> b) -> EnumSet v a -> EnumSet w b Source #

O(n). Apply map while converting the underlying representation of the set to some other representation.

Folds

foldl :: forall w a b. (FiniteBits w, Num w, Enum a) => (b -> a -> b) -> b -> EnumSet w a -> b Source #

O(n). Left fold.

foldl' :: forall w a b. (FiniteBits w, Num w, Enum a) => (b -> a -> b) -> b -> EnumSet w a -> b Source #

O(n). Left fold with strict accumulator.

foldr :: forall w a b. (FiniteBits w, Num w, Enum a) => (a -> b -> b) -> b -> EnumSet w a -> b Source #

O(n). Right fold.

foldr' :: forall w a b. (FiniteBits w, Num w, Enum a) => (a -> b -> b) -> b -> EnumSet w a -> b Source #

O(n). Right fold with strict accumulator.

foldl1 :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> a -> a) -> EnumSet w a -> a Source #

O(n). Left fold on non-empty sets.

foldl1' :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> a -> a) -> EnumSet w a -> a Source #

O(n). Left fold on non-empty sets with strict accumulator.

foldr1 :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> a -> a) -> EnumSet w a -> a Source #

O(n). Right fold on non-empty sets.

foldr1' :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> a -> a) -> EnumSet w a -> a Source #

O(n). Right fold on non-empty sets with strict accumulator.

Special folds

foldMap :: forall m w a. (Monoid m, FiniteBits w, Num w, Enum a) => (a -> m) -> EnumSet w a -> m Source #

O(n). Map each element of the structure to a monoid, and combine the results.

traverse :: forall f w a. (Applicative f, FiniteBits w, Num w, Enum a) => (a -> f a) -> EnumSet w a -> f (EnumSet w a) Source #

any :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> Bool) -> EnumSet w a -> Bool Source #

O(n). Check if any element satisfies some predicate.

all :: forall w a. (FiniteBits w, Num w, Enum a) => (a -> Bool) -> EnumSet w a -> Bool Source #

O(n). Check if all elements satisfy some predicate.

Min/Max

minimum :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> a Source #

O(1). The minimal element of a non-empty set.

maximum :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> a Source #

O(1). The maximal element of a non-empty set.

deleteMin :: forall w a. (FiniteBits w, Num w) => EnumSet w a -> EnumSet w a Source #

O(1). Delete the minimal element.

deleteMax :: forall w a. (FiniteBits w, Num w) => EnumSet w a -> EnumSet w a Source #

O(1). Delete the maximal element.

minView :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> Maybe (a, EnumSet w a) Source #

O(1). Retrieves the minimal element of the set, and the set stripped of that element, or Nothing if passed an empty set.

maxView :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> Maybe (a, EnumSet w a) Source #

O(1). Retrieves the maximal element of the set, and the set stripped of that element, or Nothing if passed an empty set.

Conversion

toList :: forall w a. (FiniteBits w, Num w, Enum a) => EnumSet w a -> [a] Source #

O(n). Convert the set to a list of values.

fromRaw :: forall w a. w -> EnumSet w a Source #

O(1). Convert a representation into an EnumSet. Intended for use with foreign types.