Copyright | (c) 2014 Edward L. Blake |
---|---|
License | BSD-style |
Maintainer | Edward L. Blake <edwardlblake@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
A cache that holds values for a length of time that uses Ord
keys with
Data.Map.Strict.
An example of creating a cache for accessing files:
{-# LANGUAGE OverloadedStrings #-} import Caching.ExpiringCacheMap.OrdECM (newECMIO, lookupECM, CacheSettings(..), consistentDuration) import qualified Data.Time.Clock.POSIX as POSIX (POSIXTime, getPOSIXTime) import qualified Data.ByteString.Char8 as BS import System.IO (withFile, IOMode(ReadMode)) example = do filecache <- newECMIO (consistentDuration 100 -- Duration between access and expiry time of each item (\state id -> do BS.putStrLn "Reading a file again..." withFile (case id :: BS.ByteString of "file1" -> "file1.txt" "file2" -> "file2.txt") ReadMode $ \fh -> do content <- BS.hGetContents fh return $! (state, content))) (do time <- POSIX.getPOSIXTime return (round (time * 100))) 1 -- Time check frequency: (accumulator `mod` this_number) == 0. (CacheWithLRUList 6 -- Expected size of key-value map when removing elements. 6 -- Size of map when to remove items from key-value map. 12 -- Size of list when to compact ) -- Use lookupECM whenever the contents of "file1" is needed. b <- lookupECM filecache "file1" BS.putStrLn b return ()
- newECMIO :: Ord k => (Maybe s -> k -> IO (TimeUnits, (Maybe s, v))) -> IO TimeUnits -> ECMIncr -> CacheSettings -> IO (ECM IO MVar s Map k v)
- newECMForM :: (Monad m1, Monad m2) => Ord k => (Maybe s -> k -> m1 (TimeUnits, (Maybe s, v))) -> m1 TimeUnits -> ECMIncr -> CacheSettings -> ECMNewState m2 mv s Map k v -> ECMEnterState m1 mv s Map k v -> ECMReadState m1 mv s Map k v -> m2 (ECM m1 mv s Map k v)
- consistentDuration :: (Monad m, Ord k) => TimeUnits -> (Maybe s -> k -> m (Maybe s, v)) -> Maybe s -> k -> m (TimeUnits, (Maybe s, v))
- lookupECM :: (Monad m, Ord k) => ECM m mv s Map k v -> k -> m v
- getValReqState :: (Monad m, Ord k) => ECM m mv s Map k v -> k -> m (Maybe s)
- invalidate :: (Monad m, Ord k) => ECM m mv s Map k v -> k -> m (Maybe v)
- invalidateCache :: (Monad m, Ord k) => ECM m mv s Map k v -> m (Maybe (k, v))
- keysCached :: (Monad m, Ord k) => ECM m mv s Map k v -> m [k]
- keysNotExpired :: (Monad m, Ord k) => ECM m mv s Map k v -> m [k]
- data ECM a b s m k v
- data CacheSettings = CacheWithLRUList {}
Create cache
newECMIO :: Ord k => (Maybe s -> k -> IO (TimeUnits, (Maybe s, v))) -> IO TimeUnits -> ECMIncr -> CacheSettings -> IO (ECM IO MVar s Map k v) Source #
Create a new expiring cache for retrieving uncached values via IO
interaction (such as in the case of reading a file from disk), with
a shared state lock via an MVar
to manage cache state.
Value request and time check request functions are provided as arguments.
The time check frequency value has to be 1 or higher, with higher values postponing time checks for longer periods of time.
A cache setting specifies how the cache should remove entries when the
cache becomes a certain size. The only constructor for this is
CacheWithLRUList
.
newECMForM :: (Monad m1, Monad m2) => Ord k => (Maybe s -> k -> m1 (TimeUnits, (Maybe s, v))) -> m1 TimeUnits -> ECMIncr -> CacheSettings -> ECMNewState m2 mv s Map k v -> ECMEnterState m1 mv s Map k v -> ECMReadState m1 mv s Map k v -> m2 (ECM m1 mv s Map k v) Source #
Create a new expiring cache along arbitrary monads with provided
functions to create cache state in Monad
m2, and modify and read
cache state in Monad
m1.
newECMIO
is just a wrapper to this function with MVar
functions:
newECMIO retr gettime timecheckmodulo cachesettings = newECMForM retr gettime timecheckmodulo cachesettingsnewMVar
modifyMVar
readMVar
Value request and time check request functions are provided as arguments.
The time check frequency value has to be 1 or higher, with higher values postponing time checks for longer periods of time.
A cache setting specifies how the cache should remove entries when the
cache becomes a certain size. The only constructor for this is
CacheWithLRUList
.
consistentDuration :: (Monad m, Ord k) => TimeUnits -> (Maybe s -> k -> m (Maybe s, v)) -> Maybe s -> k -> m (TimeUnits, (Maybe s, v)) Source #
Used with newECMIO
or newECMForM
to provide a consistent duration for requested values.
Request value from cache
lookupECM :: (Monad m, Ord k) => ECM m mv s Map k v -> k -> m v Source #
Request a value associated with a key from the cache.
- If the value is not in the cache, it will be requested through the
function defined through
newECM
, its computation returned and the value stored in the cache state map. - If the value is in the cache and has not expired, it will be returned.
- If the value is in the cache and a new time is computed in the same lookup, and the value has been determined to have since expired, it will be discarded and a new value will be requested for this computation.
Every lookupECM
computation increments an accumulator in the cache state
which is used to keep track of the succession of key accesses. Based on the
parameters provided with the CacheWithLRUList
constructor, this history
of key accesses is then used to remove entries from the cache back down to
a minimum size. Also, when the modulo of the accumulator and the modulo
value computes to 0, the time request function is invoked. In some cases
the accumulator may get incremented more than once in a lookupECM
computation.
As the accumulator is a bound unsigned integer, when the accumulator increments back to 0, the cache state is completely cleared.
The time request function is invoked in one of two different conditions
- When a new key-value entry is requested, the current time is also requested during the same lookup, as a recent time determination is needed for a new entry in the key-value cache.
- When the modulo of the accumulator and a specified value equals to 0.
When the current time is determined during a lookup, access times of the entries in the key-value cache are compared with the new time to filter out expired entries from the key-value map.
Value request function state
Invalidate cache
invalidate :: (Monad m, Ord k) => ECM m mv s Map k v -> k -> m (Maybe v) Source #
Invalidates a key from the cache and returns its value if any.
Note that this is a sequential composition of a read and modify of the
mutable cache container (e.g. readMVar
followed by modifyMVar
with newECMIO
instances).
invalidateCache :: (Monad m, Ord k) => ECM m mv s Map k v -> m (Maybe (k, v)) Source #
Invalidates the entire cache and returns the last key and value if any.
Note that this is a sequential composition of a read and modify of the
mutable cache container (e.g. readMVar
followed by modifyMVar
with newECMIO
instances).
List keys
keysCached :: (Monad m, Ord k) => ECM m mv s Map k v -> m [k] Source #
List of keys in the cache map without performing a time check, returning both stored keys that are expired and keys that are not expired. keys are in an unspecified order.
keysNotExpired :: (Monad m, Ord k) => ECM m mv s Map k v -> m [k] Source #
List of keys in the cache map that are not expired values. A time check
is always performed to compare with the elapsed time left with each key.
The cache state is not modified and the time check is not performed from
within a modifying state context, e.g. not within modifyMVar
with a
newECMIO
instance. Keys are in an unspecified order.
Type
data CacheSettings Source #
CacheWithLRUList | A cache that maintains a key access history list to perform removals
of least recently used entries. Once the key-value map reaches
Key access history entries are prepended to the head of the LRU list,
if an existing entry for the key appears close to the head of the list
it is moved to the head of the list, instead of growing the list. When the
LRU list reaches |