critbit-0.2.0.0: Crit-bit maps and sets

PortabilityGHC
Stabilityexperimental
Maintainerbos@serpentine.com
Safe HaskellNone

Data.CritBit.Set

Contents

Description

A set type that uses crit-bit trees internally.

For every n key-value pairs stored, a crit-bit tree uses n-1 internal nodes, for a total of 2n-1 internal nodes and leaves.

Synopsis

Set type

data Set a Source

A set based on crit-bit trees.

Instances

Foldable Set 
Eq a => Eq (Set a) 
Show a => Show (Set a) 
CritBitKey k => Monoid (Set k) 
NFData a => NFData (Set a) 

Operators

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

Same as difference.

Query

null :: Set a -> BoolSource

O(1). Is the set empty?

 null (empty)         == True
 null (singleton "a") == False

size :: Set a -> IntSource

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

 size empty                      == 0
 size (singleton "a")            == 1
 size (fromList ["a", "c", "b"]) == 3

member :: CritBitKey a => a -> Set a -> BoolSource

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

 member "a" (fromList ["a", "b"]) == True
 member "c" (fromList ["a", "b"]) == False

See also notMember.

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

O(k). Is the element not in the set?

 notMember "a" (fromList ["a", "b"]) == False
 notMember "c" (fromList ["a", "b"]) == True

See also member.

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

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

 lookupLT "b"  (fromList ["a", "b"]) == Just "a"
 lookupLT "aa" (fromList ["a", "b"]) == Just "a"
 lookupLT "a"  (fromList ["a", "b"]) == Nothing

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

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

 lookupGT "b"  (fromList ["a", "b"]) == Nothing
 lookupGT "aa" (fromList ["a", "b"]) == Just "b"
 lookupGT "a"  (fromList ["a", "b"]) == Just "b"

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

O(k). Find largest element smaller than or equal to the given one.

 lookupGE "b"  (fromList ["a", "b"]) == Just "b"
 lookupGE "aa" (fromList ["a", "b"]) == Just "b"
 lookupGE "a"  (fromList ["a", "b"]) == Just "a"
 lookupGE ""   (fromList ["a", "b"]) == Nothing

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

O(k). Find smallest element greater than or equal to the given one.

 lookupGE "aa" (fromList ["a", "b"]) == Just "b"
 lookupGE "b"  (fromList ["a", "b"]) == Just "b"
 lookupGE "bb" (fromList ["a", "b"]) == Nothing

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

O(n+m). Is this a proper subset (ie. a subset but not equal)? (s1 isSubsetOf s2) tells whether s1 is a proper subset of s2.

Construction

empty :: Set aSource

O(1). The empty set.

 empty      == fromList []
 size empty == 0

singleton :: a -> Set aSource

O(1). A set with a single element.

 singleton "a"        == fromList ["a"]

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

O(k). 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 :: CritBitKey a => a -> Set a -> Set aSource

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

Combine

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

O(k). The union of two sets, preferring the first set when equal elements are encountered.

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

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

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

O(k). The difference of two sets.

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

O(k). The intersection of two sets. Elements of the result come from the first set.

Filter

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

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

 filter (> "a") (fromList ["a", "b"]) == fromList [("3","b")]
 filter (> "x") (fromList ["a", "b"]) == empty
 filter (< "a") (fromList ["a", "b"]) == empty

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

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

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

 split "a" (fromList ["b", "d"]) == (empty, fromList ["b", "d")])
 split "b" (fromList ["b", "d"]) == (empty, singleton "d")
 split "c" (fromList ["b", "d"]) == (singleton "b", singleton "d")
 split "d" (fromList ["b", "d"]) == (singleton "b", empty)
 split "e" (fromList ["b", "d"]) == (fromList ["b", "d"], empty)

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

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

 splitMember "a" (fromList ["b", "d"]) == (empty, False, fromList ["b", "d"])
 splitMember "b" (fromList ["b", "d"]) == (empty, True, singleton "d")
 splitMember "c" (fromList ["b", "d"]) == (singleton "b", False, singleton "d")
 splitMember "d" (fromList ["b", "d"]) == (singleton "b", True, empty)
 splitMember "e" (fromList ["b", "d"]) == (fromList ["b", "d"], False, empty)

Map

map :: CritBitKey a2 => (a1 -> a2) -> Set a1 -> Set a2Source

O(k). 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 :: CritBitKey a2 => (a1 -> a2) -> Set a1 -> Set a2Source

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.

Min/Max

findMin :: Set a -> aSource

O(k'). The minimal element of a set.

findMax :: Set a -> aSource

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

deleteMin :: Set a -> Set aSource

O(k'). Delete the minimal element. Returns an empty set if the set is empty.

deleteMax :: Set a -> Set aSource

O(k). Delete the maximal element. Returns an empty set if the set is empty.

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

O(k'). Delete and find the minimal element.

 deleteFindMin set = (findMin set, deleteMin set)

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

O(k). Delete and find the maximal element.

 deleteFindMax set = (findMax set, deleteMax set)

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

O(k). 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(k'). 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 toList.

Returns the elements of a set in ascending order.

toList :: Set a -> [a]Source

O(n). Convert the set to a list of values. The list returned will be sorted in lexicographically ascending order.

 toList (fromList ["b", "a"]) == ["a", "b"]
 toList empty == []

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

O(k). Build a set from a list of values.

 fromList [] == empty
 fromList ["a", "b", "a"] == fromList ["a", "b"]

Ordered list

toAscList :: Set a -> [a]Source

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

toDescList :: Set a -> [a]Source

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

fromAscList :: CritBitKey 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 :: CritBitKey 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.