Copyright | (c) Peter Robinson |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | Peter Robinson <pwr@lowerbound.io> |
Stability | provisional |
Portability | non-portable (requires concurrency, stm) |
Safe Haskell | None |
Language | Haskell2010 |
Data.HashTable
Contents
Description
You can find benchmarks and more information about the internals of this package here: https://lowerbound.io/blog/2019-10-24_concurrent_hash_table_performance.html
Usage Example:
> ht <- newWithDefaults 4 -- creates hash table of initial size 4 > insert ht 1 "hello" -- adds key-value pair (1,"hello") > insert ht 2 "world" -- adds key-value pair (2,"world") > atomically $ readAssocs ht -- convert to a key-value list [(1,"hello"),(2,"world")] > readSizeIO ht -- returns 4 > insert ht 3 "!" -- adds key-value pair (3,"!") and triggers a resize since load/size is ≥ 0.75 > readSizeIO ht -- returns 8 > atomically $ readAssocs ht -- convert to a key-value list [(1,"hello"),(3,"!"),(2,"world")]
Synopsis
- data HashTable k v
- data Chain k v
- new :: Eq k => Int -> Config k -> IO (HashTable k v)
- newWithDefaults :: (Eq k, Hashable k) => Int -> IO (HashTable k v)
- mkDefaultConfig :: Hashable k => IO (Config k)
- data Config k = Config {
- _scaleFactor :: Float
- _threshold :: Float
- _numResizeWorkers :: Int
- _hashFunc :: k -> Int
- lookup :: Eq k => HashTable k v -> k -> IO (Maybe v)
- readAssocs :: Eq k => HashTable k v -> STM [(k, v)]
- readAssocsIO :: Eq k => HashTable k v -> IO [(k, v)]
- insert :: Eq k => HashTable k v -> k -> v -> IO Bool
- add :: Eq k => HashTable k v -> k -> v -> IO Bool
- update :: Eq k => HashTable k v -> k -> v -> IO Bool
- modify :: Eq k => HashTable k v -> k -> (v -> v) -> IO (Maybe v)
- delete :: Eq k => HashTable k v -> k -> IO Bool
- swapValues :: Eq k => HashTable k v -> k -> v -> IO v
- readSizeIO :: HashTable k v -> IO Int
- readSize :: HashTable k v -> STM Int
- readLoad :: HashTable k v -> IO Int
- resize :: Eq k => HashTable k v -> IO ()
Data Type
Used for chain-hashing.
Construction
Creates a new hash table with an initial size. See newWithDefaults
for more
details.
Creates a new hash table with the given initial vector size, scale factor 2.0, a resizing load threshold of 0.75, and we use as many threads for resizing as we have cores available. This will use a hash function with a (single) random salt. For security sensitive applications, you MUST supply your own hash function. (To be replaced by universal hashing in future versions.)
mkDefaultConfig :: Hashable k => IO (Config k) Source #
Default configuration: scale factor = 2.0; resizing threshold = 0.75;
number of worker threads for resizing = getNumCapabilities
;
hash function = use hashWithSalt
with a random salt.
Configuration options that may affect the performance of the hash table
Constructors
Config | |
Fields
|
Atomic Read-Operations
Lookup the value for the given key in the hash table.
readAssocs :: Eq k => HashTable k v -> STM [(k, v)] Source #
Returns an atomic snapshot of the hash table as a list of key-value pairs. If there is a lot of contention going on, this may be very inefficient.
Non-Atomic Read-Operations
readAssocsIO :: Eq k => HashTable k v -> IO [(k, v)] Source #
Returns the content of the hash table as a list of key-value pairs. This is *not* an atomic operation! If you need atomicity, use readAssoc
instead.
Atomic Write-Operations
Arguments
:: Eq k | |
=> HashTable k v | |
-> k | key |
-> v | value |
-> IO Bool | returns |
Updates the value for key k
. If k
is not in the hash table, it skips the
update and returns False
.
Arguments
:: Eq k | |
=> HashTable k v | |
-> k | key |
-> (v -> v) | update-function |
-> IO (Maybe v) | returns the old value for key |
Applies an update-function to the value for key k
. Returns the old value if
it exists. If k
is not in the hash table, it returns Nothing
.
Arguments
:: Eq k | |
=> HashTable k v | |
-> k | key of entry that will be deleted |
-> IO Bool | returns |
Deletes the entry for the given key from the hash table. Returns True
if
and only if an entry was deleted from the table.
Atomically replaces the value for the given key k
in the hash table with
the new value. Returns the old value. Throws AssertionFailed
if k
is not in
the hash table.
Utilities
readSizeIO :: HashTable k v -> IO Int Source #
Returns the size of the vector representing the hash table.
readSize :: HashTable k v -> STM Int Source #
Returns the size of the vector representing the hash table.