EdisonCore-1.2.1.3: A library of efficent, purely-functional data structures (Core Implementations)

PortabilityGHC, Hugs (MPTC and FD)
Stabilitystable
Maintainerrobdockins AT fastmail DOT fm

Data.Edison.Coll.EnumSet

Contents

Description

An efficient implementation of sets over small enumerations. The implementation of EnumSet is based on bit-wise operations.

For this implementation to work as expected at type A, there are a number of preconditions on the Eq, Enum and Ord instances.

The Enum A instance must create a bijection between the elements of type A and a finite subset of the naturals [0,1,2,3....]. As a corollary we must have:

 forall x y::A, fromEnum x == fromEnum y <==> x is indistinguishable from y

Also, the number of distinct elements of A must be less than or equal to the number of bits in Word.

The Enum A instance must be consistent with the Eq A instance. That is, we must have:

 forall x y::A, x == y <==> toEnum x == toEnum y

Additionally, for operations that require an Ord A context, we require that toEnum be monotonic with respect to comparison. That is, we must have:

 forall x y::A, x < y <==> toEnum x < toEnum y

Derived Eq, Ord and Enum instances will fulfill these conditions, if the enumerated type has sufficently few constructors.

Synopsis

Set type

data Set a Source

A set of values a implemented as bitwise operations. Useful for members of class Enum with no more elements than there are bits in Word.

Instances

Eq (Set a) 
(Ord a, Enum a) => Ord (Set a) 
(Eq a, Enum a, Read a) => Read (Set a) 
(Eq a, Enum a, Show a) => Show (Set a) 
(Eq a, Enum a, Arbitrary a) => Arbitrary (Set a) 
(Eq a, Enum a) => Monoid (Set a) 
(Eq a, Enum a) => CollX (Set a) a 
(Ord a, Enum a) => OrdCollX (Set a) a 
(Eq a, Enum a) => SetX (Set a) a 
(Ord a, Enum a) => OrdSetX (Set a) a 
(Eq a, Enum a) => Coll (Set a) a 
(Ord a, Enum a) => OrdColl (Set a) a 
(Eq a, Enum a) => Set (Set a) a 
(Ord a, Enum a) => OrdSet (Set a) a 

CollX operations

empty :: Set aSource

O(1). The empty set.

singleton :: (Eq a, Enum a) => a -> Set aSource

O(1). Create a singleton set.

fromSeq :: (Eq a, Enum a, Sequence s) => s a -> Set aSource

insert :: (Eq a, Enum a) => a -> Set a -> Set aSource

O(1). Insert an element in a set. If the set already contains an element equal to the given value, it is replaced with the new value.

insertSeq :: (Eq a, Enum a, Sequence s) => s a -> Set a -> Set aSource

union :: Set a -> Set a -> Set aSource

O(1). The union of two sets.

unionSeq :: (Eq a, Enum a, Sequence s) => s (Set a) -> Set aSource

The union of a list of sets: (unions == foldl union empty).

delete :: (Eq a, Enum a) => a -> Set a -> Set aSource

O(1). Delete an element from a set.

deleteAll :: (Eq a, Enum a) => a -> Set a -> Set aSource

deleteSeq :: (Eq a, Enum a, Sequence s) => s a -> Set a -> Set aSource

null :: Set a -> BoolSource

O(1). Is this the empty set?

size :: Set a -> IntSource

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

member :: (Eq a, Enum a) => a -> Set a -> BoolSource

O(1). Is the element in the set?

count :: (Eq a, Enum a) => a -> Set a -> IntSource

strict :: Set a -> Set aSource

OrdCollX operations

deleteMin :: Enum a => Set a -> Set aSource

O(1). Delete the minimal element.

deleteMax :: Enum a => Set a -> Set aSource

O(1). Delete the maximal element.

unsafeInsertMin :: (Ord a, Enum a) => a -> Set a -> Set aSource

unsafeInsertMax :: (Ord a, Enum a) => a -> Set a -> Set aSource

unsafeFromOrdSeq :: (Ord a, Enum a, Sequence s) => s a -> Set aSource

unsafeAppend :: (Ord a, Enum a) => Set a -> Set a -> Set aSource

filterLT :: (Ord a, Enum a) => a -> Set a -> Set aSource

filterLE :: (Ord a, Enum a) => a -> Set a -> Set aSource

filterGT :: (Ord a, Enum a) => a -> Set a -> Set aSource

