multi-containers-0.2: A few multimap variants.
MaintainerZiyang Liu <free@cofree.io>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Multimap

Description

Multimaps, where values behave like (non empty) lists.

Multimaps whose values behave like sets are in Data.Multimap.Set. Multimaps whose values behave like maps (i.e., two-dimensional tables) are in Data.Multimap.Table.

The implementation is backed by a Map k (NonEmpty a). The differences between Multimap k a and Map k (NonEmpty a) include:

  • lookup (or !) returns a possibly empty list. Unlike regular maps, the ! operator is total for multimaps.
  • Functions like map, adjust, traverse, etc., take functions on individual values (e.g., a -> b) as opposed to, e.g., NonEmpty a -> NonEmpty b.
  • union and unions concatenate the values when there are duplicate keys, rather than being left- or right-biased.
  • The difference function computes list differences for values of keys that exist in both maps.
  • The size function returns the total number of values for all keys in the multimap, not the number of distinct keys. The latter can be obtained by first getting the keysSet or first converting the multimap to a regular map via toMap.

In the following Big-O notations, unless otherwise noted, n denotes the size of the multimap, k denotes the number of distinct keys, and m denotes the maximum number of values associated with a single key.

Synopsis

Multimap type

data Multimap k a Source #

Instances

Instances details
Eq2 Multimap Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Multimap a c -> Multimap b d -> Bool #

Ord2 Multimap Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Multimap a c -> Multimap b d -> Ordering #

Show2 Multimap Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Multimap a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Multimap a b] -> ShowS #

Functor (Multimap k) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

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

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

Foldable (Multimap k) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

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

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

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

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

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

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

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

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

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

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

null :: Multimap k a -> Bool #

length :: Multimap k a -> Int #

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

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

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

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

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

Traversable (Multimap k) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

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

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

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

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

Eq k => Eq1 (Multimap k) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

liftEq :: (a -> b -> Bool) -> Multimap k a -> Multimap k b -> Bool #

Ord k => Ord1 (Multimap k) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Multimap k a -> Multimap k b -> Ordering #

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

Defined in Data.Multimap.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Multimap k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Multimap k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Multimap k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Multimap k a] #

Show k => Show1 (Multimap k) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Multimap k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Multimap k a] -> ShowS #

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

Defined in Data.Multimap.Internal

Methods

(==) :: Multimap k a -> Multimap k a -> Bool #

(/=) :: Multimap k a -> Multimap k a -> Bool #

(Data k, Data a, Ord k) => Data (Multimap k a) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

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

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

toConstr :: Multimap k a -> Constr #

dataTypeOf :: Multimap k a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Multimap.Internal

Methods

compare :: Multimap k a -> Multimap k a -> Ordering #

(<) :: Multimap k a -> Multimap k a -> Bool #

(<=) :: Multimap k a -> Multimap k a -> Bool #

(>) :: Multimap k a -> Multimap k a -> Bool #

(>=) :: Multimap k a -> Multimap k a -> Bool #

max :: Multimap k a -> Multimap k a -> Multimap k a #

min :: Multimap k a -> Multimap k a -> Multimap k a #

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

Defined in Data.Multimap.Internal

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

Defined in Data.Multimap.Internal

Methods

showsPrec :: Int -> Multimap k a -> ShowS #

show :: Multimap k a -> String #

showList :: [Multimap k a] -> ShowS #

Ord k => Semigroup (Multimap k a) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

(<>) :: Multimap k a -> Multimap k a -> Multimap k a #

sconcat :: NonEmpty (Multimap k a) -> Multimap k a #

stimes :: Integral b => b -> Multimap k a -> Multimap k a #

Ord k => Monoid (Multimap k a) Source # 
Instance details

Defined in Data.Multimap.Internal

Methods

mempty :: Multimap k a #

mappend :: Multimap k a -> Multimap k a -> Multimap k a #

mconcat :: [Multimap k a] -> Multimap k a #

Construction

empty :: Multimap k a Source #

O(1). The empty multimap.

size empty === 0

singleton :: k -> a -> Multimap k a Source #

O(1). A multimap with a single element.

singleton 1 'a' === fromList [(1, 'a')]
size (singleton 1 'a') === 1

