translatable-intset-0.1: Integer sets with a constant time translate operation.

MaintainerJannis Harder <jannis@harderweb.de>

Data.IntSet.Translatable

Contents

Description

An implementation of integer sets with a constant time translate operation, where translate is defined to be translate x s = map (+x) s.

Since many function names (but not the type name) clash with Prelude names, this module is usually imported qualified, e.g.

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

This implementation is based on Finger-Trees storing differences of consecutive entries of the ordered sequence of set elements. With this representation, a translation of all elements can be realized by changing only the leftmost element of the Finger-Tree which is a constant time operation. Together with caching of the accumulated differences most set operations can be implemented efficiently too.

Synopsis

Set type

Operators

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

O(???). See difference.

Query

null :: IntSet -> BoolSource

O(1). Is the set empty?

size :: IntSet -> IntSource

O(1). Cardinality of the set.

member :: Int -> IntSet -> BoolSource

O(log(n)). Is the value a member of the set?

notMember :: Int -> IntSet -> BoolSource

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

Construction

empty :: IntSetSource

O(1). The empty set.

singleton :: Int -> IntSetSource

O(1). A set of one element.

insert :: Int -> IntSet -> IntSetSource

O(log(n)). Add a value to the set.

delete :: Int -> IntSet -> IntSetSource

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

Combine

union :: IntSet -> IntSet -> IntSetSource

O(m log(n / m)) where m<=n. The union of two sets. O(log m) if all elements of one set are larger than all elements of the other set.

unions :: [IntSet] -> IntSetSource

The union of a list of sets.

difference :: IntSet -> IntSet -> IntSetSource

O(???). Difference between two sets.

intersection :: IntSet -> IntSet -> IntSetSource

O(???). The intersection of two sets.

Filter

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

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

partition :: (Int -> Bool) -> IntSet -> (IntSet, IntSet)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 :: Int -> IntSet -> (IntSet, IntSet)Source

O(log(min(i,n-i))). 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 :: Int -> IntSet -> (IntSet, Bool, IntSet)Source

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

Min/Max

findMin :: IntSet -> IntSource

O(1). The minimal element of the set.

findMax :: IntSet -> IntSource

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

deleteMin :: IntSet -> IntSetSource

O(1). Delete the minimal element.

deleteMax :: IntSet -> IntSetSource

O(1). Delete the maximal element.

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

O(1). Delete and find the minimal element.

 deleteFindMin set = (findMin set, deleteMin set)

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

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

 deleteFindMax set = (findMax set, deleteMax set)

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

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

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

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

Map

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

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

translate :: Int -> IntSet -> IntSetSource

O(1). Add a constant value to all elements of the set.

 translate x s == map (+x) s

Fold

fold :: (Int -> b -> b) -> b -> IntSet -> bSource

O(n). Fold over the elements of a set in an unspecified order.

 sum set   == fold (+) 0 set
 elems set == fold (:) [] set

Conversion

List

elems :: IntSet -> [Int]Source

O(n). The elements of a set. (For sets, this is equivalent to toList)

toList :: IntSet -> [Int]Source

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

fromList :: [Int] -> IntSetSource

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

Ordered list

toAscList :: IntSet -> [Int]Source

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

fromAscList :: [Int] -> IntSetSource

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

fromDistinctAscList :: [Int] -> IntSetSource

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