TCache-0.6.4: A Transactional data cache with configurable persistenceContentsIndex
Data.TCache.TMVar
Description
A version of Data.TCache using TMVars instead of TVarss. See Control.Concurrent.TMVar
Synopsis
class IResource a where
keyResource :: a -> String
serialize :: a -> String
deserialize :: String -> a
tshowp :: a -> ST String
treadp :: ST a
defPath :: a -> String
readResource :: a -> IO (Maybe a)
writeResource :: a -> IO ()
delResource :: a -> IO ()
data Resources a b
= Retry
| Resources {
toAdd :: [a]
toDelete :: [a]
toReturn :: b
}
resources :: Resources a ()
getTMVars :: IResource a => [a] -> STM [Maybe (TMVar a)]
getTMVarsIO :: IResource a => [a] -> IO [TMVar a]
withSTMResources :: IResource a => [a] -> ([Maybe a] -> Resources a x) -> STM x
withResources :: IResource a => [a] -> ([Maybe a] -> [a]) -> IO ()
withResource :: IResource a => a -> (Maybe a -> a) -> IO ()
getResources :: IResource a => [a] -> IO [Maybe a]
getResource
deleteResources
deleteResource
type Cache a = IORef (Ht a, Integer)
setCache :: (Ht a, Integer) -> IO ()
newCache :: IO (Ht a, Integer)
refcache :: Cache a
syncCache
clearSyncCacheProc :: IResource a => Cache a -> Int -> (Integer -> Integer -> Integer -> Bool) -> Int -> IO ThreadId
defaultCheck :: Integer -> Integer -> Integer -> Bool
readFileStrict
Documentation
class IResource a where

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
keyResource
:: a
-> Stringmust be defined
serialize
:: a
-> Stringmust be defined by the user
deserialize
:: String
-> amust be defined by the user
tshowp
:: a
-> ST Stringserializer in the RefSerialize monad. Either one or other serializer must be defined to use default persistence
treadp
:: ST adeserialize in the RefSerilzlize monad.
defPath
:: a
-> Stringadditional extension for default file paths or key prefixes
readResource :: a -> IO (Maybe a)
writeResource :: a -> IO ()
delResource :: a -> IO ()
show/hide Instances
data Resources a b
Resources returned by withSTMResources'
Constructors
Retryforces a retry
Resources
toAdd :: [a]resources to be inserted back in the cache
toDelete :: [a]resources to be deleted from the cache and from permanent storage
toReturn :: bresult to be returned
resources :: Resources a ()
resources= Resources  [] [] ()
getTMVars :: IResource a => [a] -> STM [Maybe (TMVar a)]
getTMVars return the TMVar that wraps the resources for which the keys are given . | it return Nothing if a TMVar with this object has not been allocated These TMVars can be used in explicit user constructed atomic blocks Additionally, the TMVars remain in the cache and can be accessed and updated by the rest of the TCache methods. the content of the TMVars are written every time the cache is syncronized with the storage until releaseTMVars is called
getTMVarsIO :: IResource a => [a] -> IO [TMVar a]
getTMVarsIO does not search for a TMVar in the cache like getTMVars. Instead of this getTMVarsIO creates a list of TMVars with the content given in the list of resourcees and add these TMVars to the cache and return them. the content of the TMVars are written every time the cache is syncronized with the storage until releaseTMVars is called
withSTMResources
:: IResource a
=> [a]the list of resources to be retrieved
-> [Maybe a] -> Resources a xThe function that process the resources found and return a Resources structure
-> STM xThe return value in the STM monad.
this is the main function for the *Resources primitivas, all the rest derive from it. the Res structure processed by the with*Resources primitives are more efficient for cached TMVars because the internal loop is never retried, since all the necessary resources at the beginning so no costly retries are necessary. The advantage increases with the complexity of the process function passed to withSTMResources is interpreted as such: -toUpdate secton is used to update the retrieved resources in the same order. if the resource dont exist, it is created. Nothing means do nothing as usual. extra resources are not considered, it uses the rules of zip. -toAdd: additional resources not read in the first parameter of withSTMResources are created/updated with toAdd -toDelete: obvious -toReturn: will be returned by the call
withResources :: IResource a => [a] -> ([Maybe a] -> [a]) -> IO ()
to atomically add/modify many objects in the cache :: (IResource a)=> [a] list of resources to be retrieve -> ([Maybe a]-> [a]) function that process the retrieved resources -> IO () and return a list of objects to be inserted/modified
withResource :: IResource a => a -> (Maybe a -> a) -> IO ()
update of a single object in the cache :: (IResource a)=> a same as withResources , but for one only object -> ([Maybe a]-> a) -> IO ()
getResources :: IResource a => [a] -> IO [Maybe a]
to read a resource from the cache
getResource
deleteResources
deleteResource
type Cache a = IORef (Ht a, Integer)
setCache :: (Ht a, Integer) -> IO ()
set the cache. this is useful for hot loaded modules that will update an existing cache
newCache :: IO (Ht a, Integer)
newCache creates a new cache
refcache :: Cache a
syncCache
clearSyncCacheProc :: IResource a => Cache a -> Int -> (Integer -> Integer -> Integer -> Bool) -> Int -> IO ThreadId
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 --The cache reference -> 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
defaultCheck :: Integer -> Integer -> Integer -> Bool
To drop from the cache all the elems not accesed since half the time between now and the last sync the default check procedure :: 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
readFileStrict
Produced by Haddock version 2.4.2