more-containers-0.2.1.1: A few more collections

Safe HaskellNone
LanguageHaskell2010

Data.Multimap

Contents

Description

This modules provides a strict multimap implementation. To avoid collision with Prelude functions, it is recommended to import this module qualified:

import qualified Data.Multiset as Mmap

All complexities below use m for the number of distinct keys and n for the total number of entries in the multimap.

Synopsis

Types

Generic

data Multimap c k v Source #

A map where the same key can be present multiple times.

Instances
Functor c => Functor (Multimap c k) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

fmap :: (a -> b) -> Multimap c k a -> Multimap c k b #

(<$) :: a -> Multimap c k b -> Multimap c k a #

Foldable c => Foldable (Multimap c k) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

fold :: Monoid m => Multimap c k m -> m #

foldMap :: Monoid m => (a -> m) -> Multimap c k a -> m #

foldr :: (a -> b -> b) -> b -> Multimap c k a -> b #

foldr' :: (a -> b -> b) -> b -> Multimap c k a -> b #

foldl :: (b -> a -> b) -> b -> Multimap c k a -> b #

foldl' :: (b -> a -> b) -> b -> Multimap c k a -> b #

foldr1 :: (a -> a -> a) -> Multimap c k a -> a #

foldl1 :: (a -> a -> a) -> Multimap c k a -> a #

toList :: Multimap c k a -> [a] #

null :: Multimap c k a -> Bool #

length :: Multimap c k a -> Int #

elem :: Eq a => a -> Multimap c k a -> Bool #

maximum :: Ord a => Multimap c k a -> a #

minimum :: Ord a => Multimap c k a -> a #

sum :: Num a => Multimap c k a -> a #

product :: Num a => Multimap c k a -> a #

Traversable c => Traversable (Multimap c k) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

traverse :: Applicative f => (a -> f b) -> Multimap c k a -> f (Multimap c k b) #

sequenceA :: Applicative f => Multimap c k (f a) -> f (Multimap c k a) #

mapM :: Monad m => (a -> m b) -> Multimap c k a -> m (Multimap c k b) #

sequence :: Monad m => Multimap c k (m a) -> m (Multimap c k a) #

(Collection c, IsList (c v), Item (c v) ~ v, Ord k) => IsList (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

Associated Types

type Item (Multimap c k v) :: Type #

Methods

fromList :: [Item (Multimap c k v)] -> Multimap c k v #

fromListN :: Int -> [Item (Multimap c k v)] -> Multimap c k v #

toList :: Multimap c k v -> [Item (Multimap c k v)] #

(Eq k, Eq (c v)) => Eq (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

(==) :: Multimap c k v -> Multimap c k v -> Bool #

(/=) :: Multimap c k v -> Multimap c k v -> Bool #

(Typeable c, Typeable v, Data k, Data (c v), Ord k) => Data (Multimap c k v) Source #

Since: 0.2.1.1

Instance details

Defined in Data.Multimap.Generic

Methods

gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> Multimap c k v -> c0 (Multimap c k v) #

gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Multimap c k v) #

toConstr :: Multimap c k v -> Constr #

dataTypeOf :: Multimap c k v -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Multimap c k v)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Multimap c k v)) #

gmapT :: (forall b. Data b => b -> b) -> Multimap c k v -> Multimap c k v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Multimap c k v -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Multimap c k v -> r #

