cache-0.1.3.0: An in-memory key/value store with expiration support

Copyright(c) 2016 Henri Verroken
LicenseBSD3
MaintainerHenri Verroken <henriverroken@gmail.com>
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

Data.Cache

Contents

Description

An in-memory key/value store with expiration support, similar to patrickmn/go-cache for Go.

The cache is a shared mutable HashMap implemented using STM. It supports item expiration.

Synopsis

How to use this library

All operations are automically executed in the IO monad. The underlying data structure is Data.HashMap.Strict.

First create a cache using newCache and possibly a default expiration value. Items can now be inserted using insert and insert'.

lookup and lookup' are used to query items. These functions only return a value when the item is in the cache and it is not expired. The lookup function will automatically delete the item if it is expired, while lookup' won't delete the item.

Note that items are not purged automatically in the background when they expire. You have to manually call lookup to purge a single item, or call purgeExpired to purge all expired items.

>>> c <- newCache Nothing :: IO (Cache String String)
>>> insert c "key" "value"
>>> lookup c "key"
Just "value"
>>> delete c "key"
>>> lookup c "key"
Nothing

Creating a cache

data Cache k v Source #

The cache with keys of type k and values of type v.

Create caches with the newCache and copyCache functions.

newCache :: Maybe TimeSpec -> IO (Cache k v) Source #

Create a new cache with a default expiration value for newly added cache items.

Items that are added to the cache without an explicit expiration value (using insert) will be inserted with the default expiration value.

If the specified default expiration value is Nothing, items inserted by insert will never expire.

newCacheSTM :: Maybe TimeSpec -> STM (Cache k v) Source #

STM variant of newCache

Cache properties

defaultExpiration :: Cache k v -> Maybe TimeSpec Source #

The default expiration value of newly added cache items.

See newCache for more information on the default expiration value.

setDefaultExpiration :: Cache k v -> Maybe TimeSpec -> Cache k v Source #

Change the default expiration value of newly added cache items.

See newCache for more information on the default expiration value.

copyCache :: Cache k v -> IO (Cache k v) Source #

Create a deep copy of the cache.

Managing items

Insertion

insert :: (Eq k, Hashable k) => Cache k v -> k -> v -> IO () Source #

Insert an item in the cache, using the default expiration value of the cache.

insert' :: (Eq k, Hashable k) => Cache k v -> Maybe TimeSpec -> k -> v -> IO () Source #

Insert an item in the cache, with an explicit expiration value.

If the expiration value is Nothing, the item will never expire. The default expiration value of the cache is ignored.

The expiration value is relative to the current Monotonic time, i.e. it will be automatically added to the result of getTime Monotonic.

insertSTM :: (Eq k, Hashable k) => k -> v -> Cache k v -> Maybe TimeSpec -> STM () Source #

Insert an item in the cache, with an explicit expiration value, in the STM monad.

If the expiration value is Nothing, the item will never expire. The default expiration value of the cache is ignored.

The expiration value is the absolute Monotonic time the item expires. You should manually construct the absolute Monotonic time, as opposed to the behaviour of insert'.

E.g.

action :: Cache -> IO ()
action c = do
    t <- getTime Monotonic
    let t' = t + (defaultExpiration c)
    atomically $ insertSTM 0 0 c (Just t')

Querying

lookup :: (Eq k, Hashable k) => Cache k v -> k -> IO (Maybe v) Source #

Lookup an item with the given key, and delete it if it is expired.

The function will only return a value if it is present in the cache and if the item is not expired.

The function will eagerly delete the item from the cache if it is expired.

lookup' :: (Eq k, Hashable k) => Cache k v -> k -> IO (Maybe v) Source #

Lookup an item with the given key, but don't delete it if it is expired.

The function will only return a value if it is present in the cache and if the item is not expired.

The function will not delete the item from the cache.

lookupSTM Source #

Arguments

:: (Eq k, Hashable k) 
=> Bool

Whether or not to eagerly delete the item if its expired

-> k

The key to lookup

-> Cache k v

The cache

-> TimeSpec

The current Monotonic time, i.e. getTime Monotonic

-> STM (Maybe v) 

Lookup an item with a given key in the STM monad, given the current Monotonic time.

STM variant of lookup and lookup'

keys :: Cache k v -> IO [k] Source #

Return all keys present in the cache.

keysSTM :: Cache k v -> STM [k] Source #

STM variant of keys.

Deletion

delete :: (Eq k, Hashable k) => Cache k v -> k -> IO () Source #

Delete an item from the cache. Won't do anything if the item is not present.

deleteSTM :: (Eq k, Hashable k) => k -> Cache k v -> STM () Source #

STM variant of delete.

filterWithKey :: (Eq k, Hashable k) => (k -> v -> Bool) -> Cache k v -> IO () Source #

Keeps elements that satify a predicate (used for cache invalidation). Note that the predicate might be called for expired items.

purge :: (Eq k, Hashable k) => Cache k v -> IO () Source #

Delete all elements (cache invalidation).

purgeExpired :: (Eq k, Hashable k) => Cache k v -> IO () Source #

Delete all items that are expired.

This is one big atomic operation.

purgeExpiredSTM :: (Eq k, Hashable k) => Cache k v -> TimeSpec -> STM () Source #

STM variant of purgeExpired.

The TimeSpec argument should be the current Monotonic time, i.e. getTime Monotonic.

Combined actions

fetchWithCache :: (Eq k, Hashable k, MonadIO m) => Cache k v -> k -> (k -> m v) -> m v Source #

Get a value from cache. If not available from cache, use the provided action and update the cache. Note that the cache check and conditional execution of the action is not one atomic action.

Cache information

size :: Cache k v -> IO Int Source #

Return the size of the cache, including expired items.

sizeSTM :: Cache k v -> STM Int Source #

STM variant of size

toList :: Cache k v -> IO [(k, v, Maybe TimeSpec)] Source #

Returns the cache content as a list. The third element of the tuple is the expiration date. Nothing means that it doesn't expire.