containers-0.5.1.0: Assorted concrete container types

Portabilityportable
Stabilityprovisional
Maintainerlibraries@haskell.org
Safe HaskellSafe

Data.IntSet

Contents

Description

An efficient implementation of integer sets.

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

  import Data.IntSet (IntSet)
  import qualified Data.IntSet as IntSet

The implementation is based on big-endian patricia trees. This data structure performs especially well on binary operations like union and intersection. However, my benchmarks show that it is also (much) faster on insertions and deletions when compared to a generic size-balanced set implementation (see Data.Set).

  • Chris Okasaki and Andy Gill, "Fast Mergeable Integer Maps", Workshop on ML, September 1998, pages 77-86, http://citeseer.ist.psu.edu/okasaki98fast.html
  • D.R. Morrison, "/PATRICIA -- Practical Algorithm To Retrieve Information Coded In Alphanumeric/", Journal of the ACM, 15(4), October 1968, pages 514-534.

Additionally, this implementation places bitmaps in the leaves of the tree. Their size is the natural size of a machine word (32 or 64 bits) and greatly reduce memory footprint and execution times for dense sets, e.g. sets where it is likely that many values lie close to each other. The asymptotics are not affected by this optimization.

Many operations have a worst-case complexity of O(min(n,W)). This means that the operation can become linear in the number of elements with a maximum of W -- the number of bits in an Int (32 or 64).

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

type Key = IntSource

Operators

(\\) :: IntSet -> IntSet -> IntSetSource

O(n+m). See difference.

Query

null :: IntSet -> BoolSource

O(1). Is the set empty?

size :: IntSet -> IntSource

O(n). Cardinality of the set.

member :: Key -> IntSet -> BoolSource

O(min(n,W)). Is the value a member of the set?

notMember :: Key -> IntSet -> BoolSource

O(min(n,W)). Is the element not in the set?

lookupLT :: Key -> IntSet -> Maybe KeySource

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 -> IntSet -> Maybe KeySource

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 -> IntSet -> Maybe KeySource

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 -> IntSet -> Maybe KeySource

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 :: IntSet -> IntSet -> BoolSource

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

isProperSubsetOf :: IntSet -> IntSet -> BoolSource

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

Construction

empty :: IntSetSource

O(1). The empty set.

singleton :: Key -> IntSetSource

O(1). A set of one element.

insert :: Key -> IntSet -> IntSetSource

O(min(n,W)). Add a value to the set. There is no left- or right bias for IntSets.

delete :: Key -> IntSet -> IntSetSource

O(min(n,W)). Delete a value in the set. Returns the original set when the value was not present.

Combine

union :: IntSet -> IntSet -> IntSetSource

O(n+m). The union of two sets.

unions :: [IntSet] -> IntSetSource

The union of a list of sets.

difference :: IntSet -> IntSet -> IntSetSource

O(n+m). Difference between two sets.

intersection :: IntSet -> IntSet -> IntSetSource

O(n+m). The intersection of two sets.

Filter

filter :: (Key -> Bool) -> IntSet -> IntSetSource

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

partition :: (Key -> Bool) -> IntSet -> (IntSet, IntSet)Source

O(n). partition the set according to some predicate.

split :: Key -> IntSet -> (IntSet, IntSet)Source

O(min(n,W)). 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 3 (fromList [1..5]) == (fromList [1,2], fromList [4,5])

splitMember :: Key -> IntSet -> (IntSet, Bool, IntSet)Source

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

Map

map :: (Key -> Key) -> IntSet -> IntSetSource

O(n*min(n,W)). 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

Folds

foldr :: (Key -> b -> b) -> b -> IntSet -> 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 -> Key -> a) -> a -> IntSet -> 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' :: (Key -> b -> b) -> b -> IntSet -> 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 -> Key -> a) -> a -> IntSet -> 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 :: (Key -> b -> b) -> b -> IntSet -> 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 :: IntSet -> KeySource

O(min(n,W)). The minimal element of the set.

findMax :: IntSet -> KeySource

O(min(n,W)). The maximal element of a set.

deleteMin :: IntSet -> IntSetSource

O(min(n,W)). Delete the minimal element.

deleteMax :: IntSet -> IntSetSource

O(min(n,W)). Delete the maximal element.

deleteFindMin :: IntSet -> (Key, IntSet)Source

O(min(n,W)). Delete and find the minimal element.

 deleteFindMin set = (findMin set, deleteMin set)

deleteFindMax :: IntSet -> (Key, IntSet)Source

O(min(n,W)). Delete and find the maximal element.

 deleteFindMax set = (findMax set, deleteMax set)

maxView :: IntSet -> Maybe (Key, IntSet)Source

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

minView :: IntSet -> Maybe (Key, IntSet)Source

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

Conversion

List

elems :: IntSet -> [Key]Source

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

toList :: IntSet -> [Key]Source

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

fromList :: [Key] -> IntSetSource

O(n*min(n,W)). Create a set from a list of integers.

Ordered list

toAscList :: IntSet -> [Key]Source

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

toDescList :: IntSet -> [Key]Source

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

fromAscList :: [Key] -> IntSetSource

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

fromDistinctAscList :: [Key] -> IntSetSource

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

Debugging

showTree :: IntSet -> StringSource

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

showTreeWith :: Bool -> Bool -> IntSet -> 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.