filterGE :: (Ord a, Enum a) => a -> Set a -> Set aSource

partitionLT_GE :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)Source

partitionLE_GT :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)Source

partitionLT_GT :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)Source

SetX operations

intersection :: Set a -> Set a -> Set aSource

O(1). The intersection of two sets.

difference :: Set a -> Set a -> Set aSource

O(1). Difference of two sets.

properSubset :: Set a -> Set a -> BoolSource

O(1). Is this a proper subset? (ie. a subset but not equal).

subset :: Set a -> Set a -> BoolSource

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

Coll operations

toSeq :: (Eq a, Enum a, Sequence s) => Set a -> s aSource

lookup :: (Eq a, Enum a) => a -> Set a -> aSource

lookupM :: (Eq a, Enum a, Monad m) => a -> Set a -> m aSource

lookupAll :: (Eq a, Enum a, Sequence s) => a -> Set a -> s aSource

lookupWithDefault :: (Eq a, Enum a) => a -> a -> Set a -> aSource

fold :: (Eq a, Enum a) => (a -> c -> c) -> c -> Set a -> cSource

fold' :: (Eq a, Enum a) => (a -> c -> c) -> c -> Set a -> cSource

fold1 :: (Eq a, Enum a) => (a -> a -> a) -> Set a -> aSource

fold1' :: (Eq a, Enum a) => (a -> a -> a) -> Set a -> aSource

filter :: (Eq a, Enum a) => (a -> Bool) -> Set a -> Set aSource

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

partition :: (Eq a, Enum a) => (a -> Bool) -> Set a -> (Set a, Set a)Source

O(n). Partition the set into two sets, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate. See also split.

strictWith :: (a -> b) -> Set a -> Set aSource

OrdColl operations

minView :: (Enum a, Monad m) => Set a -> m (a, Set a)Source

minElem :: Enum a => Set a -> aSource

O(1). The minimal element of a set.

maxView :: (Enum a, Monad m) => Set a -> m (a, Set a)Source

maxElem :: Enum a => Set a -> aSource

O(1). The maximal element of a set.

foldr :: (Ord a, Enum a) => (a -> b -> b) -> b -> Set a -> bSource

foldr' :: (Ord a, Enum a) => (a -> b -> b) -> b -> Set a -> bSource

foldl :: (Ord a, Enum a) => (c -> a -> c) -> c -> Set a -> cSource

foldl' :: (Ord a, Enum a) => (c -> a -> c) -> c -> Set a -> cSource

foldr1 :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> aSource

foldr1' :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> aSource

foldl1 :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> aSource

foldl1' :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> aSource

toOrdSeq :: (Ord a, Enum a, Sequence s) => Set a -> s aSource

unsafeMapMonotonic :: Enum a => (a -> a) -> Set a -> Set aSource

Set operations

fromSeqWith :: (Eq a, Enum a, Sequence s) => (a -> a -> a) -> s a -> Set aSource

fromOrdSeq :: (Ord a, Enum a, Sequence s) => s a -> Set aSource

insertWith :: (Eq a, Enum a) => (a -> a -> a) -> a -> Set a -> Set aSource

insertSeqWith :: (Eq a, Enum a, Sequence s) => (a -> a -> a) -> s a -> Set a -> Set aSource

unionl :: Set a -> Set a -> Set aSource

unionr :: Set a -> Set a -> Set aSource

unionWith :: (a -> a -> a) -> Set a -> Set a -> Set aSource

unionSeqWith :: (Eq a, Enum a, Sequence s) => (a -> a -> a) -> s (Set a) -> Set aSource

intersectionWith :: (a -> a -> a) -> Set a -> Set a -> Set aSource

Bonus operations

map :: (Enum a, Enum b) => (a -> b) -> Set a -> Set bSource

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

setCoerce :: (Enum a, Enum b) => Set a -> Set bSource

O(1) Changes the type of the elements in the set without changing the representation. Equivalant to map (toEnum . fromEnum), and to (fromBits . toBits). This method is operationally a no-op.

complement :: (Eq a, Bounded a, Enum a) => Set a -> Set aSource

O(1). The complement of a set with its universe set. complement can be used with bounded types for which the universe set will be automatically created.

toBits :: Set a -> WordSource

O(1) Get the underlying bit-encoded representation. This method is operationally a no-op.

fromBits :: Word -> Set aSource

O(1) Create an EnumSet from a bit-encoded representation. This method is operationally a no-op.

Documenation