unordered-containers-0.2.15.0: Efficient hashing-based container types
Safe HaskellNone
LanguageHaskell2010

Data.HashMap.Internal

Description

WARNING

This module is considered internal.

The Package Versioning Policy does not apply.

The contents of this module may change in any way whatsoever and without any warning between minor versions of this package.

Authors importing this module are expected to track development closely.

Synopsis

Documentation

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.

Constructors

Empty 
BitmapIndexed !Bitmap !(Array (HashMap k v)) 
Leaf !Hash !(Leaf k v) 
Full !(Array (HashMap k v)) 
Collision !Hash !(Array (Leaf k v)) 

Instances

Instances details
Bifoldable HashMap Source #

Since: 0.2.11

Instance details

Defined in Data.HashMap.Internal

Methods

bifold :: Monoid m => HashMap m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> HashMap a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> HashMap a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> HashMap a b -> c #

Eq2 HashMap Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> HashMap a c -> HashMap b d -> Bool #

Ord2 HashMap Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> HashMap a c -> HashMap b d -> Ordering #

Show2 HashMap Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> HashMap a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [HashMap a b] -> ShowS #

NFData2 HashMap Source #

Since: 0.2.14.0

Instance details

Defined in Data.HashMap.Internal

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> HashMap a b -> () #

Hashable2 HashMap Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> HashMap a b -> Int #

