TCache-0.10.0.11: A Transactional cache with user-defined persistence

Safe HaskellNone

Data.TCache

Contents

Description

TCache is a transactional cache with configurable persitence that permits STM transactions with objects that syncronize sincromous or asyncronously with their user defined storages. Default persistence in files is provided by default

TCache implements ''DBRef' 's . They are persistent STM references with a typical Haskell interface. simitar to TVars (newDBRef, readDBRef, writeDBRef etc) but with added. persistence . DBRefs are serializable, so they can be stored and retrieved. Because they are references,they point to other serializable registers. This permits persistent mutable Inter-object relations

For simple transactions of lists of objects of the same type TCache implements inversion of control primitives withSTMResources and variants, that call pure user defined code for registers update. Examples below.

Triggers in Data.TCache.Triggers are user defined hooks that are called back on register updates. .They are used internally for indexing.

Data.TCache.IndexQuery implements an straighforwards pure haskell type safe query language based on register field relations. This module must be imported separately.

Data.TCache.IndexText add full text search and content search to the query language

Data.TCache.DefaultPersistence has instances for key indexation , serialization and default file persistence. The file persistence is more reliable, and the embedded IO reads inside STM transactions are safe.

Data.Persistent.Collection implements a persistent, transactional collection with Queue interface as well as indexed access by key

Synopsis

Inherited from STM and variations

atomically :: STM a -> IO a

Perform a series of STM actions atomically.

You cannot use atomically inside an unsafePerformIO or unsafeInterleaveIO. Any attempt to do so will result in a runtime error. (Reason: allowing this would effectively allow a transaction inside a transaction, depending on exactly when the thunk is evaluated.)

However, see newTVarIO, which can be called inside unsafePerformIO, and which allows top-level TVars to be allocated.

atomicallySync :: STM a -> IO aSource

Perform a synchronization of the cache with permanent storage once executed the STM transaction when syncWrite policy is Synchronous

data STM a

A monad supporting atomic memory transactions.

Instances

Monad STM 
Functor STM 
Typeable1 STM 
MonadFix STM 
MonadPlus STM 
(Typeable reg, IResource reg) => Select (reg -> a) (STM [DBRef reg]) (STM [a]) 
(Typeable reg, IResource reg, Select (reg -> a) (STM [DBRef reg]) (STM [a]), Select (reg -> b) (STM [DBRef reg]) (STM [b])) => Select (reg -> a, reg -> b) (STM [DBRef reg]) (STM [(a, b)]) 
(Typeable reg, IResource reg, Select (reg -> a) (STM [DBRef reg]) (STM [a]), Select (reg -> b) (STM [DBRef reg]) (STM [b]), Select (reg -> c) (STM [DBRef reg]) (STM [c])) => Select (reg -> a, reg -> b, reg -> c) (STM [DBRef reg]) (STM [(a, b, c)]) 
(Typeable reg, IResource reg, Select (reg -> a) (STM [DBRef reg]) (STM [a]), Select (reg -> b) (STM [DBRef reg]) (STM [b]), Select (reg -> c) (STM [DBRef reg]) (STM [c]), Select (reg -> d) (STM [DBRef reg]) (STM [d])) => Select (reg -> a, reg -> b, reg -> c, reg -> d) (STM [DBRef reg]) (STM [(a, b, c, d)]) 

unsafeIOToSTM :: IO a -> STM a

Unsafely performs IO in the STM monad. Beware: this is a highly dangerous thing to do.

  • The STM implementation will often run transactions multiple times, so you need to be prepared for this if your IO has any side effects.
  • The STM implementation will abort transactions that are known to be invalid and need to be restarted. This may happen in the middle of unsafeIOToSTM, so make sure you don't acquire any resources that need releasing (exception handlers are ignored when aborting the transaction). That includes doing any IO using Handles, for example. Getting this wrong will probably lead to random deadlocks.
  • The transaction may have seen an inconsistent view of memory when the IO runs. Invariants that you expect to be true throughout your program may not be true inside a transaction, due to the way transactions are implemented. Normally this wouldn't be visible to the programmer, but using unsafeIOToSTM can expose it.