fromMap :: Map k (NonEmpty a) -> Multimap k a Source #

O(1).

fromMap' :: Map k [a] -> Multimap k a Source #

O(k). A key is retained only if it is associated with a non-empty list of values.

fromMap' (Map.fromList [(1, "ab"), (2, ""), (3, "c")]) === fromList [(1, 'a'), (1, 'b'), (3, 'c')]

From Unordered Lists

fromList :: Ord k => [(k, a)] -> Multimap k a Source #

O(n*log n) where n is the length of the input list. Build a multimap from a list of key/value pairs.

fromList ([] :: [(Int, Char)]) === empty

Insertion

insert :: Ord k => k -> a -> Multimap k a -> Multimap k a Source #

O(log k). If the key exists in the multimap, the new value will be prepended to the list of values for the key.

insert 1 'a' empty === singleton 1 'a'
insert 1 'a' (fromList [(2, 'b'), (2, 'c')]) === fromList [(1, 'a'), (2, 'b'), (2, 'c')]
insert 1 'a' (fromList [(1, 'b'), (2, 'c')]) === fromList [(1, 'a'), (1, 'b'), (2, 'c')]

Deletion/Update

delete :: Ord k => k -> Multimap k a -> Multimap k a Source #

O(log k). Delete a key and all its values from the map.

delete 1 (fromList [(1, 'a'), (1, 'b'), (2, 'c')]) === singleton 2 'c'

deleteWithValue :: (Ord k, Eq a) => k -> a -> Multimap k a -> Multimap k a Source #

O(m*log k). Remove the first occurrence of the value associated with the key, if exists.

deleteWithValue 1 'c' (fromList [(1, 'a'), (1, 'b'), (2, 'c')]) === fromList [(1, 'a'), (1, 'b'), (2, 'c')]
deleteWithValue 1 'c' (fromList [(1, 'a'), (1, 'b'), (2, 'c'), (1, 'c')]) === fromList [(1, 'a'), (1, 'b'), (2, 'c')]
deleteWithValue 1 'c' (fromList [(2, 'c'), (1, 'c')]) === singleton 2 'c'

deleteOne :: Ord k => k -> Multimap k a -> Multimap k a Source #

O(log k). Remove the first value associated with the key. If the key is associated with a single value, the key will be removed from the multimap.

deleteOne 1 (fromList [(1, 'a'), (1, 'b'), (2, 'c')]) === fromList [(1, 'b'), (2, 'c')]
deleteOne 1 (fromList [(2, 'c'), (1, 'c')]) === singleton 2 'c'

adjust :: Ord k => (a -> a) -> k -> Multimap k a -> Multimap k a Source #

O(m*log k), assuming the function a -> a takes O(1). Update values at a specific key, if exists.

adjust ("new " ++) 1 (fromList [(1,"a"),(1,"b"),(2,"c")]) === fromList [(1,"new a"),(1,"new b"),(2,"c")]

adjustWithKey :: Ord k => (k -> a -> a) -> k -> Multimap k a -> Multimap k a Source #

O(m*log k), assuming the function k -> a -> a takes O(1). Update values at a specific key, if exists.

adjustWithKey (\k x -> show k ++ ":new " ++ x) 1 (fromList [(1,"a"),(1,"b"),(2,"c")])
  === fromList [(1,"1:new a"),(1,"1:new b"),(2,"c")]

update :: Ord k => (a -> Maybe a) -> k -> Multimap k a -> Multimap k a Source #

O(m*log k), assuming the function a -> Maybe a takes O(1). The expression (update f k map) updates the values at key k, if exists. If f returns Nothing for a value, the value is deleted.

let f x = if x == "a" then Just "new a" else Nothing in do
  update f 1 (fromList [(1,"a"),(1, "b"),(2,"c")]) === fromList [(1,"new a"),(2, "c")]
  update f 1 (fromList [(1,"b"),(1, "b"),(2,"c")]) === singleton 2 "c"

update' :: Ord k => (NonEmpty a -> [a]) -> k -> Multimap k a -> Multimap k a Source #

