multiset-0.1: The Data.MultiSet container typeSource codeContentsIndex
Data.MultiSet
Portabilityportable
Stabilityprovisional
Maintainerlibraries@haskell.org
Contents
MultiSet type
Operators
Query
Construction
Combine
Filter
Map
Monadic
Fold
Min/Max
Conversion
List
Ordered list
Occurrence lists
Map
Set
Debugging
Description

An efficient implementation of multisets, also somtimes called bags.

A multiset is like a set, but it can contain multiple copies of the same element. Unless otherwise specified all insert and remove opertions affect only a single copy of an element. For example the minimal element before and after deleteMin could be the same, only with one less occurence.

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

  import Data.MultiSet (MultiSet)
  import qualified Data.MultiSet as MultiSet

The implementation of MultiSet is based on the Data.Map module.

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.

In the complexity of functions n refers to the number of distinct elements, t is the total number of elements.

Synopsis
data MultiSet a
type Occur = Int
(\\) :: Ord a => MultiSet a -> MultiSet a -> MultiSet a
null :: MultiSet a -> Bool
size :: MultiSet a -> Occur
distinctSize :: MultiSet a -> Occur
member :: Ord a => a -> MultiSet a -> Bool
notMember :: Ord a => a -> MultiSet a -> Bool
occur :: Ord a => a -> MultiSet a -> Occur
isSubsetOf :: Ord a => MultiSet a -> MultiSet a -> Bool
isProperSubsetOf :: Ord a => MultiSet a -> MultiSet a -> Bool
empty :: MultiSet a
singleton :: a -> MultiSet a
insert :: Ord a => a -> MultiSet a -> MultiSet a
insertMany :: Ord a => a -> Occur -> MultiSet a -> MultiSet a
delete :: Ord a => a -> MultiSet a -> MultiSet a
deleteMany :: Ord a => a -> Occur -> MultiSet a -> MultiSet a
deleteAll :: Ord a => a -> MultiSet a -> MultiSet a
union :: Ord a => MultiSet a -> MultiSet a -> MultiSet a
unions :: Ord a => [MultiSet a] -> MultiSet a
difference :: Ord a => MultiSet a -> MultiSet a -> MultiSet a
intersection :: Ord a => MultiSet a -> MultiSet a -> MultiSet a
filter :: Ord a => (a -> Bool) -> MultiSet a -> MultiSet a
partition :: Ord a => (a -> Bool) -> MultiSet a -> (MultiSet a, MultiSet a)
split :: Ord a => a -> MultiSet a -> (MultiSet a, MultiSet a)
splitOccur :: Ord a => a -> MultiSet a -> (MultiSet a, Occur, MultiSet a)
map :: (Ord a, Ord b) => (a -> b) -> MultiSet a -> MultiSet b
mapMonotonic :: (a -> b) -> MultiSet a -> MultiSet b
mapMaybe :: (Ord a, Ord b) => (a -> Maybe b) -> MultiSet a -> MultiSet b
mapEither :: (Ord a, Ord b, Ord c) => (a -> Either b c) -> MultiSet a -> (MultiSet b, MultiSet c)
concatMap :: (Ord a, Ord b) => (a -> [b]) -> MultiSet a -> MultiSet b
unionsMap :: (Ord a, Ord b) => (a -> MultiSet b) -> MultiSet a -> MultiSet b
bind :: (Ord a, Ord b) => MultiSet a -> (a -> MultiSet b) -> MultiSet b
join :: Ord a => MultiSet (MultiSet a) -> MultiSet a
fold :: (a -> b -> b) -> b -> MultiSet a -> b
foldOccur :: (a -> Occur -> b -> b) -> b -> MultiSet a -> b
findMin :: MultiSet a -> a
findMax :: MultiSet a -> a
deleteMin :: MultiSet a -> MultiSet a
deleteMax :: MultiSet a -> MultiSet a
deleteMinAll :: MultiSet a -> MultiSet a
deleteMaxAll :: MultiSet a -> MultiSet a
deleteFindMin :: MultiSet a -> (a, MultiSet a)
deleteFindMax :: MultiSet a -> (a, MultiSet a)
maxView :: Monad m => MultiSet a -> m (a, MultiSet a)
minView :: Monad m => MultiSet a -> m (a, MultiSet a)
elems :: MultiSet a -> [a]
distinctElems :: MultiSet a -> [a]
toList :: MultiSet a -> [a]
fromList :: Ord a => [a] -> MultiSet a
toAscList :: MultiSet a -> [a]
fromAscList :: Eq a => [a] -> MultiSet a
fromDistinctAscList :: [a] -> MultiSet a
toOccurList :: MultiSet a -> [(a, Occur)]
toAscOccurList :: MultiSet a -> [(a, Occur)]
fromOccurList :: Ord a => [(a, Occur)] -> MultiSet a
fromAscOccurList :: Eq a => [(a, Occur)] -> MultiSet a
fromDistinctAscOccurList :: [(a, Occur)] -> MultiSet a
toMap :: MultiSet a -> Map a Occur
fromMap :: Ord a => Map a Occur -> MultiSet a
fromOccurMap :: Map a Occur -> MultiSet a
toSet :: MultiSet a -> Set a
fromSet :: Set a -> MultiSet a
showTree :: Show a => MultiSet a -> String
showTreeWith :: Show a => Bool -> Bool -> MultiSet a -> String
valid :: Ord a => MultiSet a -> Bool
MultiSet type
data MultiSet a Source
A multiset of values a. The same value can occur multiple times.
show/hide Instances
type Occur = IntSource
The number of occurences of an element
Operators
(\\) :: Ord a => MultiSet a -> MultiSet a -> MultiSet aSource
O(n+m). See difference.
Query
null :: MultiSet a -> BoolSource
O(1). Is this the empty multiset?
size :: MultiSet a -> OccurSource
O(n). The number of elements in the multiset.
distinctSize :: MultiSet a -> OccurSource
O(1). The number of distinct elements in the multiset.
member :: Ord a => a -> MultiSet a -> BoolSource
O(log n). Is the element in the multiset?
notMember :: Ord a => a -> MultiSet a -> BoolSource
O(log n). Is the element not in the multiset?
occur :: Ord a => a -> MultiSet a -> OccurSource
O(log n). The number of occurences of an element in a multiset.
isSubsetOf :: Ord a => MultiSet a -> MultiSet a -> BoolSource
O(n+m). Is this a subset? (s1 `isSubsetOf` s2) tells whether s1 is a subset of s2.
isProperSubsetOf :: Ord a => MultiSet a -> MultiSet a -> BoolSource
O(n+m). Is this a proper subset? (ie. a subset but not equal).
Construction
empty :: MultiSet aSource
O(1). The empty mutli set.
singleton :: a -> MultiSet aSource
O(1). Create a singleton mutli set.
insert :: Ord a => a -> MultiSet a -> MultiSet aSource
O(log n). Insert an element in a multiset.
insertMany :: Ord a => a -> Occur -> MultiSet a -> MultiSet aSource

