containers-0.5.1.0: Assorted concrete container types

Portabilityportable
Stabilityprovisional
Maintainerlibraries@haskell.org
Safe HaskellSafe

Data.Set

Contents

Description

An efficient implementation of sets.

These modules are intended to be imported qualified, to avoid name clashes with Prelude functions, e.g.

  import Data.Set (Set)
  import qualified Data.Set as Set

The implementation of Set is based on size balanced binary trees (or trees of bounded balance) as described by:

  • Stephen Adams, "Efficient sets: a balancing act", Journal of Functional Programming 3(4):553-562, October 1993, http://www.swiss.ai.mit.edu/~adams/BB/.
  • J. Nievergelt and E.M. Reingold, "Binary search trees of bounded balance", SIAM journal of computing 2(1), March 1973.

Note that the implementation is left-biased -- the elements of a first argument are always preferred to the second, for example in union or insert. Of course, left-biasing can only be observed when equality is an equivalence relation instead of structural equality.

Synopsis

Strictness properties

This module satisfies the following strictness property:

  • Key arguments are evaluated to WHNF

Here are some examples that illustrate the property:

 delete undefined s  ==  undefined

Set type

data Set a Source

A set of values a.

Instances

Typeable1 Set 
Foldable Set 
Eq a => Eq (Set a) 
(Typeable (Set a), Data a, Ord a) => Data (Set a) 
(Eq (Set a), Ord a) => Ord (Set a) 
(Read a, Ord a) => Read (Set a) 
Show a => Show (Set a) 
Ord a => Monoid (Set a) 
NFData a => NFData (Set a) 

Operators

(\\) :: Ord a => Set a -> Set a -> Set aSource

O(n+m). See difference.

Query

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 :: Ord a => a -> Set a -> BoolSource

O(log n). Is the element in the set?

notMember :: Ord a => a -> Set a -> BoolSource

O(log n). Is the element not in the set?

lookupLT :: Ord a => a -> Set a -> Maybe aSource

O(log n). Find largest element smaller than the given one.

 lookupLT 3 (fromList [3, 5]) == Nothing
 lookupLT 5 (fromList [3, 5]) == Just 3

lookupGT :: Ord a => a -> Set a -> Maybe aSource

O(log n). Find smallest element greater than the given one.

 lookupGT 4 (fromList [3, 5]) == Just 5
 lookupGT 5 (fromList [3, 5]) == Nothing

lookupLE :: Ord a => a -> Set a -> Maybe aSource

O(log n). Find largest element smaller or equal to the given one.

 lookupLE 2 (fromList [3, 5]) == Nothing
 lookupLE 4 (fromList [3, 5]) == Just 3
 lookupLE 5 (fromList [3, 5]) == Just 5

lookupGE :: Ord a => a -> Set a -> Maybe aSource

O(log n). Find smallest element greater or equal to the given one.

 lookupGE 3 (fromList [3, 5]) == Just 3
 lookupGE 4 (fromList [3, 5]) == Just 5
 lookupGE 6 (fromList [3, 5]) == Nothing

isSubsetOf :: Ord a => Set a -> Set a -> BoolSource

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

isProperSubsetOf :: Ord a => Set a -> Set a -> BoolSource

O(n+m). Is this a proper subset? (ie. a subset but not equal).

Construction

empty :: Set aSource

O(1). The empty set.

singleton :: a -> Set aSource

O(1). Create a singleton set.

insert :: Ord a => a -> Set a -> Set aSource

O(log n). 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.

delete :: Ord a => a -> Set a -> Set aSource

O(log n). Delete an element from a set.

Combine

union :: Ord a => Set a -> Set a -> Set aSource

O(n+m). The union of two sets, preferring the first set when equal elements are encountered. The implementation uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset union smallset).

unions :: Ord a => [Set a] -> Set aSource

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

difference :: Ord a => Set a -> Set a -> Set aSource

O(n+m). Difference of two sets. The implementation uses an efficient hedge algorithm comparable with hedge-union.

intersection :: Ord a => Set a -> Set a -> Set aSource

O(n+m). The intersection of two sets. Elements of the result come from the first set, so for example

 import qualified Data.Set as S
 data AB = A | B deriving Show
 instance Ord AB where compare _ _ = EQ
 instance Eq AB where _ == _ = True
 main = print (S.singleton A `S.intersection` S.singleton B,
               S.singleton B `S.intersection` S.singleton A)

prints (fromList [A],fromList [B]).

Filter

