unpacked-containers-0: Unpacked containers via backpack

Copyright(c) Daan Leijen 2002 (c) Edward Kmett 2017-2018
LicenseBSD-style
Maintainerlibraries@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Set

Contents

Description

An efficient implementation of sets using backpack to unpack the element type

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.

Bounds for union, intersection, and difference are as given by

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.

Warning: The size of the set must not exceed maxBound::Int. Violation of this condition is not detected and if the size limit is exceeded, its behaviour is undefined.

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

A set of values a.

Instances
IsList Set Source # 
Instance details

Defined in Set.Internal

Associated Types

type Item Set :: * #

Methods

fromList :: [Item Set] -> Set #

fromListN :: Int -> [Item Set] -> Set #

toList :: Set -> [Item Set] #

Eq Set Source # 
Instance details

Defined in Set.Internal

Methods

(==) :: Set -> Set -> Bool #

(/=) :: Set -> Set -> Bool #

Data Key => Data Set Source # 
Instance details

Defined in Set.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set -> c Set #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Set #

toConstr :: Set -> Constr #

dataTypeOf :: Set -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Set) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Set) #

gmapT :: (forall b. Data b => b -> b) -> Set -> Set #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set -> r #

gmapQ :: (forall d. Data d => d -> u) -> Set -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Set -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set -> m Set #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set -> m Set #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set -> m Set #

Ord Set Source # 
Instance details

Defined in Set.Internal

Methods

compare :: Set -> Set -> Ordering #

(<) :: Set -> Set -> Bool #

(<=) :: Set -> Set -> Bool #

(>) :: Set -> Set -> Bool #

(>=) :: Set -> Set -> Bool #

max :: Set -> Set -> Set #

min :: Set -> Set -> Set #

Read Key => Read Set Source # 
Instance details

Defined in Set.Internal

Show Key => Show Set Source # 
Instance details

Defined in Set.Internal

Methods

showsPrec :: Int -> Set -> ShowS #

show :: Set -> String #

showList :: [Set] -> ShowS #

Semigroup Set Source # 
Instance details

Defined in Set.Internal

Methods

(<>) :: Set -> Set -> Set #

sconcat :: NonEmpty Set -> Set #

stimes :: Integral b => b -> Set -> Set #

Monoid Set Source # 
Instance details

Defined in Set.Internal

Methods

mempty :: Set #

mappend :: Set -> Set -> Set #

mconcat :: [Set] -> Set #

NFData Key => NFData Set Source # 
Instance details

Defined in Set.Internal

Methods

rnf :: Set -> () #

Default Set Source # 
Instance details

Defined in Set.Internal

Methods

def :: Set

type Item Set Source # 
Instance details

Defined in Set.Internal

type Item Set = Key

Operators

(\\) :: Set -> Set -> Set infixl 9 Source #

O(m*log(n/m+1)), m <= n. See difference.

Query

null :: Set -> Bool Source #

O(1). Is this the empty set?

size :: Set -> Int Source #

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

member :: Key -> Set -> Bool Source #

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

notMember :: Key -> Set -> Bool Source #

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

lookupLT :: Key -> Set -> Maybe Key Source #

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 :: Key -> Set -> Maybe Key Source #

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 :: Key -> Set -> Maybe Key Source #

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 :: Key -> Set -> Maybe Key Source #

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 :: Set -> Set -> Bool Source #

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

isProperSubsetOf :: Set -> Set -> Bool Source #

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

Construction

empty :: Set Source #

O(1). The empty set.

singleton :: Key -> Set Source #

O(1). Create a singleton set.

insert :: Key -> Set -> Set Source #

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 :: Key -> Set -> Set Source #

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

Combine

union :: Set -> Set -> Set Source #

O(m*log(n/m + 1)), m <= n. The union of two sets, preferring the first set when equal elements are encountered.

unions :: [Set] -> Set Source #

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

difference :: Set -> Set -> Set Source #

O(m*log(n/m + 1)), m <= n. Difference of two sets.

intersection :: Set -> Set -> Set Source #

O(m*log(n/m + 1)), m <= n. The intersection of two sets. Keyents 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 :: (Key -> Bool) -> Set -> Set Source #

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

takeWhileAntitone :: (Key -> Bool) -> Set -> Set Source #

O(log n). Take while a predicate on the elements holds. The user is responsible for ensuring that for all elements j and k in the set, j < k ==> p j >= p k. See note at spanAntitone.

takeWhileAntitone p = fromDistinctAscList . takeWhile p . toList
takeWhileAntitone p = filter p

dropWhileAntitone :: (Key -> Bool) -> Set -> Set Source #

O(log n). Drop while a predicate on the elements holds. The user is responsible for ensuring that for all elements j and k in the set, j < k ==> p j >= p k. See note at spanAntitone.

dropWhileAntitone p = fromDistinctAscList . dropWhile p . toList
dropWhileAntitone p = filter (not . p)

spanAntitone :: (Key -> Bool) -> Set -> (Set, Set) Source #

O(log n). Divide a set at the point where a predicate on the elements stops holding. The user is responsible for ensuring that for all elements j and k in the set, j < k ==> p j >= p k.

spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
spanAntitone p xs = partition p xs

