intset-0.1.0.3: Pure, mergeable, succinct Int sets.

Portabilityportable
Stabilityexperimental
Maintainerpxqr.sta@gmail.com
Safe HaskellNone

Data.IntervalSet

Contents

Description

An efficient implementation of dense integer sets based on Big-Endian PATRICIA trees with buddy suffix compression.

References:

This implementation performs espessially well then set contains long integer invervals like [0..2047] that are just merged into one interval description. This allow to perform many operations in constant time and space. However if set contain sparse integers like [1,12,7908,234,897] the same operations will take O(min(W, n)) which is good enough in most cases.

Conventions in complexity notation:

  • n — number of elements in a set;
  • W — number bits in a Key. This is 32 or 64 at 32 and 64 bit platforms respectively;
  • O(n) or O(k) — means this operation have complexity O(n) in worst case (e.g. sparse set) or O(k) in best case (e.g. one single interval).

Note that some operations will take centuries to compute. For example map id universe will a long time to end as well as filter applied to universe, naturals, positives or negatives.

Also note that some operations like union, intersection and difference have overriden from default fixity, so use these operations with infix syntax carefully.

Synopsis

Types

data IntSet Source

Integer set.

Constructors

Bin !Prefix !Mask !IntSet !IntSet

Layout: prefix up to branching bit, mask for branching bit, left subtree and right subtree.

IntSet = Bin: contains elements of left and right subtrees thus just merge to subtrees. All elements of left subtree is less that from right subtree. Except non-negative numbers, they are in left subtree of root bin, if any.

Tip !Prefix !BitMap

Layout: Prefix up to mask of bitmap size, and bitmap containing elements starting from the prefix.

IntSet = Tip: contains elements

Fin !Prefix !Mask

Layout: Prefix up to mask of bitmap size, and mask specifing how large is set. There is no branching bit at all. Tip is never full.

IntSet = Fin: contains all elements from prefix to (prefix - mask - 1)

Nil

Empty set. Contains nothing.

type Key = IntSource

Type of IntSet elements.

Query

Cardinality

null :: IntSet -> BoolSource

O(1). Is this the empty set?

size :: IntSet -> IntSource

O(n) or O(1). Cardinality of a set.

Membership

member :: Key -> IntSet -> BoolSource

O(min(W, n)) or O(1). Test if the value is element of the set.

notMember :: Key -> IntSet -> BoolSource

O(min(W, n)) or O(1). Test if the value is not an element of the set.

Inclusion

isSubsetOf :: IntSet -> IntSet -> BoolSource

O(n + m) or O(1). Test if the second set contain each element of the first.

isSupersetOf :: IntSet -> IntSet -> BoolSource

O(n + m) or O(1). Test if the second set is subset of the first.

Construction

empty :: IntSetSource

O(1). The empty set.

singleton :: Key -> IntSetSource

O(1). A set containing one element.

interval :: Key -> Key -> IntSetSource

O(n). Set containing elements from the specified range.

 interval a b = fromList [a..b]

Modification

insert :: Key -> IntSet -> IntSetSource

O(min(W, n) or O(1). Add a value to the set.

delete :: Key -> IntSet -> IntSetSource

O(min(n, W)). Delete a value from the set.

Map Fold Filter

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

O(n * min(W, n)). Apply the function to each element of the set.

Do not use this operation with the universe, naturals or negatives sets.

foldr :: (Key -> a -> a) -> a -> IntSet -> aSource

O(n). Fold the element using the given right associative binary operator.

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

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

Do not use this operation with the universe, naturals or negatives sets.

Splits

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

O(min(W, n). Split the set such that the left projection of the resulting pair contains elements less than the key and right element contains greater than the key. The exact key is excluded from result:

 split 5 (fromList [0..10]) == (fromList [0..4], fromList [6..10])

Performance note: if need only lesser or greater keys, use splitLT or splitGT respectively.

splitGT :: Key -> IntSet -> IntSetSource

O(min(W, n). Takes subset such that each element is greater than the specified key. The exact key is excluded from result.

splitLT :: Key -> IntSet -> IntSetSource

O(min(W, n). Takes subset such that each element is less than the specified key. The exact key is excluded from result.

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

O(n). Split a set using given predicate.

 forall f. fst . partition f = filter f
 forall f. snd . partition f = filter (not . f)

Min/Max

findMin :: IntSet -> KeySource

O(min(W, n)) or O(1). Find minimal element of the set. If set is empty then min is undefined.

findMax :: IntSet -> KeySource

O(min(W, n)) or O(1). Find maximal element of the set. Is set is empty then max is undefined.

Combine

union :: IntSet -> IntSet -> IntSetSource

O(n + m) or O(1). Find set which contains elements of both right and left sets.

unions :: [IntSet] -> IntSetSource

O(max(n)^2 * spine) or O(spine). The union of list of sets.

intersection :: IntSet -> IntSet -> IntSetSource

O(n + m) or O(1). Find maximal common subset of the two given sets.

intersections :: [IntSet] -> IntSetSource

O(max(n) * spine) or O(spine). Find out common subset of the list of sets.

difference :: IntSet -> IntSet -> IntSetSource

O(n + m) or O(1). Find difference of the two sets.

symDiff :: IntSet -> IntSet -> IntSetSource

O(n + m) or O(1). Find symmetric difference of the two sets: resulting set containts elements that either in first or second set, but not in both simultaneous.

Monoids

data Union Source

Monoid under union. Used by default for IntSet.

You could use Sum from Monoid as well.

Conversion

Arbitary

elems :: IntSet -> [Key]Source

elems is alias to toList for compatibility.

toList :: IntSet -> [Key]Source

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

fromList :: [Key] -> IntSetSource

O(n * min(W, n)) or O(n). Create a set from a list of its elements.

Ordered

toAscList :: IntSet -> [Key]Source

O(n). Convert the set to a list of its element in ascending order.

toDescList :: IntSet -> [Key]Source

O(n). Convert the set to a list of its element in descending order.

fromAscList :: [Key] -> IntSetSource

Build a set from an ascending list of elements.