Copyright | (c) David F. Place 2006 |
---|---|
License | BSD |
Maintainer | robdockins AT fastmail DOT fm |
Stability | stable |
Portability | GHC, Hugs (MPTC and FD) |
Safe Haskell | None |
Language | Haskell2010 |
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.
- data Set a
- empty :: Set a
- singleton :: (Eq a, Enum a) => a -> Set a
- fromSeq :: (Eq a, Enum a, Sequence s) => s a -> Set a
- insert :: (Eq a, Enum a) => a -> Set a -> Set a
- insertSeq :: (Eq a, Enum a, Sequence s) => s a -> Set a -> Set a
- union :: Set a -> Set a -> Set a
- unionSeq :: (Eq a, Enum a, Sequence s) => s (Set a) -> Set a
- delete :: (Eq a, Enum a) => a -> Set a -> Set a
- deleteAll :: (Eq a, Enum a) => a -> Set a -> Set a
- deleteSeq :: (Eq a, Enum a, Sequence s) => s a -> Set a -> Set a
- null :: Set a -> Bool
- size :: Set a -> Int
- member :: (Eq a, Enum a) => a -> Set a -> Bool
- count :: (Eq a, Enum a) => a -> Set a -> Int
- strict :: Set a -> Set a
- deleteMin :: Enum a => Set a -> Set a
- deleteMax :: Enum a => Set a -> Set a
- unsafeInsertMin :: (Ord a, Enum a) => a -> Set a -> Set a
- unsafeInsertMax :: (Ord a, Enum a) => a -> Set a -> Set a
- unsafeFromOrdSeq :: (Ord a, Enum a, Sequence s) => s a -> Set a
- unsafeAppend :: (Ord a, Enum a) => Set a -> Set a -> Set a
- filterLT :: (Ord a, Enum a) => a -> Set a -> Set a
- filterLE :: (Ord a, Enum a) => a -> Set a -> Set a
- filterGT :: (Ord a, Enum a) => a -> Set a -> Set a
- filterGE :: (Ord a, Enum a) => a -> Set a -> Set a
- partitionLT_GE :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)
- partitionLE_GT :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)
- partitionLT_GT :: (Ord a, Enum a) => a -> Set a -> (Set a, Set a)
- intersection :: Set a -> Set a -> Set a
- difference :: Set a -> Set a -> Set a
- symmetricDifference :: Set a -> Set a -> Set a
- properSubset :: Set a -> Set a -> Bool
- subset :: Set a -> Set a -> Bool
- toSeq :: (Eq a, Enum a, Sequence s) => Set a -> s a
- lookup :: (Eq a, Enum a) => a -> Set a -> a
- lookupM :: (Eq a, Enum a, Monad m) => a -> Set a -> m a
- lookupAll :: (Eq a, Enum a, Sequence s) => a -> Set a -> s a
- lookupWithDefault :: (Eq a, Enum a) => a -> a -> Set a -> a
- fold :: (Eq a, Enum a) => (a -> c -> c) -> c -> Set a -> c
- fold' :: (Eq a, Enum a) => (a -> c -> c) -> c -> Set a -> c
- fold1 :: (Eq a, Enum a) => (a -> a -> a) -> Set a -> a
- fold1' :: (Eq a, Enum a) => (a -> a -> a) -> Set a -> a
- filter :: (Eq a, Enum a) => (a -> Bool) -> Set a -> Set a
- partition :: (Eq a, Enum a) => (a -> Bool) -> Set a -> (Set a, Set a)
- strictWith :: (a -> b) -> Set a -> Set a
- minView :: (Enum a, Monad m) => Set a -> m (a, Set a)
- minElem :: Enum a => Set a -> a
- maxView :: (Enum a, Monad m) => Set a -> m (a, Set a)
- maxElem :: Enum a => Set a -> a
- foldr :: (Ord a, Enum a) => (a -> b -> b) -> b -> Set a -> b
- foldr' :: (Ord a, Enum a) => (a -> b -> b) -> b -> Set a -> b
- foldl :: (Ord a, Enum a) => (c -> a -> c) -> c -> Set a -> c
- foldl' :: (Ord a, Enum a) => (c -> a -> c) -> c -> Set a -> c
- foldr1 :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
- foldr1' :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
- foldl1 :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
- foldl1' :: (Ord a, Enum a) => (a -> a -> a) -> Set a -> a
- toOrdSeq :: (Ord a, Enum a, Sequence s) => Set a -> s a
- unsafeMapMonotonic :: Enum a => (a -> a) -> Set a -> Set a
- fromSeqWith :: (Eq a, Enum a, Sequence s) => (a -> a -> a) -> s a -> Set a
- fromOrdSeq :: (Ord a, Enum a, Sequence s) => s a -> Set a
- insertWith :: (Eq a, Enum a) => (a -> a -> a) -> a -> Set a -> Set a
- insertSeqWith :: (Eq a, Enum a, Sequence s) => (a -> a -> a) -> s a -> Set a -> Set a
- unionl :: Set a -> Set a -> Set a
- unionr :: Set a -> Set a -> Set a
- unionWith :: (a -> a -> a) -> Set a -> Set a -> Set a
- unionSeqWith :: (Eq a, Enum a, Sequence s) => (a -> a -> a) -> s (Set a) -> Set a
- intersectionWith :: (a -> a -> a) -> Set a -> Set a -> Set a
- map :: (Enum a, Enum b) => (a -> b) -> Set a -> Set b
- setCoerce :: (Enum a, Enum b) => Set a -> Set b
- complement :: (Eq a, Bounded a, Enum a) => Set a -> Set a
- toBits :: Set a -> Word
- fromBits :: Word -> Set a
- moduleName :: String
Set type
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
.
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) => Semigroup (Set a) Source # | |
(Eq a, Enum a) => Monoid (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) => 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
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.
OrdCollX operations
SetX operations
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
tells whether subset
s2)s1
is a subset of s2
.
Coll operations
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
Set operations
Bonus operations
map :: (Enum a, Enum b) => (a -> b) -> Set a -> Set b Source #
O(n).
is the set obtained by applying map
f sf
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
moduleName :: String Source #