hashtables-1.1.0.2: Mutable hash tables in the ST monad

Safe HaskellNone

Data.HashTable.IO

Description

This module provides wrappers in IO around the functions from Data.HashTable.Class.

This module exports three concrete hash table types, one for each hash table implementation in this package:

 type BasicHashTable  k v = IOHashTable (B.HashTable)  k v
 type CuckooHashTable k v = IOHashTable (Cu.HashTable) k v
 type LinearHashTable k v = IOHashTable (L.HashTable)  k v

The IOHashTable type can be thought of as a wrapper around a concrete hashtable type, which sets the ST monad state type to PrimState IO, a.k.a. RealWorld:

 type IOHashTable tabletype k v = tabletype (PrimState IO) k v

This module provides stToIO wrappers around the hashtable functions (which are in ST) to make it convenient to use them in IO. It is intended to be imported qualified and used with a user-defined type alias, i.e.:

 import qualified Data.HashTable.IO as H

 type HashTable k v = H.CuckooHashTable k v

 foo :: IO (HashTable Int Int)
 foo = do
     ht <- H.new
     H.insert ht 1 1
     return ht

Essentially, anywhere you see IOHashTable h k v in the type signatures below, you can plug in any of BasicHashTable k v, CuckooHashTable k v, or LinearHashTable k v.

Synopsis

Documentation

type BasicHashTable k v = IOHashTable HashTable k vSource

A type alias for a basic open addressing hash table using linear probing. See Data.HashTable.ST.Basic.

type CuckooHashTable k v = IOHashTable HashTable k vSource

A type alias for the cuckoo hash table. See Data.HashTable.ST.Cuckoo.

type LinearHashTable k v = IOHashTable HashTable k vSource

A type alias for the linear hash table. See Data.HashTable.ST.Linear.

type IOHashTable tabletype k v = tabletype (PrimState IO) k vSource

A type alias for our hash tables, which run in ST, to set the state token type to PrimState IO (aka RealWorld) so that we can use them in IO.

new :: HashTable h => IO (IOHashTable h k v)Source

See the documentation for this function in Data.HashTable.Class.

newSized :: HashTable h => Int -> IO (IOHashTable h k v)Source

See the documentation for this function in Data.HashTable.Class.

insert :: (HashTable h, Eq k, Hashable k) => IOHashTable h k v -> k -> v -> IO ()Source

See the documentation for this function in Data.HashTable.Class.

delete :: (HashTable h, Eq k, Hashable k) => IOHashTable h k v -> k -> IO ()Source

See the documentation for this function in Data.HashTable.Class.

lookup :: (HashTable h, Eq k, Hashable k) => IOHashTable h k v -> k -> IO (Maybe v)Source

See the documentation for this function in Data.HashTable.Class.

fromList :: (HashTable h, Eq k, Hashable k) => [(k, v)] -> IO (IOHashTable h k v)Source

See the documentation for this function in Data.HashTable.Class.

fromListWithSizeHint :: (HashTable h, Eq k, Hashable k) => Int -> [(k, v)] -> IO (IOHashTable h k v)Source

See the documentation for this function in Data.HashTable.Class.

toList :: (HashTable h, Eq k, Hashable k) => IOHashTable h k v -> IO [(k, v)]Source

See the documentation for this function in Data.HashTable.Class.

mapM_ :: HashTable h => ((k, v) -> IO a) -> IOHashTable h k v -> IO ()Source

See the documentation for this function in Data.HashTable.Class.

foldM :: HashTable h => (a -> (k, v) -> IO a) -> a -> IOHashTable h k v -> IO aSource

See the documentation for this function in Data.HashTable.Class.

computeOverhead :: HashTable h => IOHashTable h k v -> IO DoubleSource

See the documentation for this function in Data.HashTable.Class.