more-containers-0.1.2.0: A few more collections

Safe HaskellSafe
LanguageHaskell2010

Data.Multiset

Contents

Description

A simple multiset implementation

All complexities below use m for the number of distinct elements and n for the total number of elements.

Synopsis

Documentation

data Multiset v Source #

A multiset

Instances
Foldable Multiset Source # 
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 #

Collection Multiset Source # 
Instance details

Defined in Data.Multimap.Collection

Eq v => Eq (Multiset v) Source # 
Instance details

Defined in Data.Multiset

Methods

(==) :: Multiset v -> Multiset v -> Bool #

(/=) :: Multiset v -> Multiset v -> Bool #

Ord v => Ord (Multiset v) Source # 
Instance details

Defined in Data.Multiset

Methods

compare :: Multiset v -> Multiset v -> Ordering #

(<) :: Multiset v -> Multiset v -> Bool #

(<=) :: Multiset v -> Multiset v -> Bool #

(>) :: Multiset v -> Multiset v -> Bool #

(>=) :: Multiset v -> Multiset v -> Bool #

max :: Multiset v -> Multiset v -> Multiset v #

min :: Multiset v -> Multiset v -> Multiset v #

(Ord v, Read v) => Read (Multiset v) Source # 
Instance details

Defined in Data.Multiset

Show v => Show (Multiset v) Source # 
Instance details

Defined in Data.Multiset

Methods

showsPrec :: Int -> Multiset v -> ShowS #

show :: Multiset v -> String #

showList :: [Multiset v] -> ShowS #

Ord v => Semigroup (Multiset v) Source # 
Instance details

Defined in Data.Multiset

Methods

(<>) :: Multiset v -> Multiset v -> Multiset v #

sconcat :: NonEmpty (Multiset v) -> Multiset v #

stimes :: Integral b => b -> Multiset v -> Multiset v #

Ord v => Monoid (Multiset v) Source # 
Instance details

Defined in Data.Multiset

Methods

mempty :: Multiset v #

mappend :: Multiset v -> Multiset v -> Multiset v #

mconcat :: [Multiset v] -> Multiset v #

Tests

null :: Multiset v -> Bool Source #

O(1) Whether a multiset is empty.

size :: Multiset v -> Int Source #

The total number of elements in the multiset.

O(m) Note that this isn't the number of distinct elements, distinctSize provides it.

distinctSize :: Multiset v -> Int Source #

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

Construction

empty :: Multiset v Source #

O(1) The empty multiset.

singleton :: v -> Multiset v Source #

O(1) A multiset with a single element.

fromMap :: (Integral a, Ord v) => Map v a -> Multiset v Source #

O(m * log m) Build a multiset from a map.

Negative counts are ignored; see fromMap' for a stricter version.

fromMap' :: (Integral a, Ord v) => Map v a -> Maybe (Multiset v) Source #

O(m * log m) Build a multiset from a map.

If at least one of the counts is negative, this method will return Nothing.

fromList :: Ord v => [v] -> Multiset v Source #

O(n * log n) Build a multiset from a list.

fromCountsList :: (Integral a, Ord v) => [(v, a)] -> Multiset v Source #

O(m * log m) Build a multiset from a list of counts.

Counts of duplicate entries are added together.

fromCountsList' :: (Integral a, Ord v) => [(v, a)] -> Maybe (Multiset v) Source #

O(m * log m) Build a multiset from a list of counts.

Counts of duplicate entries are added together. Returns Nothing if the total count for any element is negative.

Accessors

member :: Ord v => v -> Multiset v -> Bool Source #

O(log m) Whether the element is present at least once.

notMember :: Ord v => v -> Multiset v -> Bool Source #

O(log m) Whether the element is not present.

(!) :: Ord v => Multiset v -> v -> Int Source #

O(1) Infix version of count.

count :: Ord v => v -> Multiset v -> Int Source #

O(1) The number of times the element is present in the multiset.

0 if absent.

Update

incr :: Ord v => Int -> v -> Multiset v -> Multiset v Source #

O(log m) Increment the count of element.

The increment can be negative (removing elements). Resulting negative counts are considered 0 (see incr' for a stricter implementation)..

incr' :: Ord v => Int -> v -> Multiset v -> Maybe (Multiset v) Source #

O(log m) Increment the count of element, enforcing that any returned multiset has non-negative counts. If a resulting count would have become negative, this function returns Nothing

insert :: Ord v => v -> Multiset v -> Multiset v Source #

O(log m) Insert a single element.

remove :: Ord v => v -> Multiset v -> Multiset v Source #

O(log m) Remove a single element. Does nothing if the element isn't present.

remove' :: Ord v => v -> Multiset v -> Maybe (Multiset v) Source #

Remove a single element. Returns Nothing if the element wasn't already in.

filter :: Ord v => (v -> Bool) -> Multiset v -> Multiset v Source #

Standard value filter.

filterCounts :: Ord v => (Int -> Bool) -> Multiset v -> Multiset v Source #

Filter on counts.

map :: (Ord v1, Ord v2) => (v1 -> v2) -> Multiset v1 -> Multiset v2 Source #

Map on the multiset's values.

mapCounts :: Ord v => (Int -> Int) -> Multiset v -> Multiset v Source #

Map on the multiset's counts.

Combination

max :: Ord v => Multiset v -> Multiset v -> Multiset v Source #

Convenience methods to get the max of two multisets.

min :: Ord v => Multiset v -> Multiset v -> Multiset v Source #

Convenience methods to get the min of two multisets.

sum :: Ord v => Multiset v -> Multiset v -> Multiset v Source #

Convenience methods to get the sum of two multisets.

unionWith :: Ord v => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v Source #

Generic union method.

difference :: Ord v => Multiset v -> Multiset v -> Multiset v Source #

The first set minus the second. Resulting negative counts are ignored.

intersectionWith :: Ord v => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v Source #

Generic intersection method.

toList :: Multiset v -> [v] Source #

Convert the multiset to a list; elements will be repeated according to their count.

toCountsList :: Multiset v -> [(v, Int)] Source #

Convert the multiset to a list of values and associated counts. The entries are in undefined order; see toAscCountsList and toDescCountsList for sorted versions.

toAscCountsList :: Multiset v -> [(v, Int)] Source #

Convert the multiset into a list of values and counts, from least common to most.

toDescCountsList :: Multiset v -> [(v, Int)] Source #

Convert the multiset into a list of values and counts, from most common to least.

Other

elems :: Multiset v -> Set v Source #

O(m) The Set of all elements in the multiset.

mostCommon :: Multiset v -> [v] Source #

O(m) The list of all elements with the highest count.