TCache-0.6.5: A Transactional data cache with configurable persistence

Data.TCache

Synopsis

Documentation

class IResource a whereSource

Interface that must be defined for every object being cached. readResource and writeResource are implemented by default as read-write to files with its key as filename serialize and deserialize are specified just to allow these defaults. If you define your own persistence, then serialize and deserialize are not needed. The package Workflow need them anyway.

minimal definition: keyResource, serialize, deserialize

While serialize and deserialize are agnostic about the way of converison to strings, either binary or textual, treadp and tshowp use the monad defined in the RefSerialize package. Both ways of serialization are alternative. one is defined by default in terms of the other. the RefSerialize monad has been introduced to permit IResource objects to be serialized as part of larger structures that embody them. This is necessary for the Workdlow package.

The keyResource string must be a unique since this is used to index it in the hash table. when accessing a resource, the user must provide a partial object for wich the key can be obtained. for example:

data Person= Person{name, surname:: String, account :: Int ....)

keyResource Person n s ...= n++s

the data being accesed must have the fields used by keyResource filled. For example

  readResource Person {name=John, surname= Adams}

leaving the rest of the fields undefined

IResource has defaults definitions for all the methods except keyResource Either one or other serializer must be defiened for default witeResource, readResource and delResource

Methods

keyResourceSource

Arguments

:: a 
-> String

must be defined

serializeSource

Arguments

:: a 
-> String

must be defined by the user

deserializeSource

Arguments

:: String 
-> a

must be defined by the user

tshowpSource

Arguments

:: a 
-> ST String

serializer in the RefSerialize monad. Either one or other serializer must be defined to use default persistence

treadpSource

Arguments

:: ST a

deserialize in the RefSerilzlize monad.

defPathSource

Arguments

:: a 
-> String

additional extension for default file paths or key prefixes

readResource :: a -> IO (Maybe a)Source

writeResource :: a -> IO ()Source

delResource :: a -> IO ()Source

data Resources a b Source

Resources returned by withSTMResources'

Constructors

Retry

forces a retry

Resources 

Fields

toAdd :: [a]

resources to be inserted back in the cache

toDelete :: [a]

resources to be deleted from the cache and from permanent storage

toReturn :: b

result to be returned

resources :: Resources a ()Source

resources= Resources  [] [] ()

getTVarsSource

Arguments

:: IResource a 
=> [a] 
-> STM [Maybe (TVar a)]

The TVars that contain such objects

getTVars return the TVar that wraps the resources for which the keys are given . | it return Nothing if a TVar with this object has not been allocated These TVars can be used as usual in explicit user constructed atomic blocks Additionally, the retrieved TVars remain in the cache and can be accessed and updated by the rest of the TCache methods. to keep the consistence in the serialized data, the content of the TVars are written every time the cache is syncronized with the storage until releaseTVars is called

releaseTVars :: IResource a => [a] -> STM ()Source

releaseTVars permits the TVars captured by getTVars to be released. so they can be discarded when not used. Do this when you no longer need to use them directly in atomic blocks.

getTVarsIO :: IResource a => [a] -> IO [TVar a]Source

getTVarsIO does not search for a TVar in the cache like getTVars. Instead of this getTVarsIO creates a list of TVars with the content given in the list of resourcees and add these TVars to the cache and return them. the content of the TVars are written every time the cache is syncronized with the storage until releaseTVars is called

withSTMResourcesSource

Arguments

:: IResource a 
=> [a]

the list of resources to be retrieved

-> ([Maybe a] -> Resources a x)

The function that process the resources found and return a Resources structure

-> STM x

The return value in the STM monad.

this is the main function for the *Resource calls. All the rest derive from it. The results are kept in the STM monad so it can be part of a larger STM transaction involving other TVars The Resources register returned by the user-defined function is interpreted as such:

toAdd: additional resources not read in the first parameter of withSTMResources are created/updated with toAdd

toDelete: from the cache and from permanent storage

toReturn: will be returned by withSTMResources

withResources :: IResource a => [a] -> ([Maybe a] -> [a]) -> IO ()Source

to atomically add/modify many objects in the cache

 withResources rs f=  atomically $ withSTMResources rs f1 >> return() where   f1 mrs= let as= f mrs in  Resources  as [] ()

withResourceSource

Arguments

:: IResource a 
=> a

prototypes of the object to be retrieved for which keyResource can be derived

-> (Maybe a -> a)

update function that return another full object

-> IO () 

update of a single object in the cache

withResource r f= withResources [r] ([mr]-> [f mr])

getResource :: IResource a => a -> IO (Maybe a)Source

to read a resource from the cache.

getResource r= do{mr<- getResources [r];return $! head mr}

deleteResources :: IResource a => [a] -> IO ()Source

delete the list of resources from cache and from persistent storage.

  deleteResources rs= atomically $ withSTMResources rs f1 where  f1 mrs = Resources  [] (catMaybes mrs) ()

deleteResource :: IResource a => a -> IO ()Source

delete the resource from cache and from persistent storage.

 deleteResource r= deleteResources [r]

type Cache a = IORef (Ht a, Integer)Source

setCache :: (Ht a, Integer) -> IO ()Source

set the cache. this is useful for hot loaded modules that will update an existing cache. Experimental

newCache :: IO (Ht a, Integer)Source

newCache creates a new cache. Experimental

syncCacheSource

Arguments

:: IResource a 
=> Cache a

the cache reference ( refcache usually)

-> IO () 

Force the atomic write of all the cached objects into permanent storage useful for termination

clearSyncCacheProcSource

Arguments

:: IResource a 
=> Cache a

The cache reference (refcache usually)

-> Int

number of seconds betwen checks. objects not written to disk are written

-> (Integer -> Integer -> Integer -> Bool)

The user-defined check-for-cleanup-from-cache for each object. defaultCheck is an example

-> Int

The max number of objects in the cache, if more, the cleanup starts

-> IO ThreadId

Identifier of the thread created

Cache handling

Start the thread that clean and writes on the persistent storage. Otherwise, clearSyncCache must be invoked explicitly or no persistence will exist :: (IResource a) =>Cache a -> Int --number of seconds betwen checks -> (Integer-> Integer-> Bool) --The user-defined check-for-cleanup-from-cache for each object (when this function return True, the object is removed from cache) -> Int --The max number of objects in the cache, if more, the cleanup start -> >IO ThreadId --Identifier of the thread created

defaultCheckSource

Arguments

:: Integer

current time in seconds

-> Integer

last access time for a given object

-> Integer

last cache syncronization (with the persisten storage)

-> Bool

return true for all the elems not accesed since half the time between now and the last sync

To drop from the cache all the elems not accesed since half the time between now and the last sync ths is a default cache clearance procedure -- it is invoke when the cache size exceeds the defined in clearSyncCacheProc