O(log k), assuming the function NonEmpty a -> [a] takes O(1). The expression (update f k map) updates the values at key k, if exists. If f returns Nothing, the key is deleted.

update' NonEmpty.tail 1 (fromList [(1, "a"), (1, "b"), (2, "c")]) === fromList [(1, "b"), (2, "c")]
update' NonEmpty.tail 1 (fromList [(1, "a"), (2, "b")]) === singleton 2 "b"

updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Multimap k a -> Multimap k a Source #

O(m*log k), assuming the function k -> a -> Maybe a takes O(1). The expression (updateWithKey f k map) updates the values at key k, if exists. If f returns Nothing for a value, the value is deleted.

let f k x = if x == "a" then Just (show k ++ ":new a") else Nothing in do
  updateWithKey f 1 (fromList [(1,"a"),(1,"b"),(2,"c")]) === fromList [(1,"1:new a"),(2,"c")]
  updateWithKey f 1 (fromList [(1,"b"),(1,"b"),(2,"c")]) === singleton 2 "c"

updateWithKey' :: Ord k => (k -> NonEmpty a -> [a]) -> k -> Multimap k a -> Multimap k a Source #

O(log k), assuming the function k -> NonEmpty a -> [a] takes O(1). The expression (update f k map) updates the values at key k, if exists. If f returns Nothing, the key is deleted.

let f k xs = if NonEmpty.length xs == 1 then (show k : NonEmpty.toList xs) else [] in do
  updateWithKey' f 1 (fromList [(1, "a"), (1, "b"), (2, "c")]) === singleton 2 "c"
  updateWithKey' f 1 (fromList [(1, "a"), (2, "b"), (2, "c")]) === fromList [(1, "1"), (1, "a"), (2, "b"), (2, "c")]

alter :: Ord k => ([a] -> [a]) -> k -> Multimap k a -> Multimap k a Source #

O(log k), assuming the function [a] -> [a] takes O(1). The expression (alter f k map) alters the values at k, if exists.

let (f, g) = (const [], ('c':)) in do
  alter f 1 (fromList [(1, 'a'), (2, 'b')]) === singleton 2 'b'
  alter f 3 (fromList [(1, 'a'), (2, 'b')]) === fromList [(1, 'a'), (2, 'b')]
  alter g 1 (fromList [(1, 'a'), (2, 'b')]) === fromList [(1, 'c'), (1, 'a'), (2, 'b')]
  alter g 3 (fromList [(1, 'a'), (2, 'b')]) === fromList [(1, 'a'), (2, 'b'), (3, 'c')]

alterWithKey :: Ord k => (k -> [a] -> [a]) -> k -> Multimap k a -> Multimap k a Source #

O(log k), assuming the function k -> [a] -> [a] takes O(1). The expression (alterWithKey f k map) alters the values at k, if exists.

let (f, g) = (const (const []), (:) . show) in do
  alterWithKey f 1 (fromList [(1, "a"), (2, "b")]) === singleton 2 "b"
  alterWithKey f 3 (fromList [(1, "a"), (2, "b")]) === fromList [(1, "a"), (2, "b")]
  alterWithKey g 1 (fromList [(1, "a"), (2, "b")]) === fromList [(1, "1"), (1, "a"), (2, "b")]
  alterWithKey g 3 (fromList [(1, "a"), (2, "b")]) === fromList [(1, "a"), (2, "b"), (3, "3")]

Query

Lookup

lookup :: Ord k => k -> Multimap k a -> [a] Source #

O(log k). Lookup the values at a key in the map. It returns an empty list if the key is not in the map.

(!) :: Ord k => Multimap k a -> k -> [a] infixl 9 Source #

O(log k). Lookup the values at a key in the map. It returns an empty list if the key is not in the map.

fromList [(3, 'a'), (5, 'b'), (3, 'c')] ! 3 === "ac"
fromList [(3, 'a'), (5, 'b'), (3, 'c')] ! 2 === []

member :: Ord k => k -> Multimap k a -> Bool Source #

O(log k). Is the key a member of the map?

A key is a member of the map if and only if there is at least one value associated with it.

member 1 (fromList [(1, 'a'), (2, 'b'), (2, 'c')]) === True
member 1 (deleteOne 1 (fromList [(2, 'c'), (1, 'c')])) === False

