multiset-0.3.4.3: The Data.MultiSet container type

Copyright(c) Twan van Laarhoven 2008
LicenseBSD-style
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.IntMultiSet

Contents

Description

An efficient implementation of multisets of integers, also sometimes called bags.

A multiset is like a set, but it can contain multiple copies of the same element.

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

 import Data.IntMultiSet (IntMultiSet)
 import qualified Data.IntMultiSet as IntMultiSet

The implementation of IntMultiSet is based on the Data.IntMap module.

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). Here n refers to the number of distinct elements, t is the total number of elements.

Synopsis

MultiSet type

data IntMultiSet Source #

A multiset of integers. The same value can occur multiple times.

Instances
Eq IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Data IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntMultiSet -> c IntMultiSet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntMultiSet #

toConstr :: IntMultiSet -> Constr #

dataTypeOf :: IntMultiSet -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntMultiSet) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntMultiSet) #

gmapT :: (forall b. Data b => b -> b) -> IntMultiSet -> IntMultiSet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntMultiSet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntMultiSet -> r #

gmapQ :: (forall d. Data d => d -> u) -> IntMultiSet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IntMultiSet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntMultiSet -> m IntMultiSet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMultiSet -> m IntMultiSet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMultiSet -> m IntMultiSet #

Ord IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Read IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Show IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Semigroup IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Monoid IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

NFData IntMultiSet Source # 
Instance details

Defined in Data.IntMultiSet

Methods

rnf :: IntMultiSet -> () #

type Key = Int Source #

Key type for IntMultiSet

type Occur = Int Source #

The number of occurrences of an element

Operators

(\\) :: IntMultiSet -> IntMultiSet -> IntMultiSet infixl 9 Source #

O(n+m). See difference.

Query

null :: IntMultiSet -> Bool Source #

O(1). Is this the empty multiset?

size :: IntMultiSet -> Int Source #

O(n). The number of elements in the multiset.

distinctSize :: IntMultiSet -> Int Source #

O(1). The number of distinct elements in the multiset.

member :: Key -> IntMultiSet -> Bool Source #

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

notMember :: Key -> IntMultiSet -> Bool Source #

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

occur :: Key -> IntMultiSet -> Int Source #

O(min(n,W)). The number of occurrences of an element in a multiset.

isSubsetOf :: IntMultiSet -> IntMultiSet -> Bool Source #

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

isProperSubsetOf :: IntMultiSet -> IntMultiSet -> Bool Source #

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

Construction

empty :: IntMultiSet Source #

O(1). The empty mutli set.

singleton :: Key -> IntMultiSet Source #

O(1). Create a singleton mutli set.

insert :: Key -> IntMultiSet -> IntMultiSet Source #

O(min(n,W)). Insert an element in a multiset.

insertMany :: Key -> Occur -> IntMultiSet -> IntMultiSet Source #

O(min(n,W)). Insert an element in a multiset a given number of times.

Negative numbers remove occurrences of the given element.

delete :: Key -> IntMultiSet -> IntMultiSet Source #

O(min(n,W)). Delete a single element from a multiset.

deleteMany :: Key -> Occur -> IntMultiSet -> IntMultiSet Source #

O(min(n,W)). Delete an element from a multiset a given number of times.

Negative numbers add occurrences of the given element.

deleteAll :: Key -> IntMultiSet -> IntMultiSet Source #

O(min(n,W)). Delete all occurrences of an element from a multiset.

Combine

union :: IntMultiSet -> IntMultiSet -> IntMultiSet Source #

O(n+m). The union of two multisets. The union adds the occurrences together.

The implementation uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset union smallset).

unions :: [IntMultiSet] -> IntMultiSet Source #

The union of a list of multisets: (unions == foldl union empty).

maxUnion :: IntMultiSet -> IntMultiSet -> IntMultiSet Source #

O(n+m). The union of two multisets. The number of occurrences of each element in the union is the maximum of the number of occurrences in the arguments (instead of the sum).

The implementation uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset union smallset).

difference :: IntMultiSet -> IntMultiSet -> IntMultiSet Source #

O(n+m). Difference of two multisets. The implementation uses an efficient hedge algorithm comparable with hedge-union.

intersection :: IntMultiSet -> IntMultiSet -> IntMultiSet Source #

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

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

Filter

filter :: (Key -> Bool) -> IntMultiSet -> IntMultiSet Source #

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

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

O(log n). Performs a split but also returns the number of occurrences of the pivot element in the original set.

Map

map :: (Key -> Key) -> IntMultiSet -> IntMultiSet Source #

O(n*log n). map f s is the multiset obtained by applying f to each element of s.

mapMonotonic :: (Key -> Key) -> IntMultiSet -> IntMultiSet Source #

O(n). 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 :: (Key -> Maybe Key) -> IntMultiSet -> IntMultiSet Source #

O(n). Map and collect the Just results.

mapEither :: (Key -> Either Key Key) -> IntMultiSet -> (IntMultiSet, IntMultiSet) Source #

O(n). Map and separate the Left and Right results.

concatMap :: (Key -> [Key]) -> IntMultiSet -> IntMultiSet Source #