O(log n). Insert an element in a multiset a given number of times.

Negative numbers remove occurences of the given element.

delete :: Ord a => a -> MultiSet a -> MultiSet aSource
O(log n). Delete a single element from a multiset.
deleteMany :: Ord a => a -> Occur -> MultiSet a -> MultiSet aSource

O(log n). Delete an element from a multiset a given number of times.

Negative numbers add occurences of the given element.

deleteAll :: Ord a => a -> MultiSet a -> MultiSet aSource
O(log n). Delete all occurences of an element from a multiset.
Combine
union :: Ord a => MultiSet a -> MultiSet a -> MultiSet aSource
O(n+m). The union of two multisets, preferring the first multiset when equal elements are encountered. The implementation uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset union smallset).
unions :: Ord a => [MultiSet a] -> MultiSet aSource
The union of a list of multisets: (unions == foldl union empty).
difference :: Ord a => MultiSet a -> MultiSet a -> MultiSet aSource
O(n+m). Difference of two multisets. The implementation uses an efficient hedge algorithm comparable with hedge-union.
intersection :: Ord a => MultiSet a -> MultiSet a -> MultiSet aSource

O(n+m). The intersection of two multisets. Elements of the result come from the first multiset, so for example

 import qualified Data.MultiSet as MS
 data AB = A | B deriving Show
 instance Ord AB where compare _ _ = EQ
 instance Eq AB where _ == _ = True
 main = print (MS.singleton A `MS.intersection` MS.singleton B,
               MS.singleton B `MS.intersection` MS.singleton A)