notMember :: Ord k => k -> Multimap k a -> Bool Source #

O(log k). Is the key not a member of the map?

A key is a member of the map if and only if there is at least one value associated with it.

notMember 1 (fromList [(1, 'a'), (2, 'b'), (2, 'c')]) === False
notMember 1 (deleteOne 1 (fromList [(2, 'c'), (1, 'c')])) === True

Size

null :: Multimap k a -> Bool Source #

O(1). Is the multimap empty?

Data.Multimap.null empty === True
Data.Multimap.null (singleton 1 'a') === False

notNull :: Multimap k a -> Bool Source #

O(1). Is the multimap non-empty?

notNull empty === False
notNull (singleton 1 'a') === True

size :: Multimap k a -> Int Source #

The total number of values for all keys.

size is evaluated lazily. Forcing the size for the first time takes up to O(n) and subsequent forces take O(1).

size empty === 0
size (singleton 1 'a') === 1
size (fromList [(1, 'a'), (2, 'b'), (2, 'c')]) === 3

Combine

Union

union :: Ord k => Multimap k a -> Multimap k a -> Multimap k a Source #

Union two multimaps, concatenating values for duplicate keys.

union (fromList [(1,'a'),(2,'b'),(2,'c')]) (fromList [(1,'d'),(2,'b')])
  === fromList [(1,'a'),(1,'d'),(2,'b'),(2,'c'),(2,'b')]

unions :: (Foldable f, Ord k) => f (Multimap k a) -> Multimap k a Source #

Union a number of multimaps, concatenating values for duplicate keys.

unions [fromList [(1,'a'),(2,'b'),(2,'c')], fromList [(1,'d'),(2,'b')]]
  === fromList [(1,'a'),(1,'d'),(2,'b'),(2,'c'),(2,'b')]

Difference

difference :: (Ord k, Eq a) => Multimap k a -> Multimap k a -> Multimap k a Source #

Difference of two multimaps.

If a key exists in the first multimap but not the second, it remains unchanged in the result. If a key exists in both multimaps, a list difference is performed on their values, i.e., the first occurrence of each value in the second multimap is removed from the first multimap.

difference (fromList [(1,'a'),(2,'b'),(2,'c'),(2,'b')]) (fromList [(1,'d'),(2,'b'),(2,'a')])
  === fromList [(1,'a'), (2,'c'), (2,'b')]

Traversal

Map

map :: (a -> b) -> Multimap k a -> Multimap k b Source #

O(n), assuming the function a -> b takes O(1). Map a function over all values in the map.

Data.Multimap.map (++ "x") (fromList [(1,"a"),(1,"a"),(2,"b")]) === fromList [(1,"ax"),(1,"ax"),(2,"bx")]

mapWithKey :: (k -> a -> b) -> Multimap k a -> Multimap k b Source #

O(n), assuming the function k -> a -> b takes O(1). Map a function over all key/value pairs in the map.

mapWithKey (\k x -> show k ++ ":" ++ x) (fromList [(1,"a"),(1,"a"),(2,"b")]) === fromList [(1,"1:a"),(1,"1:a"),(2,"2:b")]

traverseWithKey :: Applicative t => (k -> a -> t b) -> Multimap k a -> t (Multimap k b) Source #

Traverse key/value pairs and collect the results.

let f k a = if odd k then Just (succ a) else Nothing in do
  traverseWithKey f (fromList [(1, 'a'), (1, 'b'), (3, 'b'), (3, 'c')]) === Just (fromList [(1, 'b'), (1, 'c'), (3, 'c'), (3, 'd')])
  traverseWithKey f (fromList [(1, 'a'), (1, 'b'), (2, 'b')]) === Nothing

traverseMaybeWithKey :: Applicative t => (k -> a -> t (Maybe b)) -> Multimap k a -> t (Multimap k b) Source #

Traverse key/value pairs and collect the Just results.

Folds

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

O(n). Fold the values in the map using the given right-associative binary operator.

Data.Multimap.foldr ((+) . length) 0 (fromList [(1, "hello"), (1, "world"), (2, "!")]) === 11

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

