planet-mitchell-0.0.0: Planet Mitchell

Safe HaskellSafe
LanguageHaskell2010

MultiSet

Contents

Synopsis

MultiSet

data MultiSet a #

A multiset of values a. The same value can occur multiple times.

Instances
Foldable MultiSet 
Instance details

Defined in Data.MultiSet

Methods

fold :: Monoid m => MultiSet m -> m #

foldMap :: Monoid m => (a -> m) -> MultiSet a -> m #

foldr :: (a -> b -> b) -> b -> MultiSet a -> b #

foldr' :: (a -> b -> b) -> b -> MultiSet a -> b #

foldl :: (b -> a -> b) -> b -> MultiSet a -> b #

foldl' :: (b -> a -> b) -> b -> MultiSet a -> b #

foldr1 :: (a -> a -> a) -> MultiSet a -> a #

foldl1 :: (a -> a -> a) -> MultiSet a -> a #

toList :: MultiSet a -> [a] #

null :: MultiSet a -> Bool #

length :: MultiSet a -> Int #

elem :: Eq a => a -> MultiSet a -> Bool #

maximum :: Ord a => MultiSet a -> a #

minimum :: Ord a => MultiSet a -> a #

sum :: Num a => MultiSet a -> a #

product :: Num a => MultiSet a -> a #