prints (fromList [A],fromList [B]).

Filter
filter :: Ord a => (a -> Bool) -> MultiSet a -> MultiSet aSource
O(n). Filter all elements that satisfy the predicate.
partition :: Ord a => (a -> Bool) -> MultiSet a -> (MultiSet a, MultiSet a)Source
O(n). Partition the multiset into two multisets, one with all elements that satisfy the predicate and one with all elements that don't satisfy the predicate. See also split.
split :: Ord a => a -> MultiSet a -> (MultiSet a, MultiSet a)Source
O(log n). The expression (split x set) is a pair (set1,set2) where all elements in set1 are lower than x and all elements in set2 larger than x. x is not found in neither set1 nor set2.
splitOccur :: Ord a => a -> MultiSet a -> (MultiSet a, Occur, MultiSet a)Source
O(log n). Performs a split but also returns the number of occurences of the pivot element in the original set.
Map
map :: (Ord a, Ord b) => (a -> b) -> MultiSet a -> MultiSet bSource
O(n*log n). map f s is the multiset obtained by applying f to each element of s.
mapMonotonic :: (a -> b) -> MultiSet a -> MultiSet bSource

O(n). The

mapMonotonic f s == map f s, but works only when f is strictly monotonic. 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
mapMaybe :: (Ord a, Ord b) => (a -> Maybe b) -> MultiSet a -> MultiSet bSource
O(n). Map and collect the Just results.
mapEither :: (Ord a, Ord b, Ord c) => (a -> Either b c) -> MultiSet a -> (MultiSet b, MultiSet c)Source
O(n). Map and separate the Left and Right results.
concatMap :: (Ord a, Ord b) => (a -> [b]) -> MultiSet a -> MultiSet bSource
O(n). Apply a function to each element, and take the union of the results
unionsMap :: (Ord a, Ord b) => (a -> MultiSet b) -> MultiSet a -> MultiSet bSource
O(n). Apply a function to each element, and take the union of the results
Monadic
bind :: (Ord a, Ord b) => MultiSet a -> (a -> MultiSet b) -> MultiSet bSource
O(n). The monad bind operation, (>>=), for multisets.
join :: Ord a => MultiSet (MultiSet a) -> MultiSet aSource
O(n). The monad join operation for multisets.
Fold
fold :: (a -> b -> b) -> b -> MultiSet a -> bSource
O(t). Fold over the elements of a multiset in an unspecified order.
foldOccur :: (a -> Occur -> b -> b) -> b -> MultiSet a -> bSource
O(n). Fold over the elements of a multiset with their occurences.
Min/Max
findMin :: MultiSet a -> aSource
O(log n). The minimal element of a multiset.
findMax :: MultiSet a -> aSource
O(log n). The maximal element of a multiset.
deleteMin :: MultiSet a -> MultiSet aSource
O(log n). Delete the minimal element.
deleteMax :: MultiSet a -> MultiSet aSource
O(log n). Delete the maximal element.
deleteMinAll :: MultiSet a -> MultiSet aSource
O(log n). Delete all occurences of the minimal element.
deleteMaxAll :: MultiSet a -> MultiSet aSource
O(log n). Delete all occurences of the maximal element.
deleteFindMin :: MultiSet a -> (a, MultiSet a)Source

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

 deleteFindMin set = (findMin set, deleteMin set)
deleteFindMax :: MultiSet a -> (a, MultiSet a)Source

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

 deleteFindMax set = (findMax set, deleteMax set)
