| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
RIO.HashMap
Contents
Description
Strict Map with hashed keys. Import as:
import qualified RIO.HashMap as HM
This module does not export any partial functions. For those, see RIO.HashMap.Partial
Synopsis
- data HashMap k v
- empty :: HashMap k v
- singleton :: Hashable k => k -> v -> HashMap k v
- null :: HashMap k v -> Bool
- size :: HashMap k v -> Int
- member :: (Eq k, Hashable k) => k -> HashMap k a -> Bool
- lookup :: (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
- lookupDefault :: (Eq k, Hashable k) => v -> k -> HashMap k v -> v
- insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v
- insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v
- delete :: (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v
- adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v
- update :: (Eq k, Hashable k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a
- alter :: (Eq k, Hashable k) => (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v
- union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v
- unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
- unionWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
- unions :: (Eq k, Hashable k) => [HashMap k v] -> HashMap k v
- map :: (v1 -> v2) -> HashMap k v1 -> HashMap k v2
- mapWithKey :: (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
- traverseWithKey :: Applicative f => (k -> v1 -> f v2) -> HashMap k v1 -> f (HashMap k v2)
- difference :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v
- differenceWith :: (Eq k, Hashable k) => (v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v
- intersection :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v
- intersectionWith :: (Eq k, Hashable k) => (v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
- intersectionWithKey :: (Eq k, Hashable k) => (k -> v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3
- foldl' :: (a -> v -> a) -> a -> HashMap k v -> a
- foldlWithKey' :: (a -> k -> v -> a) -> a -> HashMap k v -> a
- foldr :: (v -> a -> a) -> a -> HashMap k v -> a
- foldrWithKey :: (k -> v -> a -> a) -> a -> HashMap k v -> a
- filter :: (v -> Bool) -> HashMap k v -> HashMap k v
- filterWithKey :: (k -> v -> Bool) -> HashMap k v -> HashMap k v
- mapMaybe :: (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
- mapMaybeWithKey :: (k -> v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
- keys :: HashMap k v -> [k]
- elems :: HashMap k v -> [v]
- toList :: HashMap k v -> [(k, v)]
- fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v
- fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v
Documentation
A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.
Instances
| Bifoldable HashMap | Since: unordered-containers-0.2.11 | 
| Eq2 HashMap | |
| Ord2 HashMap | |
| Defined in Data.HashMap.Internal | |
| Show2 HashMap | |
| Hashable2 HashMap | |
| Defined in Data.HashMap.Internal | |
| Functor (HashMap k) | |
| Foldable (HashMap k) | |
| Defined in Data.HashMap.Internal Methods fold :: Monoid m => HashMap k m -> m # foldMap :: Monoid m => (a -> m) -> HashMap k a -> m # foldr :: (a -> b -> b) -> b -> HashMap k a -> b # foldr' :: (a -> b -> b) -> b -> HashMap k a -> b # foldl :: (b -> a -> b) -> b -> HashMap k a -> b # foldl' :: (b -> a -> b) -> b -> HashMap k a -> b # foldr1 :: (a -> a -> a) -> HashMap k a -> a # foldl1 :: (a -> a -> a) -> HashMap k a -> a # toList :: HashMap k a -> [a] # length :: HashMap k a -> Int # elem :: Eq a => a -> HashMap k a -> Bool # maximum :: Ord a => HashMap k a -> a # minimum :: Ord a => HashMap k a -> a # | |
| Traversable (HashMap k) | |
| Defined in Data.HashMap.Internal | |
| Eq k => Eq1 (HashMap k) | |
| Ord k => Ord1 (HashMap k) | |
| Defined in Data.HashMap.Internal | |
| (Eq k, Hashable k, Read k) => Read1 (HashMap k) | |
| Defined in Data.HashMap.Internal | |
| Show k => Show1 (HashMap k) | |
| Hashable k => Hashable1 (HashMap k) | |
| Defined in Data.HashMap.Internal | |
| (Eq k, Hashable k) => IsList (HashMap k v) | |
| (Eq k, Eq v) => Eq (HashMap k v) | Note that, in the presence of hash collisions, equal  
 
 
 In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals. | 
| (Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) | |
| Defined in Data.HashMap.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashMap k v -> c (HashMap k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashMap k v) # toConstr :: HashMap k v -> Constr # dataTypeOf :: HashMap k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashMap k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashMap k v)) # gmapT :: (forall b. Data b => b -> b) -> HashMap k v -> HashMap k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQ :: (forall d. Data d => d -> u) -> HashMap k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashMap k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # | |
| (Ord k, Ord v) => Ord (HashMap k v) | The ordering is total and consistent with the  | 
| Defined in Data.HashMap.Internal | |
| (Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
| (Show k, Show v) => Show (HashMap k v) | |
| (Eq k, Hashable k) => Semigroup (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
 | 
| (Eq k, Hashable k) => Monoid (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
 | 
| (NFData k, NFData v) => NFData (HashMap k v) | |
| Defined in Data.HashMap.Internal | |
| (Hashable k, Hashable v) => Hashable (HashMap k v) | |
| Defined in Data.HashMap.Internal | |
| type Item (HashMap k v) | |
| Defined in Data.HashMap.Internal | |
Construction
Basic interface
lookup :: (Eq k, Hashable k) => k -> HashMap k v -> Maybe v #
O(log n) Return the value to which the specified key is mapped,
 or Nothing if this map contains no mapping for the key.
O(log n) Return the value to which the specified key is mapped, or the default value if this map contains no mapping for the key.
DEPRECATED: lookupDefault is deprecated as of version 0.2.11, replaced
 by findWithDefault.
insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v #
O(log n) Associate the specified value with the specified key in this map. If this map previously contained a mapping for the key, the old value is replaced.
insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v -> HashMap k v #
O(log n) Associate the value with the key in this map. If this map previously contained a mapping for the key, the old value is replaced by the result of applying the given function to the new and old value. Example:
insertWith f k v map where f new old = new + old
delete :: (Eq k, Hashable k) => k -> HashMap k v -> HashMap k v #
O(log n) Remove the mapping for the specified key from this map if present.
adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v #
O(log n) Adjust the value tied to a given key in this map only if it is present. Otherwise, leave the map alone.
Combine
Union
union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v #
O(n+m) The union of two maps. If a key occurs in both maps, the mapping from the first will be the mapping in the result.
Examples
>>>union (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])fromList [(1,'a'),(2,'b'),(3,'d')]
unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v #
O(n+m) The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.
unionWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v #
O(n+m) The union of two maps. If a key occurs in both maps, the provided function (first argument) will be used to compute the result.
unions :: (Eq k, Hashable k) => [HashMap k v] -> HashMap k v #
Construct a set containing all elements from a list of sets.
Transformations
map :: (v1 -> v2) -> HashMap k v1 -> HashMap k v2 #
O(n) Transform this map by applying a function to every value.
mapWithKey :: (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2 #
O(n) Transform this map by applying a function to every value.
traverseWithKey :: Applicative f => (k -> v1 -> f v2) -> HashMap k v1 -> f (HashMap k v2) #
O(n) Perform an Applicative action for each key-value pair
 in a HashMap and produce a HashMap of all the results. Each HashMap
 will be strict in all its values.
traverseWithKey f = fmap (mapid) . Data.HashMap.Lazy.traverseWithKeyf
Note: the order in which the actions occur is unspecified. In particular, when the map contains hash collisions, the order in which the actions associated with the keys involved will depend in an unspecified way on their insertion order.
Difference and intersection
difference :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v #
O(n*log m) Difference of two maps. Return elements of the first map not existing in the second.
differenceWith :: (Eq k, Hashable k) => (v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v #
intersection :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v #
O(n*log m) Intersection of two maps. Return elements of the first map for keys existing in the second.
intersectionWith :: (Eq k, Hashable k) => (v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3 #
O(n+m) Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.
intersectionWithKey :: (Eq k, Hashable k) => (k -> v1 -> v2 -> v3) -> HashMap k v1 -> HashMap k v2 -> HashMap k v3 #
O(n+m) Intersection of two maps. If a key occurs in both maps the provided function is used to combine the values from the two maps.
Folds
foldl' :: (a -> v -> a) -> a -> HashMap k v -> a #
O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.
foldlWithKey' :: (a -> k -> v -> a) -> a -> HashMap k v -> a #
O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the left-identity of the operator). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.
foldr :: (v -> a -> a) -> a -> HashMap k v -> a #
O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).
foldrWithKey :: (k -> v -> a -> a) -> a -> HashMap k v -> a #
O(n) Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).
Filter
filter :: (v -> Bool) -> HashMap k v -> HashMap k v #
O(n) Filter this map by retaining only elements which values satisfy a predicate.
filterWithKey :: (k -> v -> Bool) -> HashMap k v -> HashMap k v #
O(n) Filter this map by retaining only elements satisfying a predicate.
mapMaybe :: (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2 #
O(n) Transform this map by applying a function to every value and retaining only some of them.
mapMaybeWithKey :: (k -> v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2 #
O(n) Transform this map by applying a function to every value and retaining only some of them.
Conversions
Lists
toList :: HashMap k v -> [(k, v)] #
O(n) Return a list of this map's elements. The list is produced lazily. The order of its elements is unspecified.
fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v #
O(n*log n) Construct a map with the supplied mappings. If the list contains duplicate mappings, the later mappings take precedence.
fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v #
O(n*log n) Construct a map from a list of elements.  Uses
 the provided function f to merge duplicate entries with
 (f newVal oldVal).
Examples
Given a list xs, create a map with the number of occurrences of each
 element in xs:
let xs = ['a', 'b', 'a']
in fromListWith (+) [ (x, 1) | x <- xs ]
= fromList [('a', 2), ('b', 1)]Given a list of key-value pairs xs :: [(k, v)], group all values by their
 keys and return a HashMap k [v].
let xs = ('a', 1), ('b', 2), ('a', 3)]
in fromListWith (++) [ (k, [v]) | (k, v) <- xs ]
= fromList [('a', [3, 1]), ('b', [2])]Note that the lists in the resulting map contain elements in reverse order from their occurences in the original list.
More generally, duplicate entries are accumulated as follows;
 this matters when f is not commutative or not associative.
fromListWith f [(k, a), (k, b), (k, c), (k, d)] = fromList [(k, f d (f c (f b a)))]