O(n). Fold the values in the map using the given left-associative binary operator.

Data.Multimap.foldl (\len -> (+ len) . length) 0 (fromList [(1, "hello"), (1, "world"), (2, "!")]) === 11

foldrWithKey :: (k -> a -> b -> b) -> b -> Multimap k a -> b Source #

O(n). Fold the key/value pairs in the map using the given right-associative binary operator.

foldrWithKey (\k a len -> length (show k) + length a + len) 0 (fromList [(1, "hello"), (1, "world"), (20, "!")]) === 15

foldlWithKey :: (a -> k -> b -> a) -> a -> Multimap k b -> a Source #

O(n). Fold the key/value pairs in the map using the given left-associative binary operator.

foldlWithKey (\len k a -> length (show k) + length a + len) 0 (fromList [(1, "hello"), (1, "world"), (20, "!")]) === 15

foldMapWithKey :: Monoid m => (k -> a -> m) -> Multimap k a -> m Source #

O(n). Fold the key/value pairs in the map using the given monoid.

foldMapWithKey (\k x -> show k ++ ":" ++ x) (fromList [(1, "a"), (1, "a"), (2, "b")]) === "1:a1:a2:b"

Strict Folds

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

O(n). A strict version of foldr. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Data.Multimap.foldr' ((+) . length) 0 (fromList [(1, "hello"), (1, "world"), (2, "!")]) === 11

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

O(n). A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

Data.Multimap.foldl' (\len -> (+ len) . length) 0 (fromList [(1, "hello"), (1, "world"), (2, "!")]) === 11

foldrWithKey' :: (k -> a -> b -> b) -> b -> Multimap k a -> b Source #

O(n). A strict version of foldrWithKey. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldrWithKey' (\k a len -> length (show k) + length a + len) 0 (fromList [(1, "hello"), (1, "world"), (20, "!")]) === 15

foldlWithKey' :: (a -> k -> b -> a) -> a -> Multimap k b -> a Source #

O(n). A strict version of foldlWithKey. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

foldlWithKey' (\len k a -> length (show k) + length a + len) 0 (fromList [(1, "hello"), (1, "world"), (20, "!")]) === 15

Conversion

elems :: Multimap k a -> [a] Source #

O(n). Return all elements of the multimap in ascending order of their keys.

elems (fromList [(2, 'a'), (1, 'b'), (3, 'c'), (1, 'b')]) === "bbac"
elems (empty :: Multimap Int Char) === []

keys :: Multimap k a -> [k] Source #

O(k). Return all keys of the multimap in ascending order.

keys (fromList [(2, 'a'), (1, 'b'), (3, 'c'), (1, 'b')]) === [1,2,3]
keys (empty :: Multimap Int Char) === []

assocs :: Multimap k a -> [(k, a)] Source #

An alias for toAscList.

assocs (fromList [(2,'a'),(1,'b'),(3,'c'),(1,'a')]) === [(1,'b'),(1,'a'),(2,'a'),(3,'c')]

keysSet :: Multimap k a -> Set k Source #

O(k). The set of all keys of the multimap.

keysSet (fromList [(2, 'a'), (1, 'b'), (3, 'c'), (1, 'b')]) === Set.fromList [1,2,3]
keysSet (empty :: Multimap Int Char) === Set.empty

Lists

toList :: Multimap k a -> [(k, a)] Source #

Convert the multimap into a list of key/value pairs.

toList (fromList [(2,'a'),(1,'b'),(3,'c'),(1,'a')]) === [(1,'b'),(1,'a'),(2,'a'),(3,'c')]

Ordered lists

toAscList :: Multimap k a -> [(k, a)] Source #

Convert the multimap into a list of key/value pairs in ascending order of keys.

toAscList (fromList [(2,'a'),(1,'b'),(3,'c'),(1,'a')]) === [(1,'b'),(1,'a'),(2,'a'),(3,'c')]

toDescList :: Multimap k a -> [(k, a)] Source #

Convert the multimap into a list of key/value pairs in descending order of keys.

toDescList (fromList [(2,'a'),(1,'b'),(3,'c'),(1,'a')]) === [(3,'c'),(2,'a'),(1,'b'),(1,'a')]