maxView :: Monad m => MultiSet a -> m (a, MultiSet a)Source
O(log n). Retrieves the maximal element of the multiset, and the set with that element removed. fails (in the monad) when passed an empty multiset.
minView :: Monad m => MultiSet a -> m (a, MultiSet a)Source
O(log n). Retrieves the minimal element of the multiset, and the set with that element removed. fails (in the monad) when passed an empty multiset.
Conversion
List
elems :: MultiSet a -> [a]Source
O(t). The elements of a multiset.
distinctElems :: MultiSet a -> [a]Source

O(n). The distinct elements of a multiset, each element occurs only once in the list.

 distinctElems = map fst . toOccurList
toList :: MultiSet a -> [a]Source
O(t). Convert the multiset to a list of elements.
fromList :: Ord a => [a] -> MultiSet aSource
O(t*log t). Create a multiset from a list of elements.
Ordered list
toAscList :: MultiSet a -> [a]Source
O(t). Convert the multiset to an ascending list of elements.
fromAscList :: Eq a => [a] -> MultiSet aSource
O(t). Build a multiset from an ascending list in linear time. The precondition (input list is ascending) is not checked.
fromDistinctAscList :: [a] -> MultiSet aSource
O(n). Build a multiset from an ascending list of distinct elements in linear time. The precondition (input list is strictly ascending) is not checked.
Occurrence lists
toOccurList :: MultiSet a -> [(a, Occur)]Source
O(n). Convert the multiset to a list of element/occurence pairs.
toAscOccurList :: MultiSet a -> [(a, Occur)]Source
O(n). Convert the multiset to an ascending list of element/occurence pairs.
fromOccurList :: Ord a => [(a, Occur)] -> MultiSet aSource
O(n*log n). Create a multiset from a list of element/occurence pairs.
fromAscOccurList :: Eq a => [(a, Occur)] -> MultiSet aSource
O(n). Build a multiset from an ascending list of element/occurence pairs in linear time. The precondition (input list is ascending) is not checked.
fromDistinctAscOccurList :: [(a, Occur)] -> MultiSet aSource
O(n). Build a multiset from an ascending list of elements/occurence pairs where each elements appears only once. The precondition (input list is strictly ascending) is not checked.
Map
toMap :: MultiSet a -> Map a OccurSource
O(1). Convert a multiset to a Map from elements to number of occurrences.
fromMap :: Ord a => Map a Occur -> MultiSet aSource
O(n). Convert a Map from elements to occurrences to a multiset.
fromOccurMap :: Map a Occur -> MultiSet aSource
O(1). Convert a Map from elements to occurrences to a multiset. Assumes that the Map contains only values larger than one. The precondition (all elements > 1) is not checked.
Set
toSet :: MultiSet a -> Set aSource
O(n). Convert a multiset to a Set, removing duplicates.
fromSet :: Set a -> MultiSet aSource
O(n). Convert a Set to a multiset.
Debugging
showTree :: Show a => MultiSet a -> StringSource
O(n). Show the tree that implements the set. The tree is shown in a compressed, hanging format.
showTreeWith :: Show a => Bool -> Bool -> MultiSet a -> 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.

 Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1,1,2,3,4,5]
 (1*) 4
 +--(1*) 2
 |  +--(2*) 1
 |  +--(1*) 3
 +--(1*) 5
 
 Set> putStrLn $ showTreeWith True True $ fromDistinctAscList [1,1,2,3,4,5]
 (1*) 4
 |
 +--(1*) 2
 |  |
 |  +--(2*) 1
 |  |
 |  +--(1*) 3
 |
 +--(1*) 5
 
 Set> putStrLn $ showTreeWith False True $ fromDistinctAscList [1,1,2,3,4,5]
 +--(1*) 5
 |
 (1*) 4
 |
 |  +--(1*) 3
 |  |
 +--(1*) 2
    |
    +--(2*) 1
valid :: Ord a => MultiSet a -> BoolSource
O(n). Test if the internal multiset structure is valid.
Produced by Haddock version 2.4.2