safeIOToSTM :: IO a -> STM aSource

Assures that the IO computation finalizes no matter if the STM transaction is aborted or retried. The IO computation run in a different thread. The STM transaction wait until the completion of the IO procedure (or retry as usual).

It can be retried if the embedding STM computation is retried so the IO computation must be idempotent. Exceptions are bubbled up to the STM transaction

Operations with cached database references

DBRefs are persistent cached database references in the STM monad with read/write primitives, so the traditional syntax of Haskell STM references can be used for interfacing with databases. As expected, the DBRefs are transactional, because they operate in the STM monad.

A DBRef is associated with its referred object trough its key. Since DBRefs are serializable, they can be elements of mutable cached objects themselves. They could point to other mutable objects and so on, so DBRefs can act as "hardwired" relations from mutable objects to other mutable objects in the database/cache. their referred objects are loaded, saved and flused to and from the cache automatically depending on the cache handling policies and the access needs

DBRefs are univocally identified by its pointed object keys, so they can be compared, ordered checked for equality so on. The creation of a DBRef, trough getDBRef is pure. This permits an efficient lazy access to the registers trouth their DBRefs by lazy marshalling of the register content on demand.

Example: Car registers have references to Person regiters

data Person= Person {pname :: String} deriving  (Show, Read, Eq, Typeable)
data Car= Car{owner :: DBRef Person , cname:: String} deriving (Show, Read, Eq, Typeable)

Here the Car register point to the Person register trough the owner field

To permit persistence and being refered with DBRefs, define the Indexable instance for these two register types:

instance Indexable Person where key Person{pname= n} = Person  ++ n
instance Indexable Car where key Car{cname= n} = Car  ++ n

Now we create a DBRef to a Person whose name is "Bruce"

>>> let bruce =   getDBRef . key $ Person "Bruce" :: DBRef Person
>>> show bruce
>"DBRef \"Person bruce\""
>>> atomically (readDBRef bruce)
>Nothing

getDBRef is pure and creates the reference, but not the referred object; To create both the reference and the DBRef, use newDBRef. Lets create two Car's and its two Car DBRefs with bruce as owner:

>>> cars <- atomically $  mapM newDBRef [Car bruce "Bat Mobile", Car bruce "Porsche"]
>>> print cars
>[DBRef "Car Bat Mobile",DBRef "Car Porsche"]
>>> carRegs<- atomically $ mapM readDBRef cars
> [Just (Car {owner = DBRef "Person bruce", cname = "Bat Mobile"})
> ,Just (Car {owner = DBRef "Person bruce", cname = "Porsche"})]

try to write with writeDBRef

>>> atomically . writeDBRef bruce $ Person "Other"
>*** Exception: writeDBRef: law of key conservation broken: old , new= Person bruce , Person Other

DBRef's can not be written with objects of different keys

>>> atomically . writeDBRef bruce $ Person "Bruce"
>>> let Just carReg1= head carRegs

now from the Car register it is possible to recover the owner's register

>>> atomically $ readDBRef ( owner carReg1)
>Just (Person {pname = "bruce"})

DBRefs, once the pointed cached object is looked up in the cache and found at creation, they does not perform any further cache lookup afterwards, so reads and writes from/to DBRefs are faster than *Resource(s) calls, which perform cache lookups everytime the object is accessed

DBRef's and *Resource(s) primitives are completely interoperable. The latter operate implicitly with DBRef's

data DBRef a Source

Instances

