linear-base-0.3.0: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.HashMap.Mutable.Linear

Description

This module provides mutable hashmaps with a linear interface.

It is implemented with Robin Hood hashing which has amortized constant time lookups and updates.

Synopsis

A mutable hashmap

data HashMap k v Source #

A mutable hashmap with a linear interface.

Instances

Instances details
Functor (HashMap k) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear.Internal

Methods

fmap :: (a %1 -> b) -> HashMap k a %1 -> HashMap k b Source #

Semigroup (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear.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 #

Keyed k => Semigroup (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear.Internal

Methods

(<>) :: HashMap k v %1 -> HashMap k v %1 -> HashMap k v Source #

Consumable (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear.Internal

Methods

consume :: HashMap k v %1 -> () Source #

Dupable (HashMap k v) Source # 
Instance details

Defined in Data.HashMap.Mutable.Linear.Internal

Methods

dupR :: HashMap k v %1 -> Replicator (HashMap k v) Source #

dup2 :: HashMap k v %1 -> (HashMap k v, HashMap k v) Source #

type Keyed k = (Eq k, Hashable k) Source #

At minimum, we need to store hashable and identifiable keys

Constructors

empty :: forall k v b. Keyed k => Int -> (HashMap k v %1 -> Ur b) %1 -> Ur b Source #

Run a computation with an empty HashMap with given capacity.

fromList :: forall k v b. Keyed k => [(k, v)] -> (HashMap k v %1 -> Ur b) %1 -> Ur b Source #

Run a computation with an HashMap containing given key-value pairs.

Modifiers

insert :: Keyed k => k -> v -> HashMap k v %1 -> HashMap k v Source #

Insert a key value pair to a HashMap. It overwrites the previous value if it exists.

insertAll :: Keyed k => [(k, v)] -> HashMap k v %1 -> HashMap k v Source #

insert (in the provided order) the given key-value pairs to the hashmap.

delete :: Keyed k => k -> HashMap k v %1 -> HashMap k v Source #

Delete a key from a HashMap. Does nothing if the key does not exist.

filter :: Keyed k => (v -> Bool) -> HashMap k v %1 -> HashMap k v Source #

Complexity: O(capacity hm)

filterWithKey :: Keyed k => (k -> v -> Bool) -> HashMap k v %1 -> HashMap k v Source #

Complexity: O(capacity hm)

mapMaybe :: Keyed k => (v -> Maybe v') -> HashMap k v %1 -> HashMap k v' Source #

A version of fmap which can throw out the elements.

Complexity: O(capacity hm)

mapMaybeWithKey :: forall k v v'. Keyed k => (k -> v -> Maybe v') -> HashMap k v %1 -> HashMap k v' Source #

Same as mapMaybe, but also has access to the keys.

shrinkToFit :: Keyed k => HashMap k a %1 -> HashMap k a Source #

Reduce the HashMap capacity to decrease wasted memory. Returns a semantically identical HashMap.

This is only useful after a lot of deletes.

Complexity: O(capacity hm)

alter :: Keyed k => (Maybe v -> Maybe v) -> k -> HashMap k v %1 -> HashMap k v Source #

A general modification function; which can insert, update or delete a value of the key. See alterF, for an even more general function.

alterF :: (Keyed k, Functor f) => (Maybe v -> f (Ur (Maybe v))) -> k -> HashMap k v %1 -> f (HashMap k v) Source #

The most general modification function; which can insert, update or delete a value of the key, while collecting an effect in the form of an arbitrary Functor.

Accessors

size :: HashMap k v %1 -> (Ur Int, HashMap k v) Source #

Number of key-value pairs inside the HashMap

capacity :: HashMap k v %1 -> (Ur Int, HashMap k v) Source #

Maximum number of elements the HashMap can store without resizing. However, for performance reasons, the HashMap might be before full.

Use shrinkToFit to reduce the wasted space.

lookup :: Keyed k => k -> HashMap k v %1 -> (Ur (Maybe v), HashMap k v) Source #

Look up a value from a HashMap.

member :: Keyed k => k -> HashMap k v %1 -> (Ur Bool, HashMap k v) Source #

Check if the given key exists.

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

Converts a HashMap to a lazy list.

Combining maps

union :: Keyed k => HashMap k v %1 -> HashMap k v %1 -> HashMap k v Source #

A right-biased union.

Complexity: O(min(capacity hm1, capacity hm2)

unionWith :: Keyed k => (v -> v -> v) -> HashMap k v %1 -> HashMap k v %1 -> HashMap k v Source #

Union of two maps using the provided function on conflicts.

Complexity: O(min(capacity hm1, capacity hm2)

intersectionWith :: Keyed k => (a -> b -> c) -> HashMap k a %1 -> HashMap k b %1 -> HashMap k c Source #

Intersection of two maps with the provided combine function.

Complexity: O(min(capacity hm1, capacity hm2)