unordered-containers-0.2.7.1: Efficient hashing-based container types

Copyright2010-2012 Johan Tibell
LicenseBSD-style
Maintainerjohan.tibell@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Data.HashMap.Lazy

Contents

Description

A map from hashable keys to values. A map cannot contain duplicate keys; each key can map to at most one value. A HashMap makes no guarantees as to the order of its elements.

The implementation is based on hash array mapped tries. A HashMap is often faster than other tree-based set types, especially when key comparison is expensive, as in the case of strings.

Many operations have a average-case complexity of O(log n). The implementation uses a large base (i.e. 16) so in practice these operations are constant time.

Synopsis

Strictness properties

This module satisfies the following strictness property:

  • Key arguments are evaluated to WHNF

data HashMap k v Source #

A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.

Instances

Functor (HashMap k) Source # 

Methods

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

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

Foldable (HashMap k) Source # 

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] #

null :: HashMap k a -> Bool #

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 #

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

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

Traversable (HashMap k) Source # 

Methods

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

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

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

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

(Eq k, Hashable k) => IsList (HashMap k v) Source # 

Associated Types

type Item (HashMap k v) :: * #

Methods

fromList :: [Item (HashMap k v)] -> HashMap k v #

fromListN :: Int -> [Item (HashMap k v)] -> HashMap k v #

toList :: HashMap k v -> [Item (HashMap k v)] #

(Eq k, Eq v) => Eq (HashMap k v) Source # 

Methods

(==) :: HashMap k v -> HashMap k v -> Bool #

(/=) :: HashMap k v -> HashMap k v -> Bool #

(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) Source # 

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) #

(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) Source # 
(Show k, Show v) => Show (HashMap k v) Source # 

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

(Eq k, Hashable k) => Semigroup (HashMap k v) Source # 

Methods

(<>) :: HashMap k v -> HashMap k v -> HashMap k v #

sconcat :: NonEmpty (HashMap k v) -> HashMap k v #

stimes :: Integral b => b -> HashMap k v -> HashMap k v #

(Eq k, Hashable k) => Monoid (HashMap k v) Source # 

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

(NFData k, NFData v) => NFData (HashMap k v) Source # 

Methods

rnf :: HashMap k v -> () #

(Hashable k, Hashable v) => Hashable (HashMap k v) Source # 

Methods

hashWithSalt :: Int -> HashMap k v -> Int #

hash :: HashMap k v -> Int #

type Item (HashMap k v) Source # 
type Item (HashMap k v) = (k, v)

Construction

empty :: HashMap k v Source #

O(1) Construct an empty map.

singleton :: Hashable k => k -> v -> HashMap k v Source #

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

Basic interface

null :: HashMap k v -> Bool Source #

O(1) Return True if this map is empty, False otherwise.

size :: HashMap k v -> Int Source #

O(n) Return the number of key-value mappings in this map.

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

O(log n) Return True if the specified key is present in the map, False otherwise.

lookup :: (Eq k, Hashable k) => k -> HashMap 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.

lookupDefault Source #

Arguments

:: (Eq k, Hashable k) 
=> v

Default value to return.

-> k 
-> HashMap k v 
-> v 

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.

(!) :: (Eq k, Hashable k) => HashMap k v -> k -> v infixl 9 Source #

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

insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v Source #

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 Source #

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 Source #

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 Source #

O(log n) Adjust the value tied to a given key in this map only if it is present. Otherwise, leave the map alone.

update :: (Eq k, Hashable k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a Source #

O(log n) The expression (update f k map) updates the value x at k, (if it is in the map). If (f k x) is Nothing, the element is deleted. If it is (Just y), the key k is bound to the new value y.

alter :: (Eq k, Hashable k) => (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v Source #

O(log n) The expression (alter f k map) alters the value x at k, or absence thereof. alter can be used to insert, delete, or update a value in a map. In short : lookup k (alter f k m) = f (lookup k m).

Combine

Union

union :: (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v Source #

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.

unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v Source #

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 Source #

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 Source #

Construct a set containing all elements from a list of sets.

Transformations

map :: (v1 -> v2) -> HashMap k v1 -> HashMap k v2 Source #

O(n) Transform this map by applying a function to every value.

mapWithKey :: (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2 Source #

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) Source #

O(n) Transform this map by accumulating an Applicative result from every value.

Difference and intersection

difference :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v Source #

O(n*log m) Difference of two maps. Return elements of the first map not existing in the second.

intersection :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v Source #

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 Source #

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 Source #

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 Source #

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 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 Source #

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 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 Source #

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 Source #

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 Source #

O(n) Filter this map by retaining only elements which values satisfy a predicate.

filterWithKey :: forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v Source #

O(n) Filter this map by retaining only elements satisfying a predicate.

mapMaybe :: (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2 Source #

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 Source #

O(n) Transform this map by applying a function to every value and retaining only some of them.

Conversions

keys :: HashMap k v -> [k] Source #

O(n) Return a list of this map's keys. The list is produced lazily.

elems :: HashMap k v -> [v] Source #

O(n) Return a list of this map's values. The list is produced lazily.

Lists

toList :: HashMap k v -> [(k, v)] Source #

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 Source #

O(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 Source #

O(n*log n) Construct a map from a list of elements. Uses the provided function to merge duplicate entries.