toAscListBF :: Multimap k a -> [(k, a)] Source #

Convert the multimap into a list of key/value pairs, in a breadth-first manner, in ascending order of keys.

toAscListBF (fromList [("Foo",1),("Foo",2),("Foo",3),("Bar",4),("Bar",5),("Baz",6)])
  === [("Bar",4),("Baz",6),("Foo",1),("Bar",5),("Foo",2),("Foo",3)]

toDescListBF :: Multimap k a -> [(k, a)] Source #

Convert the multimap into a list of key/value pairs, in a breadth-first manner, in descending order of keys.

toDescListBF (fromList [("Foo",1),("Foo",2),("Foo",3),("Bar",4),("Bar",5),("Baz",6)])
  === [("Foo",1),("Baz",6),("Bar",4),("Foo",2),("Bar",5),("Foo",3)]

Maps

toMap :: Multimap k a -> Map k (NonEmpty a) Source #

O(1). Convert the multimap into a regular map.

SetMultimaps

fromSetMultimapAsc :: SetMultimap k a -> Multimap k a Source #

Convert a SetMultimap to a Multimap where the values of each key are in ascending order.

fromSetMultimapAsc (Data.Multimap.Set.fromList [(1,'a'),(1,'b'),(2,'c')]) === Data.Multimap.fromList [(1,'a'),(1,'b'),(2,'c')]

fromSetMultimapDesc :: SetMultimap k a -> Multimap k a Source #

Convert a SetMultimap to a Multimap where the values of each key are in descending order.

fromSetMultimapDesc (Data.Multimap.Set.fromList [(1,'a'),(1,'b'),(2,'c')]) === Data.Multimap.fromList [(1,'b'),(1,'a'),(2,'c')]

toSetMultimap :: Ord a => Multimap k a -> SetMultimap k a Source #

Convert a Multimap to a SetMultimap.

toSetMultimap (Data.Multimap.fromList [(1,'a'),(1,'b'),(2,'c')]) === Data.Multimap.Set.fromList [(1,'a'),(1,'b'),(2,'c')]

Filter

filter :: (a -> Bool) -> Multimap k a -> Multimap k a Source #

O(n), assuming the predicate function takes O(1). Retain all values that satisfy the predicate.

Data.Multimap.filter (> 'a') (fromList [(1,'a'),(1,'b'),(2,'a')]) === singleton 1 'b'
Data.Multimap.filter (< 'a') (fromList [(1,'a'),(1,'b'),(2,'a')]) === empty

filterWithKey :: (k -> a -> Bool) -> Multimap k a -> Multimap k a Source #

O(n), assuming the predicate function takes O(1). Retain all key/value pairs that satisfy the predicate.

filterWithKey (\k a -> even k && a > 'a') (fromList [(1,'a'),(1,'b'),(2,'a'),(2,'b')]) === singleton 2 'b'

filterKey :: (k -> Bool) -> Multimap k a -> Multimap k a Source #

O(k), assuming the predicate function takes O(1). Retain all keys that satisfy the predicate.

filterKey even (fromList [(1,'a'),(1,'b'),(2,'a')]) === singleton 2 'a'

filterM :: (Ord k, Applicative t) => (a -> t Bool) -> Multimap k a -> t (Multimap k a) Source #

Generalized filter.

let f a | a > 'b' = Just True
        | a < 'b' = Just False
        | a == 'b' = Nothing
 in do
   filterM f (fromList [(1,'a'),(1,'b'),(2,'a'),(2,'c')]) === Nothing
   filterM f (fromList [(1,'a'),(1,'c'),(2,'a'),(2,'c')]) === Just (fromList [(1,'c'),(2,'c')])

filterWithKeyM :: (Ord k, Applicative t) => (k -> a -> t Bool) -> Multimap k a -> t (Multimap k a) Source #

Generalized filterWithKey.

let f k a | even k && a > 'b' = Just True
          | odd k && a < 'b' = Just False
          | otherwise = Nothing
 in do
   filterWithKeyM f (fromList [(1,'a'),(1,'c'),(2,'a'),(2,'c')]) === Nothing
   filterWithKeyM f (fromList [(1,'a'),(1,'a'),(2,'c'),(2,'c')]) === Just (fromList [(2,'c'),(2,'c')])

