expiring-cache-map-0.0.5.3: 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.Utils.TestSequence

Description

TestSequence monad for testing caching behaviour.

 {-# LANGUAGE OverloadedStrings #-}
 
 import Caching.ExpiringCacheMap.HashECM (newECMForM, lookupECM, CacheSettings(..), consistentDuration)
 import qualified Caching.ExpiringCacheMap.Utils.TestSequence as TestSeq
 
 import qualified Data.ByteString.Char8 as BS
 
 test = do
   (TestSeq.TestSequenceState (_, events, _), return_value) <- TestSeq.runTestSequence test'
   (putStrLn . show . reverse) events
   return ()
   where
     test' = do
       filecache <- newECMForM
             (consistentDuration 100 -- Duration between access and expiry time of each item, no state needed.
               (\state _id -> do number <- TestSeq.readNumber
                                 return (state, number)))
             (TestSeq.getCurrentTime >>= return)
             12000 -- 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
               )
             TestSeq.newTestSVar TestSeq.enterTestSVar TestSeq.readTestSVar
       
       -- Use lookupECM whenever the contents of "file1" is needed.
       b <- lookupECM filecache ("file1" :: BS.ByteString)
       TestSeq.haveNumber b
       b <- lookupECM filecache "file1"
       b <- lookupECM filecache "file2"
       TestSeq.haveNumber b
       return b

Evaluating the test function results in a list of events.

>>> test
[GetVar 3,ReadNumber 4,GetTime 7,PutVar 11,HaveNumber 4,GetVar 14,PutVar 17,
 GetVar 19,ReadNumber 20,GetTime 23,PutVar 27,HaveNumber 20]

In this example the history shows 2 time accesses (GetTime 7 and GetTime 23) since the time check frequency number is a high value (12000), but regardless the high value a time check is still requested again because of the new key request for "file2".

Changing the time frequency to 1 will alter the list of events with more frequent time checks:

>>> test
[GetVar 3,ReadNumber 4,GetTime 7,PutVar 11,HaveNumber 4,GetVar 14,GetTime 15,
 GetTime 18,PutVar 22,GetVar 24,ReadNumber 25,GetTime 28,PutVar 32,
 HaveNumber 25]

Documentation

enterTestSVar :: TestSVar a -> (a -> TestSequence a (a, b)) -> TestSequence a b Source

newtype TestSequence b a Source

Instances

newtype TestSVar a Source

Constructors

TestSVar a