| Portability | portable |
|---|---|
| Stability | provisional |
| Maintainer | atzeus@gmail.org |
| Safe Haskell | None |
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 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
-- type can be inferred.
example :: HKey x String -> HKey x1 Double -> HKey x2 Bool
-> String
example name salary female =
format a ++ "\n" ++ format b ++ "\n"
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)
keyLocal :: String
keyLocal = withKey $ withKey $ withKey example
keyGlobal :: IO String
keyGlobal =
do name <- createKey
salary <- createKey
female <- createKey
return $ example name salary female
main = do print "local"
putStr keyLocal
print "global"
keyGlobal >>= putStr
Which gives:
"local" Edsger: salary=4450.0, female=False Ada: salary=5000.0, female=True "global" Edsger: salary=4450.0, female=False Ada: salary=5000.0, female=True
Key types carry two type arguments: the scope of the key and
the the type of things that can be stored at this key, for example String or Int.
The scope of the key depends on how it is created:
- In the
keyLocalexample, keys are created locally with thewithKeyfunction. The type of thewithKeyfunction is(forall x. Key x a -> b) -> b, which means it assigns a key and passes it to the given function. The key cannot escape the function (this would yield a type error). Hence, we say the key is scoped to the function. The scope type argument of the key is then an existential type. - In the
keyGlobalexample, keys are created globally withcreateKeyin the IO monad. This allows to create keys that are not not scoped to a single function, but to the whole program. The scope type argument of the key is thenT.
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
Map). Withhetero-mapit is possible to statically rule out such errors. - The interface of this module is more similar to
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
Mapinterface. - This module uses a Hashmap as a backend, whereas
stable-mapsusesData.Map. Hashmaps are faster, see http://blog.johantibell.com/2012/03/announcing-unordered-containers-02.html.
Another difference to both packages is that HMap has better memory performance in the following way: An entry into an HMap does not keep the value alive if the key is not alive. After all, if the key is dead, then there is no way to retrieve the value!
Hence, a HMap can have elements which can never be accessed
again. Use the IO operation purge to remove these.
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 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.
- data HMap
- (!) :: HMap -> HKey x a -> a
- (\\) :: HMap -> HMap -> HMap
- null :: HMap -> Bool
- size :: HMap -> Int
- member :: HKey x a -> HMap -> Bool
- notMember :: HKey x a -> HMap -> Bool
- lookup :: HKey x a -> HMap -> Maybe a
- findWithDefault :: a -> HKey x a -> HMap -> a
- empty :: HMap
- singleton :: HKey x a -> a -> HMap
- insert :: HKey s a -> a -> HMap -> HMap
- insertWith :: (a -> a -> a) -> HKey x a -> a -> HMap -> HMap
- delete :: HKey x a -> HMap -> HMap
- adjust :: (a -> a) -> HKey x a -> HMap -> HMap
- update :: (a -> Maybe a) -> HKey x a -> HMap -> HMap
- alter :: (Maybe a -> Maybe a) -> HKey x a -> HMap -> HMap
- union :: HMap -> HMap -> HMap
- unions :: [HMap] -> HMap
- difference :: HMap -> HMap -> HMap
- intersection :: HMap -> HMap -> HMap
- module Data.HKey
Documentation
Operators
(!) :: HMap -> HKey x a -> aSource
O(log n). Find the value at a key.
Calls error when the element can not be found.
Query
member :: HKey x a -> HMap -> BoolSource
O(log n). Is the key a member of the map? See also notMember.
notMember :: HKey x a -> HMap -> BoolSource
O(log n). Is the key not a member of the map? See also member.
lookup :: HKey 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 (,
or Just value)Nothing if the key isn't in the map.
findWithDefault :: a -> HKey x a -> HMap -> aSource
O(log n). The expression ( returns
the value at key findWithDefault def k map)k or returns default value def
when the key is not in the map.
Construction
Insertion
insert :: HKey s 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) -> HKey x a -> a -> HMap -> HMapSource
O(log n). Insert with a function, combining new value and old value.
will insert the pair (key, value) into insertWith f key value mpmp 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 :: HKey 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) -> HKey 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) -> HKey x a -> HMap -> HMapSource
O(log n). The expression () updates the value update f k mapx
at k (if it is in the map). If (f x) is Nothing, the element is
deleted. If it is (), the key Just yk is bound to the new value y.
Combine
Union
union :: HMap -> HMap -> HMapSource
O(n+m).
The expression () takes the left-biased union of union t1 t2t1 and t2.
It prefers t1 when duplicate keys are encountered.
Difference
difference :: HMap -> HMap -> HMapSource
O(n+m). Difference of two maps. Return elements of the first map not existing in the second map.
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.
Key reexports
module Data.HKey