gmapQ :: (forall d. Data d => d -> u) -> Multimap c k v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Multimap c k v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Multimap c k v -> m (Multimap c k v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Multimap c k v -> m (Multimap c k v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Multimap c k v -> m (Multimap c k v) #

(Ord k, Ord (c v)) => Ord (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

compare :: Multimap c k v -> Multimap c k v -> Ordering #

(<) :: Multimap c k v -> Multimap c k v -> Bool #

(<=) :: Multimap c k v -> Multimap c k v -> Bool #

(>) :: Multimap c k v -> Multimap c k v -> Bool #

(>=) :: Multimap c k v -> Multimap c k v -> Bool #

max :: Multimap c k v -> Multimap c k v -> Multimap c k v #

min :: Multimap c k v -> Multimap c k v -> Multimap c k v #

(Ord k, Read k, Read (c v)) => Read (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

(Show k, Show (c v)) => Show (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

showsPrec :: Int -> Multimap c k v -> ShowS #

show :: Multimap c k v -> String #

showList :: [Multimap c k v] -> ShowS #

(Ord k, Semigroup (c v)) => Semigroup (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

(<>) :: Multimap c k v -> Multimap c k v -> Multimap c k v #

sconcat :: NonEmpty (Multimap c k v) -> Multimap c k v #

stimes :: Integral b => b -> Multimap c k v -> Multimap c k v #

(Ord k, Monoid (c v)) => Monoid (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

Methods

mempty :: Multimap c k v #

mappend :: Multimap c k v -> Multimap c k v -> Multimap c k v #

mconcat :: [Multimap c k v] -> Multimap c k v #

(Binary k, Binary (c v)) => Binary (Multimap c k v) Source #

Since: 0.2.1.0

Instance details

Defined in Data.Multimap.Generic

Methods

put :: Multimap c k v -> Put #

get :: Get (Multimap c k v) #

putList :: [Multimap c k v] -> Put #

type Item (Multimap c k v) Source # 
Instance details

Defined in Data.Multimap.Generic

type Item (Multimap c k v) = (k, v)

type Group k cv = (k, cv) Source #

A group of values.

Specific

type ListMultimap = Multimap [] Source #

A multimap with list values. Note that lists do not support efficient appends or sizing, so several multimap operations will have higher complexity than for other collections. If performance is a concern, consider using a SeqMultimap instead.

See Data.Multimap.List for operations specific to this type.

type SeqMultimap = Multimap Seq Source #

A multimap with Seq values.

See Data.Multimap.Seq for operations specific to this type.

type SetMultimap = Multimap Set Source #

A multimap with Set values. This multimap implementation will automatically deduplicate values per key. For example:

let mm = fromList [('a', 1), ('a', 1)] :: SetMultimap Char Int
size mm == 1 -- True

See Data.Multimap.Set for operations specific to this type.

Construction

empty :: Multimap c k v Source #

O(1) Creates an empty multimap.

singleton :: Collection c => k -> v -> Multimap c k v Source #

O(1) Creates a multimap with a single entry.

fromList :: (Collection c, IsList (c v), Item (c v) ~ v, Ord k) => [(k, v)] -> Multimap c k v Source #

O(n * log n) Builds a multimap from a list of key, value tuples. The values are in the same order as in the original list.

fromListWith :: Ord k => ([v] -> c v) -> [(k, v)] -> Multimap c k v Source #

O(n * log n) Transforms a list of entries into a multimap, combining the values for each key into the chosen collection. The values are in the same order as in the original list.

fromGroupList :: (Collection c, Monoid (c v), Ord k) => [Group k (c v)] -> Multimap c k v Source #

O(m) Builds a multimap from already grouped collections.

fromMap :: Collection c => Map k (c v) -> Multimap c k v Source #

O(1) Transforms a map of collections into a multimap.

Tests and accessors

null :: Multimap c k v -> Bool Source #

O(1) Checks whether the multimap is empty.

size :: Collection c => Multimap c k v -> Int Source #

O(m * C) Returns the size of the multimap.

distinctSize :: Multimap c k v -> Int Source #

O(1) Returns the number of distinct keys in the multimap.

member :: Ord k => k -> Multimap c k v -> Bool Source #

O(log m) Checks whether a key is present at least once in a multimap.

notMember :: Ord k => k -> Multimap c k v -> Bool Source #

O(log m) Checks whether a key is absent from a multimap.

find :: (Monoid (c v), Ord k) => k -> Multimap c k v -> c v Source #

O(log m) Returns the collection of values associated with a key.

(!) :: (Monoid (c v), Ord k) => Multimap c k v -> k -> c v Source #

O(log m) Infix version of find.

Modification

prepend :: (Collection c, Monoid (c v), Ord k) => k -> v -> Multimap c k v -> Multimap c k v Source #

O(log m * C) Prepends a value to a key's collection.

prependMany :: (Collection c, Monoid (c v), Ord k) => k -> c v -> Multimap c k v -> Multimap c k v Source #

O(log m * C) Prepends a collection of values to a key's collection.

append :: (Collection c, Monoid (c v), Ord k) => k -> v -> Multimap c k v -> Multimap c k v Source #

O(log m * C) Appends a value to a key's collection.

appendMany :: (Collection c, Monoid (c v), Ord k) => k -> c v -> Multimap c k v -> Multimap c k v Source #

O(log m * C) Appends a collection of values to a key's collection.

deleteMany :: Ord k => k -> Multimap c k v -> Multimap c k v Source #

O(log m) Removes all entries for the given key.

modifyMany :: (Collection c, Monoid (c v), Ord k) => (c v -> c v) -> k -> Multimap c k v -> Multimap c k v Source #

Modifies a key's collection using an arbitrary function. More specifically, this function lifts an operation over a collection of values into a multimap operation.

Sample use to filter even values from a SetMultimap:

   let ms = fromList [('a', 1), ('a', 2)] :: SetMultimap Char Int
   modifyMany (Set.filter even) 'a' ms == fromList [('a', 1)]

modifyManyF :: (Collection c, Monoid (c v), Ord k, Functor f) => (c v -> f (c v)) -> k -> Multimap c k v -> f (Multimap c k v) Source #

Modifies a key's collection using an arbitrary function. This is the applicative version of modifyMany.

Maps and filters

mapGroups :: (Collection c2, Monoid (c2 v2), Ord k2) => (Group k1 (c1 v1) -> Group k2 (c2 v2)) -> Multimap c1 k1 v1 -> Multimap c2 k2 v2 Source #

Maps over the multimap's groups. This method can be used to convert between specific multimaps, for example:

let m1 = fromList [('a', 1), ('a', 1)] :: ListMultimap Char Int
let m2 = mapGroups (fmap Set.fromList) m1 :: SetMultimap Char Int

filter :: (Collection c, Monoid (c v), Ord k) => (v -> Bool) -> Multimap c k v -> Multimap c k v Source #

O(n) Filters multimap entries by value.

filterGroups :: (Collection c, Monoid (c v), Ord k) => (Group k (c v) -> Bool) -> Multimap c k v -> Multimap c k v Source #

O(m) Filters multimap groups. This enables filtering by key and collection.

Conversion

toList :: Collection c => Multimap c k v -> [(k, v)] Source #

O(n) Converts a multimap into its list of entries. Note that this is different from toList which returns the multimap's values (similar to Data.Map).

toGroupList :: Multimap c k v -> [Group k (c v)] Source #

O(m) Converts a multimap into its list of collections.

toMap :: Multimap c k v -> Map k (c v) Source #

O(1) Converts a multimap into a map of collections.

Other

keys :: Collection c => Multimap c k v -> [k] Source #

O(m) Returns a list of the multimap's keys. Each key will be repeated as many times as it is present in the multimap.

keysSet :: Multimap c k v -> Set k Source #

O(m) Returns a set of the multimap's (distinct) keys.

keysMultiset :: (Collection c, Ord k) => Multimap c k v -> Multiset k Source #

O(m * C) Returns a multiset of the map's keys with matching multiplicities.

inverse :: (Collection c, IsList (c k), Item (c k) ~ k, Ord k, Ord v) => Multimap c k v -> Multimap c v k Source #

O(n) Inverts keys and values inside a multimap.

inverseWith :: (Collection c1, Ord k, Ord v) => ([k] -> c2 k) -> Multimap c1 k v -> Multimap c2 v k Source #

O(n) Inverts keys and values inside a multimap, potentially changing the collection type.