HMap-1.0.1: Fast heterogeneous maps.

Portabilityportable
Stabilityprovisional
Maintaineratzeus@gmail.org
Safe HaskellNone

Data.HMap

Contents

Description

An efficient implementation of heterogeneous maps.

A heterogeneous map can store values of different types. This in contrast to a homogenous map (such as the one in Data.Map) which can store values of a single type.

For example, here we use a map with String (name), Double (salary) and Bool (female):

 import Data.HMap 

 example name salary female = 
   do putStrLn $ format a
      putStrLn $ format b 
    where a = insert name "Edsger" $ 
              insert salary 4450.0 $ 
              insert female False empty
          b = insert name "Ada"    $ 
              insert salary 5000.0 $ 
              insert female True empty
          format x = x ! name ++ 
                     ": salary=" ++ show (x ! salary) ++ 
                     ", female="  ++ show (x ! female)
 
 main = withKey $ withKey $ withKey example

The output of this program:

 Edsger: salary=4450.0, female=False
 Ada: salary=5000.0, female=True

This module differs from hackage package hetero-map in the following ways:

  • Lookup, insertion and updates are O(log n) when using this module, whereas they are O(n) when using hetero-map.
  • With this module we cannot statically ensure that a Heterogenous map has a some key (i.e. (!) might throw error, like in Data.Map). With hetero-map it is possible to statically rule out such errors.
  • The interface of this module is more similar to Data.Map

This module differs from stable-maps in the following ways:

  • Key can be created safely without using the IO monad.
  • The interface is more uniform and implements more of the Data.Map interface.

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

  import Data.HMap (HMap)
  import qualified Data.HMap as HMap

This module uses Data.HashMap.Lazy as a backend. Every function from Data.Map that makes sense in a heterogenous setting has been implemented.

Note that the implementation is left-biased -- the elements of a first argument are always preferred to the second, for example in union or insert.

Operation comments contain the operation time complexity in the Big-O notation http://en.wikipedia.org/wiki/Big_O_notation.

Synopsis

HMap type

Keys

data Key x a Source

withKey :: (forall x. Key x a -> b) -> bSource

O(1). Scopes a key to the given function The key cannot escape the function (because of the existential type).

The implementation actually *creates* a key, but because the key cannot escape the given function f, there is no way to observe that if we run withKey f twice, that it will get a different key the second time.

data T Source

The scope of top-level keys.

createKey :: IO (Key T a)Source

O(1). Create a new top-level key.

Operators

(!) :: HMap -> Key x a -> aSource

O(log n). Find the value at a key. Calls error when the element can not be found.

(\\) :: HMap -> HMap -> HMapSource

Same as difference.

Query

null :: HMap -> BoolSource

O(1). Is the map empty?

size :: HMap -> IntSource

O(1). The number of elements in the map.

member :: Key x a -> HMap -> BoolSource

O(log n). Is the key a member of the map? See also notMember.

notMember :: Key x a -> HMap -> BoolSource

O(log n). Is the key not a member of the map? See also member.

lookup :: Key x a -> HMap -> Maybe aSource

O(log n). 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.

findWithDefault :: a -> Key x a -> HMap -> aSource

O(log n). The expression (findWithDefault def k map) returns the value at key k or returns default value def when the key is not in the map.

Construction

empty :: HMapSource

O(1). The empty map.

singleton :: Key x a -> a -> HMapSource

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

Insertion

insert :: Key x a -> a -> HMap -> HMapSource

O(log n). 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 :: (a -> a -> a) -> Key x a -> a -> HMap -> HMapSource

O(log n). 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 :: Key x a -> HMap -> HMapSource

O(log n). 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 :: (a -> a) -> Key x a -> HMap -> HMapSource

O(log n). 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 :: (a -> Maybe a) -> Key x a -> HMap -> HMapSource

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 :: (Maybe a -> Maybe a) -> Key x a -> HMap -> HMapSource

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 :: HMap -> HMap -> HMapSource

O(n+m). The expression (union t1 t2) takes the left-biased union of t1 and t2. It prefers t1 when duplicate keys are encountered. The implementation (from Map) uses the efficient hedge-union algorithm. Hedge-union is more efficient on (bigset `union` smallset).

unions :: [HMap] -> HMapSource

The union of a list of maps: (unions == foldl union empty).

Difference

difference :: HMap -> HMap -> HMapSource

O(n+m). Difference of two maps. Return elements of the first map not existing in the second map. The implementation (from Map) uses an efficient hedge algorithm comparable with hedge-union.

Intersection

intersection :: HMap -> HMap -> HMapSource

O(n+m). Intersection of two maps. Return data in the first map for the keys existing in both maps.