Typeable1 DBRef 
Eq (DBRef a) 
Ord (DBRef a) 
(IResource a, Typeable a) => Read (DBRef a) 
Show (DBRef a) 
Queriable reg a => RelationOps (reg -> a) a [DBRef reg] 
(Typeable reg, IResource reg) => Select (reg -> a) (STM [DBRef reg]) (STM [a]) 
(Typeable reg, IResource reg, Select (reg -> a) (STM [DBRef reg]) (STM [a]), Select (reg -> b) (STM [DBRef reg]) (STM [b])) => Select (reg -> a, reg -> b) (STM [DBRef reg]) (STM [(a, b)]) 
(Typeable reg, IResource reg, Select (reg -> a) (STM [DBRef reg]) (STM [a]), Select (reg -> b) (STM [DBRef reg]) (STM [b]), Select (reg -> c) (STM [DBRef reg]) (STM [c])) => Select (reg -> a, reg -> b, reg -> c) (STM [DBRef reg]) (STM [(a, b, c)]) 
(Typeable reg, IResource reg, Select (reg -> a) (STM [DBRef reg]) (STM [a]), Select (reg -> b) (STM [DBRef reg]) (STM [b]), Select (reg -> c) (STM [DBRef reg]) (STM [c]), Select (reg -> d) (STM [DBRef reg]) (STM [d])) => Select (reg -> a, reg -> b, reg -> c, reg -> d) (STM [DBRef reg]) (STM [(a, b, c, d)]) 

getDBRef :: (Typeable a, IResource a) => String -> DBRef aSource

Get the reference to the object in the cache. if it does not exist, the reference is created empty. Every execution of getDBRef returns the same unique reference to this key, so it can be safely considered pure. This is a property useful because deserialization of objects with unused embedded DBRef's do not need to marshall them eagerly. Tbis also avoid unnecesary cache lookups of the pointed objects.

keyObjDBRef :: DBRef a -> StringSource

Return the key of the object pointed to by the DBRef

newDBRef :: (IResource a, Typeable a) => a -> STM (DBRef a)Source

Create the object passed as parameter (if it does not exist) and -- return its reference in the IO monad. -- If an object with the same key already exists, it is returned as is -- If not, the reference is created with the new value. -- If you like to update in any case, use getDBRef and writeDBRef combined newDBRefIO :: (IResource a,Typeable a) => a -> IO (DBRef a) newDBRefIO x= do let key = keyResource x mdbref <- mDBRefIO key case mdbref of Right dbref -> return dbref

Left cache -> do tv<- newTVarIO DoNotExist let dbref= DBRef key tv w <- mkWeakPtr dbref . Just $ fixToCache dbref H.update cache key (CacheElem Nothing w) t <- timeInteger atomically $ do applyTriggers [dbref] [Just x] --debug (before ++key) writeTVar tv . Exist $ Elem x t t return dbref

Create the object passed as parameter (if it does not exist) and return its reference in the STM monad. If an object with the same key already exists, it is returned as is If not, the reference is created with the new value. If you like to update in any case, use getDBRef and writeDBRef combined if you need to create the reference and the reference content, use newDBRef

readDBRef :: (IResource a, Typeable a) => DBRef a -> STM (Maybe a)Source

Return the reference value. If it is not in the cache, it is fetched from the database.

writeDBRef :: (IResource a, Typeable a) => DBRef a -> a -> STM ()Source

Write in the reference a value The new key must be the same than the old key of the previous object stored otherwise, an error law of key conservation broken will be raised

WARNING: the value to be written in the DBRef must be fully evaluated. Delayed evaluations at serialization time can cause inconsistencies in the database. In future releases this will be enforced.

delDBRef :: (IResource a, Typeable a) => DBRef a -> STM ()Source

Delete the content of the DBRef form the cache and from permanent storage

IResource class

cached objects must be instances of IResource. Such instances can be implicitly derived trough auxiliary clasess for file persistence

class IResource a whereSource

Must be defined for every object to be cached.

Methods

keyResourceSource

Arguments

:: a 
-> String

must be defined

readResourceByKey :: String -> IO (Maybe a)Source