O(n). Apply a function to each element, and take the union of the results

unionsMap :: (Key -> IntMultiSet) -> IntMultiSet -> IntMultiSet Source #

O(n). Apply a function to each element, and take the union of the results

Monadic

bind :: IntMultiSet -> (Key -> IntMultiSet) -> IntMultiSet Source #

O(n). The monad bind operation, (>>=), for multisets.

join :: MultiSet IntMultiSet -> IntMultiSet Source #

O(n). The monad join operation for multisets.

Fold

fold :: (Key -> b -> b) -> b -> IntMultiSet -> b Source #

O(t). Fold over the elements of a multiset in an unspecified order.

foldOccur :: (Key -> Occur -> b -> b) -> b -> IntMultiSet -> b Source #

O(n). Fold over the elements of a multiset with their occurrences.

Min/Max

findMin :: IntMultiSet -> Key Source #

O(log n). The minimal element of a multiset.

findMax :: IntMultiSet -> Key Source #

O(log n). The maximal element of a multiset.

deleteMin :: IntMultiSet -> IntMultiSet Source #

O(log n). Delete the minimal element.

deleteMax :: IntMultiSet -> IntMultiSet Source #

O(log n). Delete the maximal element.

deleteMinAll :: IntMultiSet -> IntMultiSet Source #

O(log n). Delete all occurrences of the minimal element.

deleteMaxAll :: IntMultiSet -> IntMultiSet Source #

O(log n). Delete all occurrences of the maximal element.

deleteFindMin :: IntMultiSet -> (Key, IntMultiSet) Source #

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

deleteFindMin set = (findMin set, deleteMin set)

deleteFindMax :: IntMultiSet -> (Key, IntMultiSet) Source #

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

deleteFindMax set = (findMax set, deleteMax set)

maxView :: IntMultiSet -> Maybe (Key, IntMultiSet) Source #

O(log n). Retrieves the maximal element of the multiset, and the set stripped from that element fails (in the monad) when passed an empty multiset.

Examples:

>>> maxView $ fromList [100, 100, 200, 300]
Just (300,fromOccurList [(100,2),(200,1)])

minView :: IntMultiSet -> Maybe (Key, IntMultiSet) Source #

O(log n). Retrieves the minimal element of the multiset, and the set stripped from that element Returns Nothing when passed an empty multiset.

Examples:

>>> minView $ fromList [100, 100, 200, 300]
Just (100,fromOccurList [(100,1),(200,1),(300,1)])

Conversion

List

elems :: IntMultiSet -> [Key] Source #

O(t). The elements of a multiset.

distinctElems :: IntMultiSet -> [Key] Source #

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

distinctElems = map fst . toOccurList

toList :: IntMultiSet -> [Key] Source #

O(t). Convert the multiset to a list of elements.

fromList :: [Int] -> IntMultiSet Source #

O(t*min(n,W)). Create a multiset from a list of elements.

Ordered list

toAscList :: IntMultiSet -> [Key] Source #

O(t). Convert the multiset to an ascending list of elements.

fromAscList :: [Int] -> IntMultiSet Source #

O(t). Build a multiset from an ascending list in linear time. The precondition (input list is ascending) is not checked.

fromDistinctAscList :: [Int] -> IntMultiSet Source #

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 :: IntMultiSet -> [(Int, Int)] Source #

O(n). Convert the multiset to a list of element/occurrence pairs.

toAscOccurList :: IntMultiSet -> [(Int, Int)] Source #

O(n). Convert the multiset to an ascending list of element/occurrence pairs.

fromOccurList :: [(Int, Int)] -> IntMultiSet Source #

O(n*min(n,W)). Create a multiset from a list of element/occurrence pairs. Occurrences must be positive. The precondition (all occurrences > 0) is not checked.

fromAscOccurList :: [(Int, Int)] -> IntMultiSet Source #

O(n). Build a multiset from an ascending list of element/occurrence pairs in linear time. Occurrences must be positive. The precondition (input list is ascending, all occurrences > 0) is not checked.

fromDistinctAscOccurList :: [(Int, Int)] -> IntMultiSet Source #

O(n). Build a multiset from an ascending list of elements/occurrence pairs where each elements appears only once. Occurrences must be positive. The precondition (input list is strictly ascending, all occurrences > 0) is not checked.

Map

toMap :: IntMultiSet -> IntMap Int Source #

O(1). Convert a multiset to an IntMap from elements to number of occurrences.

fromMap :: IntMap Int -> IntMultiSet Source #

O(n). Convert an IntMap from elements to occurrences to a multiset.

fromOccurMap :: IntMap Int -> IntMultiSet Source #

O(1). Convert an IntMap from elements to occurrences to a multiset. Assumes that the IntMap contains only values larger than zero. The precondition (all elements > 0) is not checked.

Set

toSet :: IntMultiSet -> IntSet Source #

O(n). Convert a multiset to an IntMap, removing duplicates.

fromSet :: IntSet -> IntMultiSet Source #

O(n). Convert an IntMap to a multiset.

Debugging

showTree :: IntMultiSet -> String Source #

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

showTreeWith :: Bool -> Bool -> IntMultiSet -> String Source #

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