hamtmap-0.3: A purely functional and persistent hash map

Portabilityportable
Stabilityexperimental
Maintainerexclipy@gmail.com

Data.HamtMap

Contents

Description

An implementation of maps from keys to values (dictionaries) based on the hash array mapped trie.

Since many function names (but not the type name) clash with Prelude names, this module is usually imported qualified, e.g.

  import qualified Data.HamtMap as HM

This data structure is based on Phil Bagwell's hash array mapped trie, which is described by his original paper:

Synopsis

HamtMap type

data (Eq k, Hashable k) => HamtMap k v Source

A HamtMap from keys k to values v

Instances

(Eq k, Hashable k, Show k, Show v) => Show (HamtMap k v) 
(Eq k, Hashable k, NFData k, NFData v) => NFData (HamtMap k v) 

Operators

(!) :: (Eq k, Hashable k) => HamtMap k v -> k -> vSource

Find the value at a key. Calls error when the element can not be found.

Query

member :: (Eq k, Hashable k) => k -> HamtMap k v -> BoolSource

Is the key a member of the map? See also notMember.

notMember :: (Eq k, Hashable k) => k -> HamtMap k v -> BoolSource

Is the key a member of the map? See also member.

lookup :: (Eq k, Hashable k) => k -> HamtMap k v -> Maybe vSource

Lookup the value at a key in the map.

The function will return the corresponding value as (Just value), or Nothing if the key isn't in the map.

Construction

empty :: (Eq k, Hashable k) => HamtMap k vSource

The empty HamtMap.

singleton :: (Eq k, Hashable k) => k -> v -> HamtMap k vSource

(singleton key value) is a single-element HamtMap holding (key, value)

Insertion

insert :: (Eq k, Hashable k) => k -> v -> HamtMap k v -> HamtMap k vSource

Insert a new key and value in the map. If the key is already present in the map, the associated value is replaced with the supplied value. insert is equivalent to insertWith const.

insertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HamtMap k v -> HamtMap k vSource

Insert with a function, combining new value and old value. insertWith f key value mp will insert the pair (key, value) into mp if key does not exist in the map. If the key does exist, the function will insert the pair (key, f new_value old_value).

Delete/Update

delete :: (Eq k, Hashable k) => k -> HamtMap k v -> HamtMap k vSource

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 :: (Eq k, Hashable k) => (v -> v) -> k -> HamtMap k v -> HamtMap k vSource

Update a value at a specific key with the result of the provided function. When the key is not a member of the map, the original map is returned.

update :: (Eq k, Hashable k) => (v -> Maybe v) -> k -> HamtMap k v -> HamtMap k vSource

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 -> HamtMap k v -> HamtMap k vSource

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

Traversal

map :: (Eq k, Hashable k) => (v -> v) -> HamtMap k v -> HamtMap k vSource

Map a function over all values in the map.

mapWithKey :: (Eq k, Hashable k) => (k -> v -> v) -> HamtMap k v -> HamtMap k vSource

Map a function over all values in the map.

Filter

filter :: (Eq k, Hashable k) => (v -> Bool) -> HamtMap k v -> HamtMap k vSource

Filter for all values that satisify a predicate.

filterWithKey :: (Eq k, Hashable k) => (k -> v -> Bool) -> HamtMap k v -> HamtMap k vSource

Filter for all values that satisify a predicate.

Conversion

elems :: (Eq k, Hashable k) => HamtMap k v -> [v]Source

Return all elements of the map.

keys :: (Eq k, Hashable k) => HamtMap k v -> [k]Source

Return all keys of the map.

toList :: (Eq k, Hashable k) => HamtMap k v -> [(k, v)]Source

Convert to a list of key/value pairs.

fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HamtMap k vSource

Build a map from a list of key/value pairs with a combining function.

fromList :: (Eq k, Hashable k) => [(k, v)] -> HamtMap k vSource

Build a map from a list of key/value pairs. If the list contains more than one value for the same key, the last value for the key is retained.