Portability | portable |
---|---|
Stability | provisional |
Maintainer | fox@ucw.cz |
Persistent HashMap
, which is defined as
dataHashMap
k v =Data.IntMap.IntMap
(Data.Map.Map
k v)
is an Data.IntMap.IntMap
indexed by hash values of keys,
containing a map
with keys of the same hash values.
Data.Map.Map
k v
The interface of a HashMap
is a suitable subset of Data.IntMap.IntMap
.
The complexity of operations is determined by the complexities of
Data.IntMap.IntMap
and Data.Map.Map
operations. See the sources of
HashMap
to see which operations from containers
package are used.
- data HashMap k v
- (!) :: (Hashable k, Ord k) => HashMap k a -> k -> a
- (\\) :: Ord k => HashMap k a -> HashMap k b -> HashMap k a
- null :: HashMap k a -> Bool
- size :: HashMap k a -> Int
- member :: (Hashable k, Ord k) => k -> HashMap k a -> Bool
- notMember :: (Hashable k, Ord k) => k -> HashMap k a -> Bool
- lookup :: (Hashable k, Ord k) => k -> HashMap k a -> Maybe a
- findWithDefault :: (Hashable k, Ord k) => a -> k -> HashMap k a -> a
- empty :: HashMap k a
- singleton :: Hashable k => k -> a -> HashMap k a
- insert :: (Hashable k, Ord k) => k -> a -> HashMap k a -> HashMap k a
- insertWith :: (Hashable k, Ord k) => (a -> a -> a) -> k -> a -> HashMap k a -> HashMap k a
- insertWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> HashMap k a -> HashMap k a
- insertLookupWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> k -> a -> HashMap k a -> (Maybe a, HashMap k a)
- delete :: (Hashable k, Ord k) => k -> HashMap k a -> HashMap k a
- adjust :: (Hashable k, Ord k) => (a -> a) -> k -> HashMap k a -> HashMap k a
- adjustWithKey :: (Hashable k, Ord k) => (k -> a -> a) -> k -> HashMap k a -> HashMap k a
- update :: (Hashable k, Ord k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a
- updateWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> HashMap k a -> HashMap k a
- updateLookupWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> HashMap k a -> (Maybe a, HashMap k a)
- alter :: (Hashable k, Ord k) => (Maybe a -> Maybe a) -> k -> HashMap k a -> HashMap k a
- union :: Ord k => HashMap k a -> HashMap k a -> HashMap k a
- unionWith :: Ord k => (a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a
- unionWithKey :: Ord k => (k -> a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k a
- unions :: Ord k => [HashMap k a] -> HashMap k a
- unionsWith :: Ord k => (a -> a -> a) -> [HashMap k a] -> HashMap k a
- difference :: Ord k => HashMap k a -> HashMap k b -> HashMap k a
- differenceWith :: Ord k => (a -> b -> Maybe a) -> HashMap k a -> HashMap k b -> HashMap k a
- differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> HashMap k a -> HashMap k b -> HashMap k a
- intersection :: Ord k => HashMap k a -> HashMap k b -> HashMap k a
- intersectionWith :: Ord k => (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c
- intersectionWithKey :: Ord k => (k -> a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c
- map :: (a -> b) -> HashMap k a -> HashMap k b
- mapWithKey :: (k -> a -> b) -> HashMap k a -> HashMap k b
- mapAccum :: (a -> b -> (a, c)) -> a -> HashMap k b -> (a, HashMap k c)
- mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> HashMap k b -> (a, HashMap k c)
- fold :: (a -> b -> b) -> b -> HashMap k a -> b
- foldWithKey :: (k -> a -> b -> b) -> b -> HashMap k a -> b
- elems :: HashMap k a -> [a]
- keys :: HashMap k a -> [k]
- keysSet :: Ord k => HashMap k a -> Set k
- assocs :: HashMap k a -> [(k, a)]
- toList :: HashMap k a -> [(k, a)]
- fromList :: (Hashable k, Ord k) => [(k, a)] -> HashMap k a
- fromListWith :: (Hashable k, Ord k) => (a -> a -> a) -> [(k, a)] -> HashMap k a
- fromListWithKey :: (Hashable k, Ord k) => (k -> a -> a -> a) -> [(k, a)] -> HashMap k a
- filter :: Ord k => (a -> Bool) -> HashMap k a -> HashMap k a
- filterWithKey :: Ord k => (k -> a -> Bool) -> HashMap k a -> HashMap k a
- partition :: Ord k => (a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a)
- partitionWithKey :: Ord k => (k -> a -> Bool) -> HashMap k a -> (HashMap k a, HashMap k a)
- mapMaybe :: Ord k => (a -> Maybe b) -> HashMap k a -> HashMap k b
- mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> HashMap k a -> HashMap k b
- mapEither :: Ord k => (a -> Either b c) -> HashMap k a -> (HashMap k b, HashMap k c)
- mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> HashMap k a -> (HashMap k b, HashMap k c)
- isSubmapOf :: (Ord k, Eq a) => HashMap k a -> HashMap k a -> Bool
- isSubmapOfBy :: Ord k => (a -> b -> Bool) -> HashMap k a -> HashMap k b -> Bool
- isProperSubmapOf :: (Ord k, Eq a) => HashMap k a -> HashMap k a -> Bool
- isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> HashMap k a -> HashMap k b -> Bool
Documentation
The abstract type of a HashMap
. Its interface is a suitable
subset of Data.IntMap.IntMap
.
Typeable2 HashMap | |
Functor (HashMap k) | |
Foldable (HashMap k) | |
Traversable (HashMap k) | |
(Eq k, Eq v) => Eq (HashMap k v) | |
(Data k, Hashable k, Ord k, Data a) => Data (HashMap k a) | |
(Ord k, Ord v) => Ord (HashMap k v) | |
(Read k, Hashable k, Ord k, Read a) => Read (HashMap k a) | |
(Show k, Show a) => Show (HashMap k a) | |
Ord k => Monoid (HashMap k a) |
Operators
(!) :: (Hashable k, Ord k) => HashMap k a -> k -> aSource
Find the value at a key.
Calls error
when the element can not be found.
Query
notMember :: (Hashable k, Ord k) => k -> HashMap k a -> BoolSource
Is the key not a member of the map?
lookup :: (Hashable k, Ord k) => k -> HashMap k a -> Maybe aSource
Lookup the value at a key in the map.
findWithDefault :: (Hashable k, Ord k) => a -> k -> HashMap k a -> aSource
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 -> HashMap k a -> HashMap k aSource
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 -> HashMap k a -> HashMap k aSource
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 -> HashMap k a -> HashMap k aSource
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 -> HashMap k a -> (Maybe a, HashMap 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 -> HashMap k a -> HashMap k aSource
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 -> HashMap k a -> HashMap k aSource
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 -> HashMap k a -> HashMap k aSource
Adjust a value at a specific key. When the key is not a member of the map, the original map is returned.
updateWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> HashMap k a -> HashMap k aSource
updateLookupWithKey :: (Hashable k, Ord k) => (k -> a -> Maybe a) -> k -> HashMap k a -> (Maybe a, HashMap k a)Source
Lookup and update. The function returns original value, if it is updated.
This is different behavior than Data.Map.updateLookupWithKey
. Returns the
original key value if the map entry is deleted.
Combine
Union
unionWith :: Ord k => (a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k aSource
The union with a combining function.
unionWithKey :: Ord k => (k -> a -> a -> a) -> HashMap k a -> HashMap k a -> HashMap k aSource
The union with a combining function.
unionsWith :: Ord k => (a -> a -> a) -> [HashMap k a] -> HashMap k aSource
The union of a list of maps, with a combining operation.
Difference
difference :: Ord k => HashMap k a -> HashMap k b -> HashMap k aSource
Difference between two maps (based on keys).
differenceWith :: Ord k => (a -> b -> Maybe a) -> HashMap k a -> HashMap k b -> HashMap k aSource
Difference with a combining function.
differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> HashMap k a -> HashMap k b -> HashMap k aSource
Intersection
intersection :: Ord k => HashMap k a -> HashMap k b -> HashMap k aSource
The (left-biased) intersection of two maps (based on keys).
intersectionWith :: Ord k => (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k cSource
The intersection with a combining function.
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k cSource
The intersection with a combining function.
Traversal
Map
mapWithKey :: (k -> a -> b) -> HashMap k a -> HashMap k bSource
Map a function over all values in the map.
mapAccum :: (a -> b -> (a, c)) -> a -> HashMap k b -> (a, HashMap 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 -> HashMap k b -> (a, HashMap 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 -> HashMap k a -> bSource
Fold the keys and values in the map, such that
.
foldWithKey
f z ==
foldr
(uncurry
f) z . toAscList
Conversion
assocs :: HashMap k a -> [(k, a)]Source
Return all key/value pairs in the map in arbitrary key order.
Lists
fromList :: (Hashable k, Ord k) => [(k, a)] -> HashMap k aSource
Create a map from a list of key/value pairs.
fromListWith :: (Hashable k, Ord k) => (a -> a -> a) -> [(k, a)] -> HashMap k aSource
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)] -> HashMap k aSource
Build a map from a list of key/value pairs with a combining function.
Filter
filter :: Ord k => (a -> Bool) -> HashMap k a -> HashMap k aSource
Filter all values that satisfy some predicate.
filterWithKey :: Ord k => (k -> a -> Bool) -> HashMap k a -> HashMap k aSource
Filter all keys/values that satisfy some predicate.
partition :: Ord k => (a -> Bool) -> HashMap k a -> (HashMap k a, HashMap 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) -> HashMap k a -> (HashMap k a, HashMap 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) -> HashMap k a -> HashMap k bSource
Map values and collect the Just
results.
mapMaybeWithKey :: Ord k => (k -> a -> Maybe b) -> HashMap k a -> HashMap k bSource
Map keys/values and collect the Just
results.
mapEitherWithKey :: Ord k => (k -> a -> Either b c) -> HashMap k a -> (HashMap k b, HashMap k c)Source
Submap
isSubmapOfBy :: Ord k => (a -> b -> Bool) -> HashMap k a -> HashMap k b -> BoolSource
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) => HashMap k a -> HashMap k a -> BoolSource
Is this a proper submap? (ie. a submap but not equal).
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> HashMap k a -> HashMap k b -> BoolSource
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.