Implements the database access and marshalling of the object. while the database access must be strict, the marshaling must be lazy if, as is often the case, some parts of the object are not really accesed. If the object contains DBRefs, this avoids unnecesary cache lookups. This method is called inside atomically blocks. Since STM transactions retry, readResourceByKey may be called twice in strange situations. So it must be idempotent, not only in the result but also in the effect in the database . However, because it is executed by safeIOToSTM it is guaranteed that the execution is not interrupted.

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

writeResource :: a -> IO ()Source

To write into persistent storage. It must be strict. Since STM transactions may retry, writeResource must be idempotent, not only in the result but also in the effect in the database. . However, because it is executed by safeIOToSTM it is guaranteed that the execution is not interrupted. All the new obbects are writeen to the database on synchromization, so writeResource must not autocommit. Commit code must be located in the postcondition. (see setConditions) Since there is no provision for rollback from failure in writing to persistent storage, writeResource must retry until success.

delResource :: a -> IO ()Source

Delete the resource. It is called syncronously. So it must tocommit

Instances

Operations with cached objects

implement inversion of control primitives where the user defines the objects to retrive. The primitives then call a the defined function that, determines how to transform the objects retrieved,wich are sent back to the storage and a result is returned.

In this example "buy" is a transaction where the user buy an item. The spent amount is increased and the stock of the product is decreased:

data  Data=   User{uname:: String, uid:: String, spent:: Int} |
              Item{iname:: String, iid:: String, price:: Int, stock:: Int}
              deriving (Read, Show)

instance Indexable Data where
        key   User{uid=id}= id
        key   Item{iid=id}= id

user buy item=  withResources[user,item] buyIt
 where
    buyIt[Just us,Just it]
       | stock it > 0= [us',it']
       | otherwise   = error "stock is empty for this product"
      where
       us'= us{spent=spent us + price it}
       it'= it{stock= stock it-1}
    buyIt _ = error "either the user or the item (or both) does not exist"

data Resources a b Source

Resources data definition used 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

Empty resources: resources= Resources [] [] ()

withSTMResourcesSource

Arguments

