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

Copyright(c) David F. Place 2006
LicenseBSD
Maintainerrobdockins AT fastmail DOT fm
Stabilitystable
PortabilityGHC, Hugs (MPTC and FD)
Safe HaskellNone
LanguageHaskell2010

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) Source 
(Ord a, Enum a) => Ord (Set a) Source 
(Eq a, Enum a, Read a) => Read (Set a) Source 
(Eq a, Enum a, Show a) => Show (Set a) Source 
(Eq a, Enum a, Arbitrary a) => Arbitrary (Set a) Source 
(Eq a, Enum a, CoArbitrary a) => CoArbitrary (Set a) Source 
(Eq a, Enum a) => Monoid (Set a) Source 
(Eq a, Enum a) => CollX (Set a) a Source 
(Ord a, Enum a) => OrdCollX (Set a) a Source 
(Eq a, Enum a) => SetX (Set a) a Source 
(Ord a, Enum a) => OrdSetX (Set a) a Source 
(Eq a, Enum a) => Coll (Set a) a Source 
(Ord a, Enum a) => OrdColl (Set a) a Source 
(Eq a, Enum a) => Set (Set a) a Source 
(Ord a, Enum a) => OrdSet (Set a) a Source 

CollX operations

empty :: Set a Source

O(1). The empty set.

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

O(1). Create a singleton set.

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

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

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

union :: Set a -> Set a -> Set a Source

O(1). The union of two sets.

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

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

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

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

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

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

null :: Set a -> Bool Source

O(1). Is this the empty set?

size :: Set a -> Int Source

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

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

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

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

strict :: Set a -> Set a Source

OrdCollX operations

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

O(1). Delete the minimal element.

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

O(1). Delete the maximal element.

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

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

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

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

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

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

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

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

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

O(1). The intersection of two sets.

difference :: Set a -> Set a -> Set a Source

O(1). Difference of two sets.

properSubset :: Set a -> Set a -> Bool Source

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

subset :: Set a -> Set a -> Bool Source

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

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

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

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

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

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

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

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

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

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

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

OrdColl operations

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Set operations

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

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

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

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

unionl :: Set a -> Set a -> Set a Source

unionr :: Set a -> Set a -> Set a Source

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

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

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

Bonus operations

map :: (Enum a, Enum b) => (a -> b) -> Set a -> Set 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

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

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

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 -> Word Source

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

fromBits :: Word -> Set a Source

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

Documenation