monoidal-containers-0.1.1.0: Containers with monoidal accumulation

Safe HaskellNone
LanguageHaskell2010

Data.HashMap.Monoidal

Contents

Description

This module provides a HashMap variant which uses the value's Monoid instance to accumulate conflicting entries when merging Maps.

While some functions mirroring those of HashMap are provided here for convenience, more specialized needs will likely want to use either the Newtype or Wrapped instances to manipulate the underlying Map.

Synopsis

Documentation

data MonoidalHashMap k a Source

A HashMap with monoidal accumulation

Instances

(Eq k, Hashable k) => TraversableWithIndex k (MonoidalHashMap k) Source 
(Eq k, Hashable k) => FunctorWithIndex k (MonoidalHashMap k) Source 
(Eq k, Hashable k) => FoldableWithIndex k (MonoidalHashMap k) Source 
Functor (MonoidalHashMap k) Source 
Foldable (MonoidalHashMap k) Source 
Traversable (MonoidalHashMap k) Source 
(Eq k, Hashable k, Monoid a) => IsList (MonoidalHashMap k a) Source 
(Eq k, Eq a) => Eq (MonoidalHashMap k a) Source 
(Eq k, Data k, Data a, Hashable k) => Data (MonoidalHashMap k a) Source 
(Eq k, Read k, Read a, Hashable k) => Read (MonoidalHashMap k a) Source 
(Show k, Show a) => Show (MonoidalHashMap k a) Source 
(Eq k, Hashable k, Monoid a) => Monoid (MonoidalHashMap k a) Source 
(NFData k, NFData a) => NFData (MonoidalHashMap k a) Source 
Wrapped (MonoidalHashMap k a) Source 
AsEmpty (MonoidalHashMap k a) Source 
(Eq k, Hashable k) => Ixed (MonoidalHashMap k a) Source 
(Eq k, Hashable k) => At (MonoidalHashMap k a) Source 
Typeable (* -> * -> *) MonoidalHashMap Source 
Newtype (MonoidalHashMap k a) (HashMap k a) Source 
Each (MonoidalHashMap k a) (MonoidalHashMap k b) a b Source 
type Item (MonoidalHashMap k a) = (k, a) Source 
type Unwrapped (MonoidalHashMap k a) = HashMap k a Source 
type IxValue (MonoidalHashMap k a) = a Source 
type Index (MonoidalHashMap k a) = k Source 

Often-needed functions

singleton :: (Eq k, Hashable k) => k -> a -> MonoidalHashMap k a Source

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

size :: MonoidalHashMap k a -> Int Source

O(1). The number of elements in the map.

member :: (Eq k, Hashable k) => k -> MonoidalHashMap k a -> Bool Source

O(log n). Is the key a member of the map? See also notMember.

notMember :: (Eq k, Hashable k) => k -> MonoidalHashMap k a -> Bool Source

O(log n). Is the key not a member of the map? See also member.

lookup :: (Eq k, Hashable k) => k -> MonoidalHashMap k v -> Maybe v Source

O(log n) Return the value to which the specified key is mapped, or Nothing if this map contains no mapping for the key.

lookupM :: (Eq k, Hashable k, Monoid v) => k -> MonoidalHashMap k v -> v Source

O(log n) Return the value to which the specified key is mapped, or mempty if this map contains no mapping for the key.

elems :: MonoidalHashMap k a -> [a] Source

O(n). Return all elements of the map in the ascending order of their keys. Subject to list fusion.

keys :: MonoidalHashMap k a -> [k] Source

O(n). Return all keys of the map in ascending order. Subject to list fusion.

delete :: (Eq k, Hashable k) => k -> MonoidalHashMap k a -> MonoidalHashMap k a Source

O(log n). Delete a key and its value from the map. When the key is not a member of the map, the original map is returned.

mapKeys :: (Monoid a, Hashable k, Eq k, Hashable k', Eq k') => (k -> k') -> MonoidalHashMap k a -> MonoidalHashMap k' a Source

O(n). Map a function to each key of a map

modify :: (Monoid a, Hashable k, Eq k) => (a -> a) -> k -> MonoidalHashMap k a -> MonoidalHashMap k a Source

O(log n). Modify a value on some key with a function, if value under key doesn't exist -- use mempty.

modifyDef :: (Monoid a, Hashable k, Eq k) => a -> (a -> a) -> k -> MonoidalHashMap k a -> MonoidalHashMap k a Source

O(log n). Modify a value on some key with a function, providing a default value if that key doesn't exist.