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

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

Caching.ExpiringCacheMap.OrdECM

Contents

Description

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 #-}
module Example where

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)))
        12000 -- Time check frequency: (accumulator `mod` this_number) == 0.
        (CacheWithLRUList
          6     -- Expected size of key-value map when removing elements.
          6     -- Size of list 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 :: 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.

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.

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. 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 defined when the ECM value was created is invoked for the current time to determine of which if any of the entries in the cache state map needs to be removed. 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.

Type

data ECM a b s m k v Source

The type that encapsulates a cache map.