bitwise-enum-0.1.0.3: Bitwise operations on bounded enumerations

Safe HaskellNone
LanguageHaskell2010

Data.Enum.Set

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 as E

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

instance E.AsEnumSet Foo

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

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

barHasA :: Bool
barHasA = E.member A bar

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

By default, Words are used as the representation. Other representations may be chosen in the class instance:

{-# LANGUAGE TypeFamilies #-}

import Data.Enum.Set as E
import Data.Word (Word64)

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

instance E.AsEnumSet Foo where
    type EnumSetRep Foo = Word64

For type EnumSet E, EnumSetRep E 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 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 EnumSetRep E. For this reason, it is preferable for E to be a type that derives Eq and Enum, and for EnumSetRep E to have more bits than the number of constructors of E.

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

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

Synopsis

Documentation

class (Enum a, FiniteBits (EnumSetRep a), Num (EnumSetRep a)) => AsEnumSet a Source #

Associated Types

type EnumSetRep a Source #

Set type

Construction

empty :: forall a. AsEnumSet a => EnumSet a Source #

O(1). The empty set.

singleton :: forall a. AsEnumSet a => a -> EnumSet a Source #

O(1). A set of one element.

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

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

Insertion

insert :: forall a. AsEnumSet a => a -> EnumSet a -> EnumSet a Source #

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

Deletion

delete :: forall a. AsEnumSet a => a -> EnumSet a -> EnumSet a Source #

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

Query

member :: forall a. AsEnumSet a => a -> EnumSet a -> Bool Source #

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

notMember :: forall a. AsEnumSet a => a -> EnumSet a -> Bool Source #

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

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

O(1). Is this the empty set?

size :: forall a. AsEnumSet a => EnumSet a -> Int Source #

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

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

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

Combine

union :: forall a. AsEnumSet a => EnumSet a -> EnumSet a -> EnumSet a Source #

O(1). The union of two sets.

difference :: forall a. AsEnumSet a => EnumSet a -> EnumSet a -> EnumSet a Source #

O(1). Difference between two sets.

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

O(1). See difference.

symmetricDifference :: forall a. AsEnumSet a => EnumSet a -> EnumSet a -> EnumSet a Source #

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

intersection :: forall a. AsEnumSet a => EnumSet a -> EnumSet a -> EnumSet a Source #

O(1). The intersection of two sets.

Filter

filter :: forall a. AsEnumSet a => (a -> Bool) -> EnumSet a -> EnumSet a Source #

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

partition :: forall a. AsEnumSet a => (a -> Bool) -> EnumSet a -> (EnumSet a, EnumSet 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 a b. (AsEnumSet a, AsEnumSet b) => (a -> b) -> EnumSet a -> EnumSet 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

Folds

foldl :: forall a b. AsEnumSet a => (b -> a -> b) -> b -> EnumSet a -> b Source #

O(n). Left fold.

foldl' :: forall a b. AsEnumSet a => (b -> a -> b) -> b -> EnumSet a -> b Source #

O(n). Left fold with strict accumulator.

foldr :: forall a b. AsEnumSet a => (a -> b -> b) -> b -> EnumSet a -> b Source #

O(n). Right fold.

foldr' :: forall a b. AsEnumSet a => (a -> b -> b) -> b -> EnumSet a -> b Source #

O(n). Right fold with strict accumulator.

foldl1 :: forall a. AsEnumSet a => (a -> a -> a) -> EnumSet a -> a Source #

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

foldl1' :: forall a. AsEnumSet a => (a -> a -> a) -> EnumSet a -> a Source #

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

foldr1 :: forall a. AsEnumSet a => (a -> a -> a) -> EnumSet a -> a Source #

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

foldr1' :: forall a. AsEnumSet a => (a -> a -> a) -> EnumSet a -> a Source #

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

Special folds

foldMap :: forall m a. (Monoid m, AsEnumSet a) => (a -> m) -> EnumSet a -> m Source #

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

traverse :: forall f a. (Applicative f, AsEnumSet a) => (a -> f a) -> EnumSet a -> f (EnumSet a) Source #

any :: forall a. AsEnumSet a => (a -> Bool) -> EnumSet a -> Bool Source #

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

all :: forall a. AsEnumSet a => (a -> Bool) -> EnumSet a -> Bool Source #

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

Min/Max

minimum :: forall a. AsEnumSet a => EnumSet a -> a Source #

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

maximum :: forall a. AsEnumSet a => EnumSet a -> a Source #

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

deleteMin :: forall a. AsEnumSet a => EnumSet a -> EnumSet a Source #

O(1). Delete the minimal element.

deleteMax :: forall a. AsEnumSet a => EnumSet a -> EnumSet a Source #

O(1). Delete the maximal element.

minView :: forall a. AsEnumSet a => EnumSet a -> Maybe (a, EnumSet 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 a. AsEnumSet a => EnumSet a -> Maybe (a, EnumSet 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 a. AsEnumSet a => EnumSet a -> [a] Source #

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

fromRaw :: forall a. AsEnumSet a => EnumSetRep a -> EnumSet a Source #

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