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.Internal
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
Synopsis
- data MigrationStatus
- data Chain k v = Chain {
- _itemsTV :: TVar [(k, v)]
- _migrationStatusTV :: TVar MigrationStatus
- newChainIO :: IO (Chain k v)
- data HashTable k v = HashTable {
- _chainsVecTV :: TVar (Vector (Chain k v))
- _totalLoad :: IORef Int
- _config :: Config k
- data Config k = Config {
- _scaleFactor :: Float
- _threshold :: Float
- _numResizeWorkers :: Int
- _hashFunc :: k -> Int
- mkDefaultConfig :: Hashable k => IO (Config k)
- new :: Eq k => Int -> Config k -> IO (HashTable k v)
- newWithDefaults :: (Eq k, Hashable k) => Int -> IO (HashTable k v)
- readSizeIO :: HashTable k v -> IO Int
- readSize :: HashTable k v -> STM Int
- resize :: Eq k => HashTable k v -> IO ()
- lookup :: Eq k => HashTable k v -> k -> IO (Maybe v)
- type STMAction k v a = TVar [(k, v)] -> STM a
- genericModify :: Eq k => HashTable k v -> k -> STMAction k v a -> IO a
- 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)
- swapValues :: Eq k => HashTable k v -> k -> v -> IO v
- delete :: Eq k => HashTable k v -> k -> IO Bool
- atomicallyChangeLoad :: Eq k => HashTable k v -> Int -> IO ()
- readLoad :: HashTable k v -> IO Int
- readAssocs :: Eq k => HashTable k v -> STM [(k, v)]
- readAssocsIO :: Eq k => HashTable k v -> IO [(k, v)]
- deleteFirstKey :: Eq a => a -> [(a, b)] -> [(a, b)]
- readChainForKeyIO :: HashTable k v -> k -> IO (Chain k v)
- readChainForIndexIO :: HashTable k v -> Int -> IO (Chain k v)
- readChainForIndex :: HashTable k v -> Int -> STM (Chain k v)
- debug :: Show a => a -> IO ()
Documentation
data MigrationStatus Source #
Constructors
NotStarted | |
Ongoing | |
Finished |
Instances
Eq MigrationStatus Source # | |
Defined in Data.HashTable.Internal Methods (==) :: MigrationStatus -> MigrationStatus -> Bool # (/=) :: MigrationStatus -> MigrationStatus -> Bool # | |
Show MigrationStatus Source # | |
Defined in Data.HashTable.Internal Methods showsPrec :: Int -> MigrationStatus -> ShowS # show :: MigrationStatus -> String # showList :: [MigrationStatus] -> ShowS # |
Used for chain-hashing.
Constructors
Chain | |
Fields
|
newChainIO :: IO (Chain k v) Source #
Create a new empty chain.
A thread-safe hash table that supports dynamic resizing.
Constructors
HashTable | |
Fields
|
Configuration options that may affect the performance of the hash table
Constructors
Config | |
Fields
|
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.
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.)
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.
resize :: Eq k => HashTable k v -> IO () Source #
Increases the size of the hash table by scaling the current size it according to the _scaleFactor in the configuration.
Lookup the value for the given key in the hash table.
type STMAction k v a = TVar [(k, v)] -> STM a Source #
An action to be executed atomically for the content of the chain (i.e. list) stored at a specific table index. Used in genericModify
.
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
.
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.
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 increment/decrement the table load value by adding the provided
integer offest to the current value. Forks a thread that executes resize
if
the load passes the configured threshold.
readLoad :: HashTable k v -> IO Int Source #
The load (i.e. number of stored items) in the table. Note that this is not synchronized for performance reasons and hence might be somewhat out of date if a lot of contention is happening.
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.
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.
deleteFirstKey :: Eq a => a -> [(a, b)] -> [(a, b)] Source #
Takes a key k
and an assocation list ys
, and deletes the first entry with
key k
in ys
. Used internally.
readChainForKeyIO :: HashTable k v -> k -> IO (Chain k v) Source #
Atomically read the chain for the given key.
readChainForIndexIO :: HashTable k v -> Int -> IO (Chain k v) Source #
Atomically read the chain for the given index. (Warning: bounds are not checked.)