Safe Haskell | None |
---|---|
Language | Haskell2010 |
This modules provides a strict multiset implementation. To avoid collision with Prelude functions, it is recommended to import this module qualified:
import qualified Data.Multiset as Mset
All complexities below use m for the number of distinct elements and n for the total number of elements.
Synopsis
- data Multiset v
- type Group v = (v, Int)
- empty :: Multiset v
- singleton :: v -> Multiset v
- replicate :: Int -> v -> Multiset v
- fromList :: Ord v => [v] -> Multiset v
- fromGroupList :: Ord v => [Group v] -> Multiset v
- fromCountMap :: Ord v => Map v Int -> Multiset v
- null :: Multiset v -> Bool
- size :: Multiset v -> Int
- distinctSize :: Multiset v -> Int
- member :: Ord v => v -> Multiset v -> Bool
- notMember :: Ord v => v -> Multiset v -> Bool
- isSubsetOf :: Ord v => Multiset v -> Multiset v -> Bool
- isProperSubsetOf :: Ord v => Multiset v -> Multiset v -> Bool
- count :: Ord v => v -> Multiset v -> Int
- (!) :: Ord v => Multiset v -> v -> Int
- insert :: Ord v => v -> Multiset v -> Multiset v
- remove :: Ord v => v -> Multiset v -> Multiset v
- removeAll :: Ord v => v -> Multiset v -> Multiset v
- modify :: Ord v => (Int -> Int) -> v -> Multiset v -> Multiset v
- map :: (Ord v1, Ord v2) => (v1 -> v2) -> Multiset v1 -> Multiset v2
- mapCounts :: Ord v => (Int -> Int) -> Multiset v -> Multiset v
- mapGroups :: Ord v => (Group v -> Group v) -> Multiset v -> Multiset v
- filter :: Ord v => (v -> Bool) -> Multiset v -> Multiset v
- filterGroups :: Ord v => (Group v -> Bool) -> Multiset v -> Multiset v
- max :: Ord v => Multiset v -> Multiset v -> Multiset v
- min :: Ord v => Multiset v -> Multiset v -> Multiset v
- difference :: Ord v => Multiset v -> Multiset v -> Multiset v
- unionWith :: Ord v => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v
- intersectionWith :: Ord v => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v
- toSet :: Multiset v -> Set v
- toGroupList :: Multiset v -> [Group v]
- toGrowingGroupList :: Multiset v -> [Group v]
- toShrinkingGroupList :: Multiset v -> [Group v]
- toCountMap :: Multiset v -> Map v Int
- elems :: Multiset v -> [v]
- distinctElems :: Multiset v -> [v]
- maxView :: Ord v => Multiset v -> Maybe (v, Multiset v)
- minView :: Ord v => Multiset v -> Maybe (v, Multiset v)
- mostCommon :: Multiset v -> [(Int, [v])]
Documentation
A strict implementation of a multiset. It is backed by a Map
and inherits
several of its properties and operation's complexities. In particular, the number of elements in
a multiset must not exceed maxBound :: Int
.
Instances
Foldable Multiset Source # | |
Defined in Data.Multiset 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 # elem :: Eq a => a -> Multiset a -> Bool # maximum :: Ord a => Multiset a -> a # minimum :: Ord a => Multiset a -> a # | |
Ord v => IsList (Multiset v) Source # | |
Eq v => Eq (Multiset v) Source # | |
(Data v, Ord v) => Data (Multiset v) Source # | Since: 0.2.1.1 |
Defined in Data.Multiset gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Multiset v -> c (Multiset v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Multiset v) # toConstr :: Multiset v -> Constr # dataTypeOf :: Multiset v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Multiset v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Multiset v)) # gmapT :: (forall b. Data b => b -> b) -> Multiset v -> Multiset v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Multiset v -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Multiset v -> r # gmapQ :: (forall d. Data d => d -> u) -> Multiset v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Multiset v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Multiset v -> m (Multiset v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Multiset v -> m (Multiset v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Multiset v -> m (Multiset v) # | |
Ord v => Ord (Multiset v) Source # | |
(Ord v, Read v) => Read (Multiset v) Source # | |
Show v => Show (Multiset v) Source # | |
Ord v => Semigroup (Multiset v) Source # | |
Ord v => Monoid (Multiset v) Source # | |
Binary v => Binary (Multiset v) Source # | Since: 0.2.1.0 |
type Item (Multiset v) Source # | |
Defined in Data.Multiset |
Construction
replicate :: Int -> v -> Multiset v Source #
O(1) Returns a multiset with the same element repeated. If n is zero or negative, replicate
returns an empty multiset.
fromGroupList :: Ord v => [Group v] -> Multiset v Source #
O(m * log m) Builds a multiset from a list of groups. Counts of duplicate groups are added together and elements with negative total count are omitted.
fromCountMap :: Ord v => Map v Int -> Multiset v Source #
O(m * log m) Builds a multiset from a map. Negative counts are ignored.
Tests and accessors
size :: Multiset v -> Int Source #
O(1) Returns the total number of elements in the multiset. Note that this isn't the number of
distinct elements, see distinctSize
for that.
distinctSize :: Multiset v -> Int Source #
O(1) Returns the number of distinct elements in the multiset.
member :: Ord v => v -> Multiset v -> Bool Source #
O(log m) Checks whether the element is present at least once.
notMember :: Ord v => v -> Multiset v -> Bool Source #
O(log m) Checks whether the element is not present.
isSubsetOf :: Ord v => Multiset v -> Multiset v -> Bool Source #
O(m * log m) Checks whether the first subset is a subset of the second (potentially equal to it).
isProperSubsetOf :: Ord v => Multiset v -> Multiset v -> Bool Source #
O(m * log m) Checks whether the first subset is a strict subset of the second.
count :: Ord v => v -> Multiset v -> Int Source #
O(log m) Returns the number of times the element is present in the multiset, or 0 if absent.
Update
remove :: Ord v => v -> Multiset v -> Multiset v Source #
O(log m) Removes a single element. Does nothing if the element isn't present.
removeAll :: Ord v => v -> Multiset v -> Multiset v Source #
O(log m) Removes all occurrences of a given element.
modify :: Ord v => (Int -> Int) -> v -> Multiset v -> Multiset v Source #
O(log m) Modifies the count of an element. If the resulting element's count is zero or negative, it will be removed.
Maps and filters
map :: (Ord v1, Ord v2) => (v1 -> v2) -> Multiset v1 -> Multiset v2 Source #
Maps on the multiset's values.
mapCounts :: Ord v => (Int -> Int) -> Multiset v -> Multiset v Source #
Maps on the multiset's counts. Groups with resulting non-positive counts will be removed from the final multiset.
mapGroups :: Ord v => (Group v -> Group v) -> Multiset v -> Multiset v Source #
Maps on the multiset's groups. Groups with resulting non-positive counts will be removed from the final multiset.
filterGroups :: Ord v => (Group v -> Bool) -> Multiset v -> Multiset v Source #
Filters a multiset by group.
Combination
max :: Ord v => Multiset v -> Multiset v -> Multiset v Source #
Combines two multisets, returning the max count of each element.
min :: Ord v => Multiset v -> Multiset v -> Multiset v Source #
Combines two multisets, returning the minimum count of each element (or omitting it if the element is present in only one of the two multisets).
difference :: Ord v => Multiset v -> Multiset v -> Multiset v Source #
O(m * log m) Returns the first set minus the second. Resulting negative counts are ignored.
unionWith :: Ord v => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v Source #
Unions two multisets with a generic function. The combining function will be called with a count of 0 when an element is only present in one set.
intersectionWith :: Ord v => (Int -> Int -> Int) -> Multiset v -> Multiset v -> Multiset v Source #
Intersects two multisets with a generic function. The combining function is guaranteed to be called only with positive counts.
Conversions
toGroupList :: Multiset v -> [Group v] Source #
O(m) Converts the multiset to a list of values and associated counts. The groups are in
undefined order; see toGrowingGroupList
and toShrinkingGroupList
for sorted versions.
toGrowingGroupList :: Multiset v -> [Group v] Source #
O(m * log m) Converts the multiset into a list of values and counts, from least common to most.
toShrinkingGroupList :: Multiset v -> [Group v] Source #
O(m * log m) Converts the multiset into a list of values and counts, from most common to least.
toCountMap :: Multiset v -> Map v Int Source #
O(1) Converts the multiset to a map of (positive) counts.
Other
elems :: Multiset v -> [v] Source #
O(n) Returns the multiset's elements as a list where each element is repeated as many times
as its number of occurrences. This is a synonym for toList
.
distinctElems :: Multiset v -> [v] Source #
O(m) Returns a list of the distinct elements in the multiset.
maxView :: Ord v => Multiset v -> Maybe (v, Multiset v) Source #
O(log m) Takes an element of maximum value from the multiset and the remaining multiset, or
Nothing
if the multiset was already empty.
Since: 0.2.1.2
minView :: Ord v => Multiset v -> Maybe (v, Multiset v) Source #
O(log m) Takes an element of minimum value from the multiset and the remaining multiset, or
Nothing
if the multiset was already empty.
Since: 0.2.1.2
mostCommon :: Multiset v -> [(Int, [v])] Source #
O(m) Returns the multiset's elements grouped by count, most common first.