Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module contains a HashTable
typeclass for the hash table
implementations in this package. This allows you to provide functions which
will work for any hash table implementation in this collection.
It is recommended to create a concrete type alias in your code when using this package, i.e.:
import qualified Data.HashTable.IO as H type HashTable k v = H.BasicHashTable k v foo :: IO (HashTable Int Int) foo = do ht <- H.new H.insert ht 1 1 return ht
or
import qualified Data.HashTable.ST.Cuckoo as C import qualified Data.HashTable.Class as H type HashTable s k v = C.HashTable s k v foo :: ST s (HashTable s k v) foo = do ht <- H.new H.insert ht 1 1 return ht
Firstly, this makes it easy to switch to a different hash table
implementation, and secondly, using a concrete type rather than leaving your
functions abstract in the HashTable
class should allow GHC to optimize
away the typeclass dictionaries.
Note that the functions in this typeclass are in the ST
monad; if you want
hash tables in IO
, use the convenience wrappers in Data.HashTable.IO.
Synopsis
- class HashTable h where
- new :: ST s (h s k v)
- newSized :: Int -> ST s (h s k v)
- mutate :: (Eq k, Hashable k) => h s k v -> k -> (Maybe v -> (Maybe v, a)) -> ST s a
- mutateST :: (Eq k, Hashable k) => h s k v -> k -> (Maybe v -> ST s (Maybe v, a)) -> ST s a
- insert :: (Eq k, Hashable k) => h s k v -> k -> v -> ST s ()
- delete :: (Eq k, Hashable k) => h s k v -> k -> ST s ()
- lookup :: (Eq k, Hashable k) => h s k v -> k -> ST s (Maybe v)
- foldM :: (a -> (k, v) -> ST s a) -> a -> h s k v -> ST s a
- mapM_ :: ((k, v) -> ST s b) -> h s k v -> ST s ()
- lookupIndex :: (Eq k, Hashable k) => h s k v -> k -> ST s (Maybe Word)
- nextByIndex :: h s k v -> Word -> ST s (Maybe (Word, k, v))
- computeOverhead :: h s k v -> ST s Double
- fromList :: (HashTable h, Eq k, Hashable k) => [(k, v)] -> ST s (h s k v)
- fromListWithSizeHint :: (HashTable h, Eq k, Hashable k) => Int -> [(k, v)] -> ST s (h s k v)
- toList :: HashTable h => h s k v -> ST s [(k, v)]
Documentation
class HashTable h where Source #
A typeclass for hash tables in the ST
monad. The operations on these
hash tables are typically both key- and value-strict.
new, newSized, mutateST, insert, delete, lookup, foldM, mapM_, lookupIndex, nextByIndex, computeOverhead
new :: ST s (h s k v) Source #
Creates a new, default-sized hash table. O(1).
newSized :: Int -> ST s (h s k v) Source #
Creates a new hash table sized to hold n
elements. O(n).
mutate :: (Eq k, Hashable k) => h s k v -> k -> (Maybe v -> (Maybe v, a)) -> ST s a Source #
Generalized update. Given a key k, and a user function f, calls:
- `f Nothing` if the key did not exist in the hash table
- `f (Just v)` otherwise
If the user function returns (Nothing, _)
, then the value is deleted
from the hash table. Otherwise the mapping for k is inserted or
replaced with the provided value.
Returns the second part of the tuple returned by f.
mutateST :: (Eq k, Hashable k) => h s k v -> k -> (Maybe v -> ST s (Maybe v, a)) -> ST s a Source #
As mutate
, except that the action can perform additional side
effects.
insert :: (Eq k, Hashable k) => h s k v -> k -> v -> ST s () Source #
Inserts a key/value mapping into a hash table, replacing any existing mapping for that key.
O(n) worst case, O(1) amortized.
delete :: (Eq k, Hashable k) => h s k v -> k -> ST s () Source #
Deletes a key-value mapping from a hash table. O(n) worst case, O(1) amortized.
lookup :: (Eq k, Hashable k) => h s k v -> k -> ST s (Maybe v) Source #
Looks up a key-value mapping in a hash table. O(n) worst case, (O(1) for cuckoo hash), O(1) amortized.
foldM :: (a -> (k, v) -> ST s a) -> a -> h s k v -> ST s a Source #
A strict fold over the key-value records of a hash table in the ST
monad. O(n).
mapM_ :: ((k, v) -> ST s b) -> h s k v -> ST s () Source #
A side-effecting map over the key-value records of a hash table. O(n).
lookupIndex :: (Eq k, Hashable k) => h s k v -> k -> ST s (Maybe Word) Source #
Looks up the index of a key-value mapping in a hash table suitable
for passing to nextByIndex
.
nextByIndex :: h s k v -> Word -> ST s (Maybe (Word, k, v)) Source #
Returns the next key-value mapping stored at the given index or at a greater index. The index, key, and value of the next record are returned.
computeOverhead :: h s k v -> ST s Double Source #
Computes the overhead (in words) per key-value mapping. Used for debugging, etc; time complexity depends on the underlying hash table implementation. O(n).
Instances
HashTable HashTable Source # | |
Defined in Data.HashTable.ST.Basic new :: ST s (HashTable s k v) Source # newSized :: Int -> ST s (HashTable s k v) Source # mutate :: (Eq k, Hashable k) => HashTable s k v -> k -> (Maybe v -> (Maybe v, a)) -> ST s a Source # mutateST :: (Eq k, Hashable k) => HashTable s k v -> k -> (Maybe v -> ST s (Maybe v, a)) -> ST s a Source # insert :: (Eq k, Hashable k) => HashTable s k v -> k -> v -> ST s () Source # delete :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s () Source # lookup :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s (Maybe v) Source # foldM :: (a -> (k, v) -> ST s a) -> a -> HashTable s k v -> ST s a Source # mapM_ :: ((k, v) -> ST s b) -> HashTable s k v -> ST s () Source # lookupIndex :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s (Maybe Word) Source # nextByIndex :: HashTable s k v -> Word -> ST s (Maybe (Word, k, v)) Source # | |
HashTable HashTable Source # | |
Defined in Data.HashTable.ST.Cuckoo new :: ST s (HashTable s k v) Source # newSized :: Int -> ST s (HashTable s k v) Source # mutate :: (Eq k, Hashable k) => HashTable s k v -> k -> (Maybe v -> (Maybe v, a)) -> ST s a Source # mutateST :: (Eq k, Hashable k) => HashTable s k v -> k -> (Maybe v -> ST s (Maybe v, a)) -> ST s a Source # insert :: (Eq k, Hashable k) => HashTable s k v -> k -> v -> ST s () Source # delete :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s () Source # lookup :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s (Maybe v) Source # foldM :: (a -> (k, v) -> ST s a) -> a -> HashTable s k v -> ST s a Source # mapM_ :: ((k, v) -> ST s b) -> HashTable s k v -> ST s () Source # lookupIndex :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s (Maybe Word) Source # nextByIndex :: HashTable s k v -> Word -> ST s (Maybe (Word, k, v)) Source # | |
HashTable HashTable Source # | |
Defined in Data.HashTable.ST.Linear new :: ST s (HashTable s k v) Source # newSized :: Int -> ST s (HashTable s k v) Source # mutate :: (Eq k, Hashable k) => HashTable s k v -> k -> (Maybe v -> (Maybe v, a)) -> ST s a Source # mutateST :: (Eq k, Hashable k) => HashTable s k v -> k -> (Maybe v -> ST s (Maybe v, a)) -> ST s a Source # insert :: (Eq k, Hashable k) => HashTable s k v -> k -> v -> ST s () Source # delete :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s () Source # lookup :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s (Maybe v) Source # foldM :: (a -> (k, v) -> ST s a) -> a -> HashTable s k v -> ST s a Source # mapM_ :: ((k, v) -> ST s b) -> HashTable s k v -> ST s () Source # lookupIndex :: (Eq k, Hashable k) => HashTable s k v -> k -> ST s (Maybe Word) Source # nextByIndex :: HashTable s k v -> Word -> ST s (Maybe (Word, k, v)) Source # |
fromList :: (HashTable h, Eq k, Hashable k) => [(k, v)] -> ST s (h s k v) Source #
Create a hash table from a list of key-value pairs. O(n).