Copyright | (c) Daan Leijen 2002 (c) Edward Kmett 2011 |
---|---|
License | BSD-style |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | non-portable (TypeFamilies, MagicHash) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An efficient implementation of integer sets.
Since many function names (but not the type name) clash with
Prelude names, this module is usually imported qualified
, 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.
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).
Unlike the reference implementation in Data.IntSet, Data.Interned.IntSet uses hash consing to ensure that there is only ever one copy of any given IntSet in memory. This is enabled by the normal form of the PATRICIA trie.
This can mean a drastic reduction in the memory footprint of a program in exchange for much more costly set manipulation.
Synopsis
- data IntSet
- identity :: IntSet -> Id
- (\\) :: IntSet -> IntSet -> IntSet
- null :: IntSet -> Bool
- size :: IntSet -> Int
- member :: Int -> IntSet -> Bool
- notMember :: Int -> IntSet -> Bool
- isSubsetOf :: IntSet -> IntSet -> Bool
- isProperSubsetOf :: IntSet -> IntSet -> Bool
- empty :: IntSet
- singleton :: Int -> IntSet
- insert :: Int -> IntSet -> IntSet
- delete :: Int -> IntSet -> IntSet
- union :: IntSet -> IntSet -> IntSet
- unions :: [IntSet] -> IntSet
- difference :: IntSet -> IntSet -> IntSet
- intersection :: IntSet -> IntSet -> IntSet
- filter :: (Int -> Bool) -> IntSet -> IntSet
- partition :: (Int -> Bool) -> IntSet -> (IntSet, IntSet)
- split :: Int -> IntSet -> (IntSet, IntSet)
- splitMember :: Int -> IntSet -> (IntSet, Bool, IntSet)
- findMin :: IntSet -> Int
- findMax :: IntSet -> Int
- deleteMin :: IntSet -> IntSet
- deleteMax :: IntSet -> IntSet
- deleteFindMin :: IntSet -> (Int, IntSet)
- deleteFindMax :: IntSet -> (Int, IntSet)
- maxView :: IntSet -> Maybe (Int, IntSet)
- minView :: IntSet -> Maybe (Int, IntSet)
- map :: (Int -> Int) -> IntSet -> IntSet
- fold :: (Int -> b -> b) -> b -> IntSet -> b
- elems :: IntSet -> [Int]
- toList :: IntSet -> [Int]
- fromList :: [Int] -> IntSet
- toAscList :: IntSet -> [Int]
- fromAscList :: [Int] -> IntSet
- fromDistinctAscList :: [Int] -> IntSet
- showTree :: IntSet -> String
- showTreeWith :: Bool -> Bool -> IntSet -> String
Set type
A set of integers.
Instances
Monoid IntSet Source # | |
Semigroup IntSet Source # | |
Read IntSet Source # | |
Show IntSet Source # | |
Eq IntSet Source # | |
Ord IntSet Source # | |
Hashable IntSet Source # | |
Defined in Data.Interned.IntSet | |
Interned IntSet Source # | |
Defined in Data.Interned.IntSet data Description IntSet Source # type Uninterned IntSet Source # | |
Uninternable IntSet Source # | |
Defined in Data.Interned.IntSet | |
Eq (Description IntSet) Source # | |
Defined in Data.Interned.IntSet (==) :: Description IntSet -> Description IntSet -> Bool # (/=) :: Description IntSet -> Description IntSet -> Bool # | |
Hashable (Description IntSet) Source # | |
Defined in Data.Interned.IntSet hashWithSalt :: Int -> Description IntSet -> Int # hash :: Description IntSet -> Int # | |
data Description IntSet Source # | |
Defined in Data.Interned.IntSet | |
type Uninterned IntSet Source # | |
Defined in Data.Interned.IntSet |
Operators
Query
isSubsetOf :: IntSet -> IntSet -> Bool Source #
O(n+m). Is this a subset?
(s1
tells whether isSubsetOf
s2)s1
is a subset of s2
.
isProperSubsetOf :: IntSet -> IntSet -> Bool Source #
O(n+m). Is this a proper subset? (ie. a subset but not equal).
Construction
insert :: Int -> IntSet -> IntSet Source #
O(min(n,W)). Add a value to the set. When the value is already
an element of the set, it is replaced by the new one, ie. insert
is left-biased.
delete :: Int -> IntSet -> IntSet Source #
O(min(n,W)). Delete a value in the set. Returns the original set when the value was not present.
Combine
Filter
filter :: (Int -> Bool) -> IntSet -> IntSet Source #
O(n). Filter all elements that satisfy some predicate.
partition :: (Int -> Bool) -> IntSet -> (IntSet, IntSet) Source #
O(n). partition the set according to some predicate.
split :: Int -> IntSet -> (IntSet, IntSet) Source #
O(min(n,W)). The expression (
) is a pair split
x set(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(min(n,W)). Performs a split
but also returns whether the pivot
element was found in the original set.
Min/Max
deleteFindMin :: IntSet -> (Int, IntSet) Source #
O(min(n,W)). Delete and find the minimal element.
deleteFindMin set = (findMin set, deleteMin set)
deleteFindMax :: IntSet -> (Int, IntSet) Source #
O(min(n,W)). Delete and find the maximal element.
deleteFindMax set = (findMax set, deleteMax set)
maxView :: IntSet -> Maybe (Int, 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 (Int, 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.
Map
map :: (Int -> Int) -> IntSet -> IntSet Source #
O(n*min(n,W)).
is the set obtained by applying map
f sf
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
Fold
fold :: (Int -> b -> b) -> b -> IntSet -> b Source #
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)
Ordered list
fromAscList :: [Int] -> IntSet Source #
O(n). Build a set from an ascending list of elements. The precondition (input list is ascending) is not checked.
fromDistinctAscList :: [Int] -> IntSet Source #
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 -> String Source #
O(n). Show the tree that implements the set. The tree is shown in a compressed, hanging format.
showTreeWith :: Bool -> Bool -> IntSet -> String Source #
O(n). The expression (
) shows
the tree that implements the set. If showTreeWith
hang wide maphang
is
True
, a hanging tree is shown otherwise a rotated tree is shown. If
wide
is True
, an extra wide version is shown.