Functor (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

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

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

Foldable (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

fold :: Monoid m => HashMap k m -> m #

foldMap :: Monoid m => (a -> m) -> HashMap k a -> 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 # 
Instance details

Defined in Data.HashMap.Internal

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 => Eq1 (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftEq :: (a -> b -> Bool) -> HashMap k a -> HashMap k b -> Bool #

Ord k => Ord1 (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> HashMap k a -> HashMap k b -> Ordering #

(Eq k, Hashable k, Read k) => Read1 (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (HashMap k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [HashMap k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (HashMap k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [HashMap k a] #

Show k => Show1 (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> HashMap k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [HashMap k a] -> ShowS #

NFData k => NFData1 (HashMap k) Source #

Since: 0.2.14.0

Instance details

Defined in Data.HashMap.Internal

Methods

liftRnf :: (a -> ()) -> HashMap k a -> () #

Hashable k => Hashable1 (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> HashMap k a -> Int #

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

Defined in Data.HashMap.Internal

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 #

Note that, in the presence of hash collisions, equal HashMaps may behave differently, i.e. substitutivity may be violated:

>>> data D = A | B deriving (Eq, Show)
>>> instance Hashable D where hashWithSalt salt _d = salt
>>> x = fromList [(A,1), (B,2)]
>>> y = fromList [(B,2), (A,1)]
>>> x == y
True
>>> toList x
[(A,1),(B,2)]
>>> toList y
[(B,2),(A,1)]

In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals.

Instance details

Defined in Data.HashMap.Internal

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 # 
Instance details

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 :: forall r r'. (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) Source #

The ordering is total and consistent with the Eq instance. However, nothing else about the ordering is specified, and it may change from version to version of either this package or of hashable.

Instance details

Defined in Data.HashMap.Internal

Methods

compare :: HashMap k v -> HashMap k v -> Ordering #

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

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

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

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

max :: HashMap k v -> HashMap k v -> HashMap k v #

min :: HashMap k v -> HashMap k v -> HashMap k v #

(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) Source # 
Instance details

Defined in Data.HashMap.Internal

(Show k, Show v) => Show (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Internal

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 #

<> = union

If a key occurs in both maps, the mapping from the first will be the mapping in the result.

Examples

Expand
>>> fromList [(1,'a'),(2,'b')] <> fromList [(2,'c'),(3,'d')]
fromList [(1,'a'),(2,'b'),(3,'d')]
Instance details

Defined in Data.HashMap.Internal

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 #

mempty = empty

mappend = union

If a key occurs in both maps, the mapping from the first will be the mapping in the result.

Examples

Expand
>>> mappend (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
fromList [(1,'a'),(2,'b'),(3,'d')]
Instance details

Defined in Data.HashMap.Internal

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 # 
Instance details

Defined in Data.HashMap.Internal

Methods

rnf :: HashMap k v -> () #

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

Defined in Data.HashMap.Internal

Methods

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

hash :: HashMap k v -> Int #

type Item (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Internal

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

data Leaf k v Source #

Constructors

L !k v 

Instances

Instances details
NFData2 Leaf Source #

Since: 0.2.14.0

Instance details

Defined in Data.HashMap.Internal

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Leaf a b -> () #

NFData k => NFData1 (Leaf k) Source #

Since: 0.2.14.0

Instance details

Defined in Data.HashMap.Internal

Methods

liftRnf :: (a -> ()) -> Leaf k a -> () #

(Eq k, Eq v) => Eq (Leaf k v) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

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

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

(NFData k, NFData v) => NFData (Leaf k v) Source # 
Instance details

Defined in Data.HashMap.Internal

Methods

rnf :: Leaf 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.

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

This is a flipped version of lookup.

Since: 0.2.11

findWithDefault 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.

Since: 0.2.11

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.

DEPRECATED: lookupDefault is deprecated as of version 0.2.11, replaced by findWithDefault.

(!) :: (Eq k, Hashable k, HasCallStack) => 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

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

In-place update version of insert

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

alterF :: (Functor f, Eq k, Hashable k) => (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v) Source #

O(log n) The expression (alterF f k map) alters the value x at k, or absence thereof.

alterF can be used to insert, delete, or update a value in a map.

Note: alterF is a flipped version of the at combinator from Control.Lens.At.

Since: 0.2.10

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

O(n*log m) Inclusion of maps. A map is included in another map if the keys are subsets and the corresponding values are equal:

isSubmapOf m1 m2 = keys m1 `isSubsetOf` keys m2 &&
                   and [ v1 == v2 | (k1,v1) <- toList m1; let v2 = m2 ! k1 ]

Examples

Expand
>>> fromList [(1,'a')] `isSubmapOf` fromList [(1,'a'),(2,'b')]
True
>>> fromList [(1,'a'),(2,'b')] `isSubmapOf` fromList [(1,'a')]
False

Since: 0.2.12

isSubmapOfBy :: (Eq k, Hashable k) => (v1 -> v2 -> Bool) -> HashMap k v1 -> HashMap k v2 -> Bool Source #

O(n*log m) Inclusion of maps with value comparison. A map is included in another map if the keys are subsets and if the comparison function is true for the corresponding values:

isSubmapOfBy cmpV m1 m2 = keys m1 `isSubsetOf` keys m2 &&
                          and [ v1 `cmpV` v2 | (k1,v1) <- toList m1; let v2 = m2 ! k1 ]

Examples

Expand
>>> isSubmapOfBy (<=) (fromList [(1,'a')]) (fromList [(1,'b'),(2,'c')])
True
>>> isSubmapOfBy (<=) (fromList [(1,'b')]) (fromList [(1,'a'),(2,'c')])
False

Since: 0.2.12

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.

Examples

Expand
>>> 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 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.

Compose

compose :: (Eq b, Hashable b) => HashMap b c -> HashMap a b -> HashMap a c Source #

Relate the keys of one map to the values of the other, by using the values of the former as keys for lookups in the latter.

Complexity: \( O (n * \log(m)) \), where \(m\) is the size of the first argument

>>> compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')])
fromList [(1,"A"),(2,"B")]
(compose bc ab !?) = (bc !?) <=< (ab !?)

Since: 0.2.13.0

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) Perform an Applicative action for each key-value pair in a HashMap and produce a HashMap of all the results.

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.

mapKeys :: (Eq k2, Hashable k2) => (k1 -> k2) -> HashMap k1 v -> HashMap k2 v Source #

O(n). mapKeys f s is the map obtained by applying f to each key of s.

The size of the result may be smaller if f maps two or more distinct keys to the same new key. In this case there is no guarantee which of the associated values is chosen for the conflicting key.

>>> mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])
fromList [(4,"b"),(6,"a")]
>>> mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")])
fromList [(1,"c")]
>>> mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")])
fromList [(3,"c")]

Since: 0.2.14.0

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.

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

O(n*log m) Difference with a combining function. When two equal keys are encountered, the combining function is applied to the values of these keys. If it returns Nothing, the element is discarded (proper set difference). If it returns (Just y), the element is updated with a new value y.

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*log 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*log 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

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). Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.

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 using the result in the next application. This function is strict in the starting value.

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

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

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

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

foldMapWithKey :: Monoid m => (k -> v -> m) -> HashMap k v -> m Source #

O(n) Reduce the map by applying a function to each element and combining the results with a monoid operation.

Filter

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.

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.

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

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

Examples

Given a list of key-value pairs where the keys are of different flavours, e.g:

data Key = Div | Sub

and the values need to be combined differently when there are duplicates, depending on the key:

combine Div = div
combine Sub = (-)

then fromListWithKey can be used as follows:

fromListWithKey combine [(Div, 2), (Div, 6), (Sub, 2), (Sub, 3)]
= fromList [(Div, 3), (Sub, 1)]

More generally, duplicate entries are accumulated as follows;

fromListWith f [(k, a), (k, b), (k, c), (k, d)]
= fromList [(k, f k d (f k c (f k b a)))]

Since: 0.2.11

type Hash = Word Source #

collision :: Hash -> Leaf k v -> Leaf k v -> HashMap k v Source #

Create a Collision value with two Leaf values.

hash :: Hashable a => a -> Hash Source #

A set of values. A set cannot contain duplicate values.

Convenience function. Compute a hash value for the given value.

mask :: Word -> Shift -> Bitmap Source #

index :: Hash -> Shift -> Int Source #

Mask out the bitsPerSubkey bits used for indexing at this level of the tree.

fullNodeMask :: Bitmap Source #

A bitmask with the bitsPerSubkey least significant bits set.

two :: Shift -> Hash -> k -> v -> Hash -> HashMap k v -> ST s (HashMap k v) Source #

Create a map from two key-value pairs which hashes don't collide. To enhance sharing, the second key-value pair is represented by the hash of its key and a singleton HashMap pairing its key with its value.

Note: to avoid silly thunks, this function must be strict in the key. See issue #232. We don't need to force the HashMap argument because it's already in WHNF (having just been matched) and we just put it directly in an array.

unionArrayBy :: (a -> a -> a) -> Bitmap -> Bitmap -> Array a -> Array a -> Array a Source #

Strict in the result of f.

update16 :: Array e -> Int -> e -> Array e Source #

O(n) Update the element at the given position in this array.

update16M :: Array e -> Int -> e -> ST s (Array e) Source #

O(n) Update the element at the given position in this array.

update16With' :: Array e -> Int -> (e -> e) -> Array e Source #

O(n) Update the element at the given position in this array, by applying a function to it.

updateOrConcatWith :: Eq k => (v -> v -> v) -> Array (Leaf k v) -> Array (Leaf k v) -> Array (Leaf k v) Source #

updateOrConcatWithKey :: Eq k => (k -> v -> v -> v) -> Array (Leaf k v) -> Array (Leaf k v) -> Array (Leaf k v) Source #

filterMapAux :: forall k v1 v2. (HashMap k v1 -> Maybe (HashMap k v2)) -> (Leaf k v1 -> Maybe (Leaf k v2)) -> HashMap k v1 -> HashMap k v2 Source #

Common implementation for filterWithKey and mapMaybeWithKey, allowing the former to former to reuse terms.

equalKeys :: Eq k => HashMap k v -> HashMap k v' -> Bool Source #

equalKeys1 :: (k -> k' -> Bool) -> HashMap k v -> HashMap k' v' -> Bool Source #

data LookupRes a Source #

Constructors

Absent 
Present a !Int 

insert' :: Eq k => Hash -> k -> v -> HashMap k v -> HashMap k v Source #

delete' :: Eq k => Hash -> k -> HashMap k v -> HashMap k v Source #

lookup' :: Eq k => Hash -> k -> HashMap k v -> Maybe v Source #

lookup' is a version of lookup that takes the hash separately. It is used to implement alterF.

insertNewKey :: Hash -> k -> v -> HashMap k v -> HashMap k v Source #

insertKeyExists :: Int -> Hash -> k -> v -> HashMap k v -> HashMap k v Source #

deleteKeyExists :: Int -> Hash -> k -> HashMap k v -> HashMap k v Source #

Delete optimized for the case when we know the key is in the map.

It is only valid to call this when the key exists in the map and you know the hash collision position if there was one. This information can be obtained from lookupRecordCollision. If there is no collision pass (-1) as collPos.

We can skip: - the key equality check on the leaf, if we reach a leaf it must be the key

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

insertModifying is a lot like insertWith; we use it to implement alterF. It takes a value to insert when the key is absent and a function to apply to calculate a new value when the key is present. Thanks to the unboxed unary tuple, we avoid introducing any unnecessary thunks in the tree.

ptrEq :: a -> a -> Bool Source #

Check if two the two arguments are the same value. N.B. This function might give false negatives (due to GC moving objects.)

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

Much like adjust, but not inherently leaky.