expiring-cache-map-0.0.6.0: General purpose simple caching.

Copyright(c) 2014 Edward L. Blake
LicenseBSD-style
MaintainerEdward L. Blake <edwardlblake@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Caching.ExpiringCacheMap.HashECM

Contents

Description

A cache that holds values for a length of time that uses Hashable keys with Data.HashMap.Strict.

An example of creating a cache for accessing files:

{-# LANGUAGE OverloadedStrings #-}

import Caching.ExpiringCacheMap.HashECM (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 ()

Synopsis

Create cache

newECMIO :: (Eq k, Hashable k) => (Maybe s -> k -> IO (TimeUnits, (Maybe s, v))) -> IO TimeUnits -> ECMIncr -> CacheSettings -> IO (ECM IO MVar s HashMap 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) => (Eq k, Hashable k) => (Maybe s -> k -> m1 (TimeUnits, (Maybe s, v))) -> m1 TimeUnits -> ECMIncr -> CacheSettings -> ECMNewState m2 mv s HashMap k v -> ECMEnterState m1 mv s HashMap k v -> ECMReadState m1 mv s HashMap k v -> m2 (ECM m1 mv s HashMap 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 cachesettings
     newMVar 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, Eq k, Hashable 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, Eq k, Hashable k) => ECM m mv s HashMap k v -> k -> m v Source #

Request a value associated with a key from the cache.

  • If the value is not in the cache, the value will be requested through the function defined when the ECM value was created, 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

getValReqState :: (Monad m, Eq k, Hashable k) => ECM m mv s HashMap k v -> k -> m (Maybe s) Source #

Invalidate cache

invalidate :: (Monad m, Eq k, Hashable k) => ECM m mv s HashMap k v -> k -> m (Maybe v) Source #

Invalidates a key from the cache and returns its value if any. Note this is a sequential composition of a read and modify of the mutable cache container (readMVar and modifyMVar with newECMIO).

invalidateCache :: (Monad m, Eq k, Hashable k) => ECM m mv s HashMap k v -> m (Maybe (k, v)) Source #

Invalidates the entire cache and returns the last key and value if any. Note this is a sequential composition of a read and modify of the mutable cache container (readMVar and modifyMVar with newECMIO).

List keys

keysCached :: (Monad m, Eq k, Hashable k) => ECM m mv s HashMap k v -> m [k] Source #

List of keys in the cache map, which can contain expired values, since the list is returned without performing a time check. keys are in an unspecified order.

keysNotExpired :: (Monad m, Eq k, Hashable k) => ECM m mv s HashMap 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 the elapsed time and the cache state is not modified. 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 ECM a b s m k v Source #

The type that encapsulates a cache map.

data CacheSettings Source #

Constructors

CacheWithLRUList

A cache that maintains a key access history list to perform removals of least recently used entries. Once the key-value map reaches removalsize keys, then a list of keys to keep in the map is determined which is no larger than mapsize size. Entries are removed only on insertion of a new entry in the key-value map.

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 compactlistsize items, it is compacted by removing duplicate keys, by keeping only the most recent accumulator value for that key.