Note: if p is not actually antitone, then spanAntitone will split the set at some unspecified point where the predicate switches from holding to not holding (where the predicate is seen to hold before the first element and to fail after the last element).

partition :: (Key -> Bool) -> Set -> (Set, Set) 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 :: Key -> Set -> (Set, Set) 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 :: Key -> Set -> (Set, Bool, Set) Source #

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

splitRoot :: Set -> [Set] Source #

O(1). Decompose a set into pieces based on the structure of the underlying tree. This function is useful for consuming a set in parallel.

No guarantee is made as to the sizes of the pieces; an internal, but deterministic process determines this. However, it is guaranteed that the pieces returned will be in ascending order (all elements in the first subset less than all elements in the second, and so on).

Examples:

splitRoot (fromList [1..6]) ==
  [fromList [1,2,3],fromList [4],fromList [5,6]]
splitRoot empty == []

Note that the current implementation does not return more than three subsets, but you should not depend on this behaviour because it can change in the future without notice.

Indexed

lookupIndex :: Key -> Set -> Maybe Int Source #

O(log n). Lookup the index of an element, which is its zero-based index in the sorted sequence of elements. The index is a number from 0 up to, but not including, the size of the set.

isJust   (lookupIndex 2 (fromList [5,3])) == False
fromJust (lookupIndex 3 (fromList [5,3])) == 0
fromJust (lookupIndex 5 (fromList [5,3])) == 1
isJust   (lookupIndex 6 (fromList [5,3])) == False

findIndex :: Key -> Set -> Int Source #

O(log n). Return the index of an element, which is its zero-based index in the sorted sequence of elements. The index is a number from 0 up to, but not including, the size of the set. Calls error when the element is not a member of the set.

findIndex 2 (fromList [5,3])    Error: element is not in the set
findIndex 3 (fromList [5,3]) == 0
findIndex 5 (fromList [5,3]) == 1
findIndex 6 (fromList [5,3])    Error: element is not in the set

elemAt :: Int -> Set -> Key Source #

O(log n). Retrieve an element by its index, i.e. by its zero-based index in the sorted sequence of elements. If the index is out of range (less than zero, greater or equal to size of the set), error is called.

elemAt 0 (fromList [5,3]) == 3
elemAt 1 (fromList [5,3]) == 5
elemAt 2 (fromList [5,3])    Error: index out of range

deleteAt :: Int -> Set -> Set Source #

O(log n). Delete the element at index, i.e. by its zero-based index in the sorted sequence of elements. If the index is out of range (less than zero, greater or equal to size of the set), error is called.

deleteAt 0    (fromList [5,3]) == singleton 5
deleteAt 1    (fromList [5,3]) == singleton 3
deleteAt 2    (fromList [5,3])    Error: index out of range
deleteAt (-1) (fromList [5,3])    Error: index out of range

take :: Int -> Set -> Set Source #

Take a given number of elements in order, beginning with the smallest ones.

take n = fromDistinctAscList . take n . toAscList

drop :: Int -> Set -> Set Source #

Drop a given number of elements in order, beginning with the smallest ones.

drop n = fromDistinctAscList . drop n . toAscList

splitAt :: Int -> Set -> (Set, Set) Source #

O(log n). Split a set at a particular index.

splitAt !n !xs = (take n xs, drop n xs)

Map

map :: (Key -> Key) -> Set -> Set Source #

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 :: (Key -> Key) -> Set -> Set Source #

O(n). The

mapMonotonic f s == map f s, but works only when f is strictly increasing. 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

foldMap :: Monoid m => (Key -> m) -> Set -> m Source #

foldr :: (Key -> b -> b) -> b -> Set -> b Source #

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 -> Key -> a) -> a -> Set -> a Source #

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' :: (Key -> b -> b) -> b -> Set -> b Source #

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 -> Key -> a) -> a -> Set -> a Source #

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

lookupMin :: Set -> Maybe Key Source #

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

Since: unpacked-containers-0.5.9

lookupMax :: Set -> Maybe Key Source #

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

Since: unpacked-containers-0.5.9

findMin :: Set -> Key Source #

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

findMax :: Set -> Key Source #

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

deleteMin :: Set -> Set Source #

O(log n). Delete the minimal element. Returns an empty set if the set is empty.

deleteMax :: Set -> Set Source #

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

deleteFindMin :: Set -> (Key, Set) Source #

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

deleteFindMin set = (findMin set, deleteMin set)

deleteFindMax :: Set -> (Key, Set) Source #

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

deleteFindMax set = (findMax set, deleteMax set)

maxView :: Set -> Maybe (Key, Set) 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 -> Maybe (Key, Set) 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 -> [Key] Source #

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

toList :: Set -> [Key] Source #

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

fromList :: [Key] -> Set Source #

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

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

Ordered list

toAscList :: Set -> [Key] Source #

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

toDescList :: Set -> [Key] Source #

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

fromAscList :: [Key] -> Set Source #

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

fromDescList :: [Key] -> Set Source #

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

fromDistinctAscList :: [Key] -> Set Source #

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.

fromDistinctDescList :: [Key] -> Set Source #

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

Debugging

showTree :: Show Key => Set -> String Source #

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

showTreeWith :: Show Key => Bool -> Bool -> Set -> String Source #

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 :: Set -> Bool Source #

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