:: (IResource a, Typeable 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(s) 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 DBRefs. The Resources register returned by the user-defined function is interpreted as such:

  • toAdd: the content of this field will be added/updated to the cache
  • toDelete: the content of this field will be removed from the cache and from permanent storage
  • toReturn: the content of this field will be returned by withSTMResources

WARNING: To catch evaluations errors at the right place, the values to be written must be fully evaluated. Errors in delayed evaluations at serialization time can cause inconsistencies in the database.

withResources :: (IResource a, Typeable 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 [] ()

withResource :: (IResource a, Typeable a) => a -> (Maybe a -> a) -> IO ()Source

Update of a single object in the cache

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

getResources :: (IResource a, Typeable a) => [a] -> IO [Maybe a]Source

To read a list of resources from the cache if they exist

| getResources rs= atomically $ withSTMResources rs f1 where f1 mrs= Resources [] [] mrs

getResource :: (IResource a, Typeable 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, Typeable 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, Typeable a) => a -> IO ()Source

Delete the resource from cache and from persistent storage.

 deleteResource r= deleteResources [r]

Trigger operations

Trriggers are called just before an object of the given type is created, modified or deleted. The DBRef to the object and the new value is passed to the trigger. The called trigger function has two parameters: the DBRef being accesed (which still contains the old value), and the new value. If the content of the DBRef is being deleted, the second parameter is Nothing. if the DBRef contains Nothing, then the object is being created

Example:

Every time a car is added, or deleted, the owner's list is updated. This is done by the user defined trigger addCar

 addCar pcar (Just(Car powner _ )) = addToOwner powner pcar
 addCar pcar Nothing  = readDBRef pcar >>= \(Just car)-> deleteOwner (owner car) pcar

addToOwner powner pcar=do
    Just owner <- readDBRef powner
    writeDBRef powner owner{cars= nub $ pcar : cars owner}

deleteOwner powner pcar= do
   Just owner <- readDBRef powner
   writeDBRef powner owner{cars= delete  pcar $ cars owner}

main= do
    addTrigger addCar
    putStrLn "create bruce's register with no cars"
    bruce <- atomically newDBRef $ Person "Bruce" []
    putStrLn "add two car register with \bruce\ as owner using the reference to the bruces register"
    let newcars= [Car bruce "Bat Mobile" , Car bruce "Porsche"]
    insert newcars
    Just bruceData <- atomically $ readDBRef bruce
    putStrLn "the trigger automatically updated the car references of the Bruce register"
    print . length $ cars bruceData
    print bruceData

gives:

 main
 2
 Person {pname = "Bruce", cars = [DBRef "Car Porsche",DBRef "Car Bat Mobile"]}

addTrigger :: (IResource a, Typeable a) => (DBRef a -> Maybe a -> STM ()) -> IO ()Source

Add an user defined trigger to the list of triggers Trriggers are called just before an object of the given type is created, modified or deleted. The DBRef to the object and the new value is passed to the trigger. The called trigger function has two parameters: the DBRef being accesed (which still contains the old value), and the new value. If the DBRef is being deleted, the second parameter is Nothing. if the DBRef contains Nothing, then the object is being created

Cache control

flushDBRef :: (IResource a, Typeable a) => DBRef a -> STM ()Source

Deletes the pointed object from the cache, not the database (see delDBRef) useful for cache invalidation when the database is modified by other process

flushKey :: String -> STM ()Source

flush the element with the given key

invalidateKey :: String -> STM ()Source

label the object as not existent in database

flushAll :: STM ()Source

drops the entire cache.

setCache :: Cache -> IO ()Source

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

newCache :: IO (Ht, Integer)Source

Creates a new cache. Experimental

syncCache :: IO ()Source

Force the atomic write of all cached objects modified since the last save into permanent storage. Cache writes allways save a coherent state. As allways, only the modified objects are written.

setConditions :: IO () -> IO () -> IO ()Source

stablishes the procedures to call before and after saving with syncCache, clearSyncCache or clearSyncCacheProc. The postcondition of database persistence should be a commit.

clearSyncCache :: (Integer -> Integer -> Integer -> Bool) -> Int -> IO ()Source

Saves the unsaved elems of the cache. Cache writes allways save a coherent state. Unlike syncChace this call deletes some elems of the cache when the number of elems > sizeObjects. The deletion depends on the check criteria, expressed by the first parameter. defaultCheck is the one implemented to be passed by default. Look at it to understand the clearing criteria.

numElems :: IO IntSource

Return the total number of DBRefs in the cache. For debug purposes. This does not count the number of objects in the cache since many of the DBRef may not have the pointed object loaded. It's O(n).

syncWrite :: SyncMode -> IO ()Source

Specify the cache synchronization policy with permanent storage. See SyncMode for details

data SyncMode Source

Constructors

Synchronous

sync state to permanent storage when atomicallySync is invoked

Asyncronous 

Fields

frecuency :: Int

number of seconds between saves when asyncronous

check :: Integer -> Integer -> Integer -> Bool

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

cacheSize :: Int

size of the cache when async

SyncManual

use syncCache to write the state

clearSyncCacheProcSource

Arguments

:: 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

Start the thread that periodically call clearSyncCache to clean and writes on the persistent storage. it is indirecly set by means of syncWrite, since it is more higuer level. I recommend to use the latter Otherwise, syncCache or clearSyncCache or atomicallySync must be invoked explicitly or no persistence will exist. Cache writes allways save a coherent state

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

This is a default cache clearance check. It forces to drop from the cache all the elems not accesed since half the time between now and the last sync if it returns True, the object will be discarded from the cache it is invoked when the cache size exceeds the number of objects configured in clearSyncCacheProc or clearSyncCache

Other

onNothing :: Monad m => m (Maybe b) -> m b -> m bSource

Handles Nothing cases in a simpler way than runMaybeT. it is used in infix notation. for example:

result <- readDBRef ref `onNothing` error ("Not found "++ keyObjDBRef ref)

or

result <- readDBRef ref `onNothing` return someDefaultValue