ttl-hashtables-1.3.1.1: Extends hashtables so that entries added can be expired after a TTL

Copyright(c) Erick Gonzalez 2019
LicenseBSD3
Maintainererick@codemonkeylabs.de
Safe HaskellNone
LanguageHaskell2010

Data.TTLHashTable

Contents

Description

This library extends fast mutable hashtables so that entries added can be expired after a given TTL (time to live). This TTL can be specified as a default property of the table or on a per entry basis.

Synopsis

How to use this module:

Import one of the hash table modules from the hashtables package.. i.e. Basic, Cuckoo, etc and "wrap" them in a TTLHashTable:

import Data.HashTable.ST.Basic as Basic

type HashTable k v = TTLHashTable Basic.HashTable k v

You can then use the functions in this module with this hashtable type. Note that the functions in this module which can fail offer a flexible error handling strategy by virtue of working in the context of a Failable monad. So for example, if the function is used directly in the IO monad and a failure occurs it would then result in an exception being thrown. However if the context supports the possibiliy of failure like a MaybeT or ExceptT transformer, it would then instead return something like IO Nothing or Left NotFound respectively (depending on the actual failure of course).

None of the functions in this module are thread safe, just as the underlying mutable hash tables in the ST monad aren't as well. If concurrent threads need to operate on the same table, you need to provide external means of synchronization to guarantee exclusive access to the table

data TTLHashTable h k v Source #

The TTL hash table type, parameterized on the type of table, key and value.

data TTLHashTableError Source #

Exception type used to report failures (depending on calling context)

Constructors

NotFound

The entry was not found in the table

ExpiredEntry

The entry did exist but is no longer valid

HashTableFull

The maximum size for the table has been reached

UnsupportedPlatform String

The platform is not supported

HashTableTooLarge

The hash table is too large for the provided settings

data Settings Source #

The Settings type allows for specifying how the hash table should behave.

Constructors

Settings 

Fields

  • maxSize :: Int

    Maximum size of the hash table. Once reached, insertion of keys will fail. Defaults to maxBound

  • renewUponRead :: Bool

    Whether a succesful lookup of an entry means the TTL of the entry should be restarted. Default is False

  • defaultTTL :: Int

    Default TTL value in milliseconds to be used for an entry if none is specified at insertion time

  • gcMaxEntries :: Int

    Maximum number of entries that can be garbage collected in one single call to removeExpired. This setting is provided so that the possibility of long running garbage collection can be managed by the user of the library. Default is maxBound

Instances
Default Settings Source # 
Instance details

Defined in Data.TTLHashTable

Methods

def :: Settings #

insert :: (Eq k, Hashable k, HashTable h, MonadIO m, Failable m) => TTLHashTable h k v -> k -> v -> m () Source #

Insert a new entry into the hash table. Take note of the fact that this function can fail for example if table has reached maxSize entries for example. Failure is signaled depending on the calling Failable context. So for example if called in pure IO, it would throw a regular IO exception (of type TTLHashTableError). For this reason, you probably want to call this function in a MaybeT or ExceptT monad

insert_ :: (Eq k, Hashable k, HashTable h, MonadIO m) => TTLHashTable h k v -> k -> v -> m () Source #

Just like insert but doesn't result in a failure if the insertion doesn't succeed. It just saves you from ignoring the return code returned from insert manually (or catching and ignoring the exception in the case of IO)

insertWithTTL :: (Eq k, Hashable k, HashTable h, MonadIO m, Failable m) => TTLHashTable h k v -> Int -> k -> v -> m () Source #

like insert but an entry specific TTL in milliseconds can be provided.

insertWithTTL_ :: (Eq k, Hashable k, HashTable h, MonadIO m) => TTLHashTable h k v -> Int -> k -> v -> m () Source #

like insertWithTTL but ignores insertion failure

delete :: (HashTable h, Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m () Source #

delete an entry from the hash table.

find :: (Eq k, Hashable k, MonadIO m) => TTLHashTable h k v -> k -> m (Maybe v) Source #

A lookup function which simply returns Maybe wrapped in the calling MonadIO context, to accomodate the more conventional users

foldM :: MonadIO m => (a -> (k, v) -> IO a) -> a -> TTLHashTable h k v -> m a Source #

A strict fold in IO over the (key, value) records in a hash table

mapM_ :: MonadIO m => ((k, v) -> IO a) -> TTLHashTable h k v -> m () Source #

A side-effecting map over the (key, value) records in a hash table

lookup :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m v Source #

Lookup a key in the hash table. If called straight in the IO monad it would throw a NotFound exception, but if called under MaybeT IO or ExceptT SomeException IO it would return IO Nothing or IO (Left NotFound) respectively. So you probably want to execute this function in one of these transformer monads

mutate :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> (Maybe v -> (Maybe v, a)) -> m a Source #

mutate an entry with the provided modification function. The tuple returned corresponds to the new value mapped to the key and a result to return from the mutate operation. Note that if the new value is Nothing then the entry is deleted if it exists or no change is performed if it didn't. If the value is Just v then the value is replaced or inserted depending on whether it was found or not respectively for that key.

new :: (HashTable h, MonadIO m, Failable m) => m (TTLHashTable h k v) Source #

Creates a new hash table with default settings

newWithSettings :: (HashTable h, MonadIO m, Failable m) => Settings -> m (TTLHashTable h k v) Source #

Creates a new hash table with the specified settings. Use the Default instance of Settings and then fine tune parameters as needed. I.e: newWithSettings def { maxSize = 64 }

reconfigure :: (MonadIO m, Failable m) => TTLHashTable h k v -> Settings -> m () Source #

Provide a new set of settings for a given hash table

removeExpired :: (MonadIO m, Eq k, Hashable k) => TTLHashTable h k v -> m Int Source #

Run garbage collection of expired entries in the table. It returns the number of expired entries left yet to be removed from the table, if the gcMaxEntries limit was reached before finishing cleaning up all old entries. Note that this function as well as all other operations in a hash table are not thread safe. If concurrent threads need to operate on the table, some concurrency primitive must be used to guarantee exclusive access.

size :: MonadIO m => TTLHashTable h k v -> m Int Source #

Report the current number of entries in the table, including those who have expired but haven't been garbage collected yet