| Copyright | (c) Milan Straka 2011 |
|---|---|
| License | BSD-style |
| Maintainer | fox@ucw.cz |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell98 |
Data.HashMap
Contents
Description
Persistent Map based on hashing, which is defined as
dataMapk v =IntMap(Some k v)
is an IntMap indexed by hash values of keys,
containing a value of Some e. That contains either one
( pair or a k, v) with keys of the same hash values.Map k v
The interface of a Map is a suitable subset of IntMap
and can be used as a drop-in replacement of Map.
The complexity of operations is determined by the complexities of
IntMap and Map operations. See the sources of
Map to see which operations from containers package are used.
- data Map k v
- type HashMap k v = Map k v
- (!) :: (Hashable k, Ord k) => Map k a -> k -> a
- (\\) :: Ord k => Map k a -> Map k b -> Map k a
- null :: Map k a -> Bool
- size :: Map k a -> Int
- member :: (Hashable k, Ord k) => k -> Map k a -> Bool
- notMember :: (Hashable k, Ord k) => k -> Map k a -> Bool
- lookup :: (Hashable k, Ord k) => k -> Map k a -> Maybe a
- findWithDefault :: (Hashable k, Ord k) => a -> k -> Map k a -> a
- empty :: Map k a
- singleton :: Hashable k => k -> a -> Map k a
- insert :: (Hashable k, Ord k) => k -> a -> Map k a -> Map k a
- insertWith :: (Hashable k, Ord k) => (a -> a -> a) -> k -> a -> Map k a -> Map k a
- insertWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
- insertLookupWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a)
- delete :: (Hashable k, Ord k) => k -> Map k a -> Map k a
- adjust :: (Hashable k, Ord k) => (a -> a) -> k -> Map k a -> Map k a
- adjustWithKey :: (Hashable k, Ord k) => (k -> a -> a) -> k -> Map k a -> Map k a
- update :: (Hashable k, Ord k) => (a -> Maybe a) -> k -> Map k a -> Map k a
- updateWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
- updateLookupWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a)
- alter :: (Hashable k, Ord k) => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
- union :: Ord k => Map k a -> Map k a -> Map k a
- unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
- unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
- unions :: Ord k => [Map k a] -> Map k a
- unionsWith :: Ord k => (a -> a -> a) -> [Map k a] -> Map k a
- difference :: Ord k => Map k a -> Map k b -> Map k a
- differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a
- differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a
- intersection :: Ord k => Map k a -> Map k b -> Map k a
- intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
- intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
- map :: (a -> b) -> Map k a -> Map k b
- mapWithKey :: (k -> a -> b) -> Map k a -> Map k b
- mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
- mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
- fold :: (a -> b -> b) -> b -> Map k a -> b
- foldWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b
- elems :: Map k a -> [a]
- keys :: Map k a -> [k]
- keysSet :: Ord k => Map k a -> Set k
- assocs :: Map k a -> [(k, a)]
- toList :: Map k a -> [(k, a)]
- fromList :: (Hashable k, Ord k) => [(k, a)] -> Map k a
- fromListWith :: (Hashable k, Ord k) => (a -> a -> a) -> [(k, a)] -> Map k a
- fromListWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> [(k, a)] -> Map k a
- filter :: Ord k => (a -> Bool) -> Map k a -> Map k a
- filterWithKey :: Ord k => (k -> a -> Bool) -> Map k a -> Map k a
- partition :: Ord k => (a -> Bool) -> Map k a -> (Map k a, Map k a)
- partitionWithKey :: Ord k => (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
- mapMaybe :: Ord k => (a -> Maybe b) -> Map k a -> Map k b
- mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> Map k a -> Map k b
- mapEither :: Ord k => (a -> Either b c) -> Map k a -> (Map k b, Map k c)
- mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c)
- isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool
- isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool
- isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool
- isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool
Documentation
The abstract type of a Map. Its interface is a suitable
subset of IntMap.
Instances
| Functor (Map k) Source # | |
| Foldable (Map k) Source # | |
| Traversable (Map k) Source # | |
| (Eq k, Eq v) => Eq (Map k v) Source # | |
| (Data k, Hashable k, Ord k, Data a) => Data (Map k a) Source # | |
| (Ord k, Ord v) => Ord (Map k v) Source # | |
| (Read k, Hashable k, Ord k, Read a) => Read (Map k a) Source # | |
| (Show k, Show a) => Show (Map k a) Source # | |
| Ord k => Semigroup (Map k a) Source # | |
| Ord k => Monoid (Map k a) Source # | |
| (NFData k, NFData v) => NFData (Map k v) Source # | |
type HashMap k v = Map k v Source #
Deprecated: HashMap is deprecated. Please use Map instead.
The HashMap is a type synonym for Map for backward compatibility.
It is deprecated and will be removed in furture releases.
Operators
(!) :: (Hashable k, Ord k) => Map k a -> k -> a Source #
Find the value at a key.
Calls error when the element can not be found.
Query
notMember :: (Hashable k, Ord k) => k -> Map k a -> Bool Source #
Is the key not a member of the map?
lookup :: (Hashable k, Ord k) => k -> Map k a -> Maybe a Source #
Lookup the value at a key in the map.
findWithDefault :: (Hashable k, Ord k) => a -> k -> Map k a -> a Source #
The expression ( returns the value at key
findWithDefault def k map)k or returns def when the key is not an element of the map.
Construction
Insertion
insert :: (Hashable k, Ord k) => k -> a -> Map k a -> Map k a Source #
Insert a new key/value pair in the map. If the key is already present in
the map, the associated value is replaced with the supplied value, i.e.
insert is equivalent to .insertWith const
insertWith :: (Hashable k, Ord k) => (a -> a -> a) -> k -> a -> Map k a -> Map k a Source #
Insert with a combining function. will
insert the pair (key, value) into insertWith f key value mpmp if key does not exist in the map. If
the key does exist, the function will insert f new_value old_value.
insertWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a Source #
Insert with a combining function. will
insert the pair (key, value) into insertWithKey f key value mpmp if key does not exist in the map. If
the key does exist, the function will insert f key new_value old_value.
insertLookupWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) Source #
The expression () is a pair where the
first element is equal to (insertLookupWithKey f k x map) and the second element equal to
(lookup k map).insertWithKey f k x map
Delete/Update
delete :: (Hashable k, Ord k) => k -> Map k a -> Map k a Source #
Delete a key and its value from the map. When the key is not a member of the map, the original map is returned.
adjust :: (Hashable k, Ord k) => (a -> a) -> k -> Map k a -> Map k a Source #
Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.
adjustWithKey :: (Hashable k, Ord k) => (k -> a -> a) -> k -> Map k a -> Map k a Source #
Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.
updateLookupWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a) Source #
Lookup and update. The function returns original value, if it is updated.
This is different behavior than updateLookupWithKey. Returns the
original key value if the map entry is deleted.
Combine
Union
unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a Source #
The union with a combining function.
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a Source #
The union with a combining function.
unionsWith :: Ord k => (a -> a -> a) -> [Map k a] -> Map k a Source #
The union of a list of maps, with a combining operation.
Difference
difference :: Ord k => Map k a -> Map k b -> Map k a Source #
Difference between two maps (based on keys).
differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a Source #
Difference with a combining function.
Intersection
intersection :: Ord k => Map k a -> Map k b -> Map k a Source #
The (left-biased) intersection of two maps (based on keys).
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #
The intersection with a combining function.
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c Source #
The intersection with a combining function.
Traversal
Map
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b Source #
Map a function over all values in the map.
mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #
The function threads an accumulating argument through the map
in unspecified order of keys.mapAccum
mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #
The function threads an accumulating argument through
the map in unspecified order of keys.mapAccumWithKey
Fold
foldWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b Source #
Fold the keys and values in the map, such that .foldWithKey f z ==
foldr (uncurry f) z . toAscList
Conversion
Lists
fromList :: (Hashable k, Ord k) => [(k, a)] -> Map k a Source #
Create a map from a list of key/value pairs.
fromListWith :: (Hashable k, Ord k) => (a -> a -> a) -> [(k, a)] -> Map k a Source #
Create a map from a list of key/value pairs with a combining function.
fromListWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> [(k, a)] -> Map k a Source #
Build a map from a list of key/value pairs with a combining function.
Filter
filter :: Ord k => (a -> Bool) -> Map k a -> Map k a Source #
Filter all values that satisfy some predicate.
filterWithKey :: Ord k => (k -> a -> Bool) -> Map k a -> Map k a Source #
Filter all keys/values that satisfy some predicate.
partition :: Ord k => (a -> Bool) -> Map k a -> (Map k a, Map k a) Source #
Partition the map according to some predicate. The first map contains all elements that satisfy the predicate, the second all elements that fail the predicate.
partitionWithKey :: Ord k => (k -> a -> Bool) -> Map k a -> (Map k a, Map k a) Source #
Partition the map according to some predicate. The first map contains all elements that satisfy the predicate, the second all elements that fail the predicate.
mapMaybe :: Ord k => (a -> Maybe b) -> Map k a -> Map k b Source #
Map values and collect the Just results.
mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> Map k a -> Map k b Source #
Map keys/values and collect the Just results.
Submap
isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool Source #
The expression () returns isSubmapOfBy f m1 m2True if all keys in
m1 are in m2, and when f returns True when applied to their
respective values.
isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool Source #
Is this a proper submap? (ie. a submap but not equal).
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool Source #
Is this a proper submap? (ie. a submap but not equal). The expression
() returns isProperSubmapOfBy f m1 m2True when m1 and m2 are not
equal, all keys in m1 are in m2, and when f returns True when
applied to their respective values.