Eq a => Eq (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

(==) :: MultiSet a -> MultiSet a -> Bool #

(/=) :: MultiSet a -> MultiSet a -> Bool #

(Data a, Ord a) => Data (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

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

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

toConstr :: MultiSet a -> Constr #

dataTypeOf :: MultiSet a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

compare :: MultiSet a -> MultiSet a -> Ordering #

(<) :: MultiSet a -> MultiSet a -> Bool #

(<=) :: MultiSet a -> MultiSet a -> Bool #

(>) :: MultiSet a -> MultiSet a -> Bool #

(>=) :: MultiSet a -> MultiSet a -> Bool #

max :: MultiSet a -> MultiSet a -> MultiSet a #

min :: MultiSet a -> MultiSet a -> MultiSet a #

(Read a, Ord a) => Read (MultiSet a) 
Instance details

Defined in Data.MultiSet

Show a => Show (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

showsPrec :: Int -> MultiSet a -> ShowS #

show :: MultiSet a -> String #

showList :: [MultiSet a] -> ShowS #

Ord a => Semigroup (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

(<>) :: MultiSet a -> MultiSet a -> MultiSet a #

sconcat :: NonEmpty (MultiSet a) -> MultiSet a #

stimes :: Integral b => b -> MultiSet a -> MultiSet a #

Ord a => Monoid (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

mempty :: MultiSet a #

mappend :: MultiSet a -> MultiSet a -> MultiSet a #

mconcat :: [MultiSet a] -> MultiSet a #

NFData a => NFData (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

rnf :: MultiSet a -> () #

type Occur = Int #

The number of occurrences of an element

null :: MultiSet a -> Bool #

O(1). Is this the empty multiset?

size :: MultiSet a -> Occur #

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

distinctSize :: MultiSet a -> Occur #

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

member :: Ord a => a -> MultiSet a -> Bool #

O(log n). Is the element in the multiset?

notMember :: Ord a => a -> MultiSet a -> Bool #

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

occur :: Ord a => a -> MultiSet a -> Occur #

O(log n). The number of occurrences of an element in a multiset.

isSubsetOf :: Ord a => MultiSet a -> MultiSet a -> Bool #

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 -> Bool #

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

empty :: MultiSet a #

O(1). The empty mutli set.

singleton :: a -> MultiSet a #

O(1). Create a singleton mutli set.

insert :: Ord a => a -> MultiSet a -> MultiSet a #

O(log n). Insert an element in a multiset.

insertMany :: Ord a => a -> Occur -> MultiSet a -> MultiSet a #

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

Negative numbers remove occurrences of the given element.

delete :: Ord a => a -> MultiSet a -> MultiSet a #

O(log n). Delete a single element from a multiset.

deleteMany :: Ord a => a -> Occur -> MultiSet a -> MultiSet a #

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

Negative numbers add occurrences of the given element.

deleteAll :: Ord a => a -> MultiSet a -> MultiSet a #

O(log n). Delete all occurrences of an element from a multiset.

union :: Ord a => MultiSet a -> MultiSet a -> MultiSet a #

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 :: Ord a => [MultiSet a] -> MultiSet a #

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

maxUnion :: Ord a => MultiSet a -> MultiSet a -> MultiSet a #

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 :: Ord a => MultiSet a -> MultiSet a -> MultiSet a #

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 a #

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 :: (a -> Bool) -> MultiSet a -> MultiSet a #

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

partition :: (a -> Bool) -> MultiSet a -> (MultiSet a, MultiSet a) #

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) #

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) #

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

map :: Ord b => (a -> b) -> MultiSet a -> MultiSet b #

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 b #

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 b => (a -> Maybe b) -> MultiSet a -> MultiSet b #

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

mapEither :: (Ord b, Ord c) => (a -> Either b c) -> MultiSet a -> (MultiSet b, MultiSet c) #

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

concatMap :: Ord b => (a -> [b]) -> MultiSet a -> MultiSet b #

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

unionsMap :: Ord b => (a -> MultiSet b) -> MultiSet a -> MultiSet b #

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

bind :: Ord b => MultiSet a -> (a -> MultiSet b) -> MultiSet b #

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

join :: Ord a => MultiSet (MultiSet a) -> MultiSet a #

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

fold :: (a -> b -> b) -> b -> MultiSet a -> b #

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

foldOccur :: (a -> Occur -> b -> b) -> b -> MultiSet a -> b #

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

findMin :: MultiSet a -> a #

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

findMax :: MultiSet a -> a #

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

deleteMin :: MultiSet a -> MultiSet a #

O(log n). Delete the minimal element.

deleteMax :: MultiSet a -> MultiSet a #

O(log n). Delete the maximal element.

deleteMinAll :: MultiSet a -> MultiSet a #

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

deleteMaxAll :: MultiSet a -> MultiSet a #

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

deleteFindMin :: MultiSet a -> (a, MultiSet a) #

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

deleteFindMin set = (findMin set, deleteMin set)

deleteFindMax :: MultiSet a -> (a, MultiSet a) #

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

deleteFindMax set = (findMax set, deleteMax set)

maxView :: MultiSet a -> Maybe (a, MultiSet a) #

O(log n). Retrieves the maximal element of the multiset, and the set with that element removed. Returns Nothing when passed an empty multiset.

Examples:

>>> maxView $ fromList ['a', 'a', 'b', 'c']
Just ('c',fromOccurList [('a',2),('b',1)])

minView :: MultiSet a -> Maybe (a, MultiSet a) #

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

Examples:

>>> minView $ fromList ['a', 'a', 'b', 'c']
Just ('a',fromOccurList [('a',1),('b',1),('c',1)])

elems :: MultiSet a -> [a] #

O(t). The elements of a multiset.

distinctElems :: MultiSet a -> [a] #

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

distinctElems = map fst . toOccurList

toList :: MultiSet a -> [a] #

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

toAscList :: MultiSet a -> [a] #

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

toOccurList :: MultiSet a -> [(a, Occur)] #

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

toAscOccurList :: MultiSet a -> [(a, Occur)] #

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

fromList :: Ord a => [a] -> MultiSet a #

O(t*log t). Create a multiset from a list of elements.

fromAscList :: Eq a => [a] -> MultiSet a #

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

fromDistinctAscList :: [a] -> MultiSet a #

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.

fromOccurList :: Ord a => [(a, Occur)] -> MultiSet a #

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

fromAscOccurList :: Eq a => [(a, Occur)] -> MultiSet a #

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 :: [(a, Occur)] -> MultiSet a #

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.

toMap :: MultiSet a -> Map a Occur #

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

fromMap :: Map a Occur -> MultiSet a #

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

fromOccurMap :: Map a Occur -> MultiSet a #

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

toSet :: MultiSet a -> Set a #

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

fromSet :: Set a -> MultiSet a #

O(n). Convert a Set to a multiset.