mapMaybe :: (a -> Maybe b) -> Multimap k a -> Multimap k b Source #

O(n), assuming the function a -> Maybe b takes O(1). Map values and collect the Just results.

mapMaybe (\a -> if a == "a" then Just "new a" else Nothing) (fromList [(1,"a"),(1,"b"),(2,"a"),(2,"c")])
  === fromList [(1,"new a"),(2,"new a")]

mapMaybeWithKey :: (k -> a -> Maybe b) -> Multimap k a -> Multimap k b Source #

O(n), assuming the function k -> a -> Maybe b takes O(1). Map key/value pairs and collect the Just results.

mapMaybeWithKey (\k a -> if k > 1 && a == "a" then Just "new a" else Nothing) (fromList [(1,"a"),(1,"b"),(2,"a"),(2,"c")])
  === singleton 2 "new a"

mapEither :: (a -> Either b c) -> Multimap k a -> (Multimap k b, Multimap k c) Source #

O(n), assuming the function a -> Either b c takes O(1). Map values and separate the Left and Right results.

mapEither (\a -> if a < 'b' then Left a else Right a) (fromList [(1,'a'),(1,'c'),(2,'a'),(2,'c')])
  === (fromList [(1,'a'),(2,'a')],fromList [(1,'c'),(2,'c')])

mapEitherWithKey :: (k -> a -> Either b c) -> Multimap k a -> (Multimap k b, Multimap k c) Source #

O(n), assuming the function k -> a -> Either b c takes O(1). Map key/value pairs and separate the Left and Right results.

mapEitherWithKey (\k a -> if even k && a < 'b' then Left a else Right a) (fromList [(1,'a'),(1,'c'),(2,'a'),(2,'c')])
  === (fromList [(2,'a')],fromList [(1,'a'),(1,'c'),(2,'c')])

Min/Max

lookupMin :: Multimap k a -> Maybe (k, NonEmpty a) Source #

O(log n). Return the smallest key and the associated values. Returns Nothing if the map is empty.

lookupMin (fromList [(1,'a'),(1,'c'),(2,'c')]) === Just (1, NonEmpty.fromList "ac")
lookupMin (empty :: Multimap Int Char) === Nothing

lookupMax :: Multimap k a -> Maybe (k, NonEmpty a) Source #

O(log n). Return the largest key and the associated values. Returns Nothing if the map is empty.

lookupMax (fromList [(1,'a'),(1,'c'),(2,'c')]) === Just (2, NonEmpty.fromList "c")
lookupMax (empty :: Multimap Int Char) === Nothing

lookupLT :: Ord k => k -> Multimap k a -> Maybe (k, NonEmpty a) Source #

O(log n). Return the largest key smaller than the given one, and the associated values, if exist.

lookupLT 1 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Nothing
lookupLT 4 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Just (3, NonEmpty.fromList "bc")

lookupGT :: Ord k => k -> Multimap k a -> Maybe (k, NonEmpty a) Source #

O(log n). Return the smallest key larger than the given one, and the associated values, if exist.

lookupGT 5 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Nothing
lookupGT 2 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Just (3, NonEmpty.fromList "bc")

lookupLE :: Ord k => k -> Multimap k a -> Maybe (k, NonEmpty a) Source #

O(log n). Return the largest key smaller than or equal to the given one, and the associated values, if exist.

lookupLE 0 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Nothing
lookupLE 1 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Just (1, NonEmpty.fromList "a")
lookupLE 4 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Just (3, NonEmpty.fromList "bc")

lookupGE :: Ord k => k -> Multimap k a -> Maybe (k, NonEmpty a) Source #

O(log n). Return the smallest key larger than or equal to the given one, and the associated values, if exist.

lookupGE 6 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Nothing
lookupGE 5 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Just (5, NonEmpty.fromList "c")
lookupGE 2 (fromList [(1,'a'),(3,'b'),(3,'c'),(5,'c')]) === Just (3, NonEmpty.fromList "bc")