filter :: (a -> Bool) -> Set a -> Set aSource

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

partition :: (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.

split :: Ord a => a -> Set a -> (Set a, Set a)Source

O(log n). The expression (split x set) is a pair (set1,set2) where set1 comprises the elements of set less than x and set2 comprises the elements of set greater than x.

splitMember :: Ord a => a -> Set a -> (Set a, Bool, Set a)Source

O(log n). Performs a split but also returns whether the pivot element was found in the original set.

Map

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

O(n*log 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

mapMonotonic :: (a -> b) -> Set a -> Set bSource

O(n). The

mapMonotonic f s == map f s, but works only when f is monotonic. The precondition is not checked. Semi-formally, we have:

 and [x < y ==> f x < f y | x <- ls, y <- ls]
                     ==> mapMonotonic f s == map f s
     where ls = toList s

Folds

foldr :: (a -> b -> b) -> b -> Set a -> bSource

O(n). Fold the elements in the set using the given right-associative binary operator, such that foldr f z == foldr f z . toAscList.

For example,

 toAscList set = foldr (:) [] set

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

O(n). Fold the elements in the set using the given left-associative binary operator, such that foldl f z == foldl f z . toAscList.

For example,

 toDescList set = foldl (flip (:)) [] set

Strict folds

foldr' :: (a -> b -> b) -> b -> Set a -> bSource

O(n). A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldl' :: (a -> b -> a) -> a -> Set b -> aSource

O(n). A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Legacy folds

fold :: (a -> b -> b) -> b -> Set a -> bSource

O(n). Fold the elements in the set using the given right-associative binary operator. This function is an equivalent of foldr and is present for compatibility only.

Please note that fold will be deprecated in the future and removed.

Min/Max

findMin :: Set a -> aSource

O(log n). The minimal element of a set.

findMax :: Set a -> aSource

O(log n). The maximal element of a set.

deleteMin :: Set a -> Set aSource

O(log n). Delete the minimal element.

deleteMax :: Set a -> Set aSource

O(log n). Delete the maximal element.

deleteFindMin :: Set a -> (a, Set a)Source

O(log n). Delete and find the minimal element.

 deleteFindMin set = (findMin set, deleteMin set)

deleteFindMax :: Set a -> (a, Set a)Source

O(log n). Delete and find the maximal element.

 deleteFindMax set = (findMax set, deleteMax set)

maxView :: Set a -> Maybe (a, Set a)Source

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

minView :: Set a -> Maybe (a, Set a)Source

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

Conversion

List

elems :: Set a -> [a]Source

O(n). An alias of toAscList. The elements of a set in ascending order. Subject to list fusion.

toList :: Set a -> [a]Source

O(n). Convert the set to a list of elements. Subject to list fusion.

fromList :: Ord a => [a] -> Set aSource

O(n*log n). Create a set from a list of elements.

If the elemens are ordered, linear-time implementation is used, with the performance equal to fromDistinctAscList.

Ordered list

toAscList :: Set a -> [a]Source

O(n). Convert the set to an ascending list of elements. Subject to list fusion.

toDescList :: Set a -> [a]Source

O(n). Convert the set to a descending list of elements. Subject to list fusion.

fromAscList :: Eq a => [a] -> Set aSource

O(n). Build a set from an ascending list in linear time. The precondition (input list is ascending) is not checked.

fromDistinctAscList :: [a] -> Set aSource

O(n). Build a set from an ascending list of distinct elements in linear time. The precondition (input list is strictly ascending) is not checked.

Debugging

showTree :: Show a => Set a -> StringSource

O(n). Show the tree that implements the set. The tree is shown in a compressed, hanging format.

showTreeWith :: Show a => Bool -> Bool -> Set a -> StringSource

O(n). The expression (showTreeWith hang wide map) shows the tree that implements the set. If hang is True, a hanging tree is shown otherwise a rotated tree is shown. If wide is True, an extra wide version is shown.

 Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1..5]
 4
 +--2
 |  +--1
 |  +--3
 +--5

 Set> putStrLn $ showTreeWith True True $ fromDistinctAscList [1..5]
 4
 |
 +--2
 |  |
 |  +--1
 |  |
 |  +--3
 |
 +--5

 Set> putStrLn $ showTreeWith False True $ fromDistinctAscList [1..5]
 +--5
 |
 4
 |
 |  +--3
 |  |
 +--2
    |
    +--1

valid :: Ord a => Set a -> BoolSource

O(n). Test if the internal set structure is valid.