Copyright | (c) Erick Gonzalez 2019 |
---|---|
License | BSD3 |
Maintainer | erick@codemonkeylabs.de |
Safe Haskell | None |
Language | Haskell2010 |
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
- data TimeStamp
- data TTLHashTable h k v
- data TTLHashTableError
- data Settings = Settings {
- maxSize :: Int
- defaultTTL :: Int
- gcMaxEntries :: Int
- insert :: (Eq k, Hashable k, HashTable h, MonadIO m, Failable m) => TTLHashTable h k v -> k -> v -> m ()
- insert_ :: (Eq k, Hashable k, HashTable h, MonadIO m) => TTLHashTable h k v -> k -> v -> m ()
- insertWithTTL :: (Eq k, Hashable k, HashTable h, MonadIO m, Failable m) => TTLHashTable h k v -> Int -> k -> v -> m ()
- insertWithTTL_ :: (Eq k, Hashable k, HashTable h, MonadIO m) => TTLHashTable h k v -> Int -> k -> v -> m ()
- delete :: (HashTable h, Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m ()
- find :: (Eq k, Hashable k, MonadIO m) => TTLHashTable h k v -> k -> m (Maybe v)
- foldM :: MonadIO m => (a -> (k, v) -> IO a) -> a -> TTLHashTable h k v -> m a
- getSettings :: MonadIO m => TTLHashTable h k v -> m Settings
- getTimeStamp :: MonadIO m => m TimeStamp
- mapM_ :: MonadIO m => ((k, v) -> IO a) -> TTLHashTable h k v -> m ()
- lookup :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m v
- lookupAndRenew :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m v
- lookupMaybeExpired :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m (v, TimeStamp)
- mutate :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> (Maybe v -> (Maybe v, a)) -> m a
- new :: (HashTable h, MonadIO m, Failable m) => m (TTLHashTable h k v)
- newWithSettings :: (HashTable h, MonadIO m, Failable m) => Settings -> m (TTLHashTable h k v)
- reconfigure :: (MonadIO m, Failable m) => TTLHashTable h k v -> Settings -> m ()
- removeExpired :: (MonadIO m, Eq k, Hashable k) => TTLHashTable h k v -> m Int
- size :: MonadIO m => TTLHashTable h k v -> m Int
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
A representation of a point in time, used to track entry lifetime.
Instances
Enum TimeStamp Source # | |
Defined in Data.TTLHashTable succ :: TimeStamp -> TimeStamp # pred :: TimeStamp -> TimeStamp # fromEnum :: TimeStamp -> Int # enumFrom :: TimeStamp -> [TimeStamp] # enumFromThen :: TimeStamp -> TimeStamp -> [TimeStamp] # enumFromTo :: TimeStamp -> TimeStamp -> [TimeStamp] # enumFromThenTo :: TimeStamp -> TimeStamp -> TimeStamp -> [TimeStamp] # | |
Eq TimeStamp Source # | |
Integral TimeStamp Source # | |
Defined in Data.TTLHashTable | |
Num TimeStamp Source # | |
Ord TimeStamp Source # | |
Defined in Data.TTLHashTable | |
Real TimeStamp Source # | |
Defined in Data.TTLHashTable toRational :: TimeStamp -> Rational # |
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)
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 |
Instances
Eq TTLHashTableError Source # | |
Defined in Data.TTLHashTable (==) :: TTLHashTableError -> TTLHashTableError -> Bool # (/=) :: TTLHashTableError -> TTLHashTableError -> Bool # | |
Show TTLHashTableError Source # | |
Defined in Data.TTLHashTable showsPrec :: Int -> TTLHashTableError -> ShowS # show :: TTLHashTableError -> String # showList :: [TTLHashTableError] -> ShowS # | |
Exception TTLHashTableError Source # | |
Defined in Data.TTLHashTable |
The Settings
type allows for specifying how the hash table should behave.
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 #
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.
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
getSettings :: MonadIO m => TTLHashTable h k v -> m Settings Source #
getTimeStamp :: MonadIO m => m TimeStamp Source #
Returns a timestamp for the current moment (now). This value can be used when
| comparing expiration times manually as returned by lookupMaybeExpired
for example,
| when it makes sense to do so in the name of performance.
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
lookupAndRenew :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m v Source #
Like lookup but it restarts the lifetime of the entry if found. Note that this is not a read only operation (i.e. the entry must be of course modified to update its timestamp)
lookupMaybeExpired :: (Eq k, Hashable k, MonadIO m, Failable m) => TTLHashTable h k v -> k -> m (v, TimeStamp) Source #
Perform a lookup without doing any actual checks to see if the entry is still alive or if it has expired. Instead, the entry expiration timestamp is returned together with the value (if found). The purpose of this function is to provide a manual way to check expiration, for example when performing batch lookups or sacrificing lifetime resolution for the sake of performance (and thus avoiding an expensive timestamp retrieval every time a lookup is performed)
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 #
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.