Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
TCache is a transactional cache with configurable persistence that permits STM transactions with objects that synchronize synchronously or asynchronously with their user defined storages. Persistence in files is provided by default.
TCache implements DBRef
s . They are persistent STM references with a typical Haskell interface.
similar 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 on register updates. They are used internally for indexing.
Data.TCache.IndexQuery implements a straightforward 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
- atomically :: STM a -> IO a
- atomicallySync :: STM a -> IO a
- data STM a
- unsafeIOToSTM :: IO a -> STM a
- safeIOToSTM :: IO a -> STM a
- data DBRef a
- getDBRef :: (Typeable a, IResource a) => String -> DBRef a
- keyObjDBRef :: DBRef a -> String
- newDBRef :: (IResource a, Typeable a) => a -> STM (DBRef a)
- readDBRef :: (IResource a, Typeable a) => DBRef a -> STM (Maybe a)
- readDBRefs :: (IResource a, Typeable a) => [DBRef a] -> STM [Maybe a]
- writeDBRef :: (IResource a, Typeable a) => DBRef a -> a -> STM ()
- delDBRef :: (IResource a, Typeable a) => DBRef a -> STM ()
- class IResource a where
- keyResource :: a -> String
- readResourceByKey :: String -> IO (Maybe a)
- readResourcesByKey :: [String] -> IO [Maybe a]
- readResource :: a -> IO (Maybe a)
- writeResource :: a -> IO ()
- writeResources :: [a] -> IO ()
- delResource :: a -> IO ()
- delResources :: [a] -> IO ()
- data Resources a b
- resources :: Resources a ()
- withSTMResources :: (IResource a, Typeable a) => [a] -> ([Maybe a] -> Resources a x) -> STM x
- withResources :: (IResource a, Typeable a) => [a] -> ([Maybe a] -> [a]) -> IO ()
- withResource :: (IResource a, Typeable a) => a -> (Maybe a -> a) -> IO ()
- getResources :: (IResource a, Typeable a) => [a] -> IO [Maybe a]
- getResource :: (IResource a, Typeable a) => a -> IO (Maybe a)
- deleteResources :: (IResource a, Typeable a) => [a] -> IO ()
- deleteResource :: (IResource a, Typeable a) => a -> IO ()
- addTrigger :: (IResource a, Typeable a) => (DBRef a -> Maybe a -> STM ()) -> IO ()
- flushDBRef :: (IResource a, Typeable a) => DBRef a -> STM ()
- flushKey :: String -> STM ()
- invalidateKey :: String -> STM ()
- flushAll :: STM ()
- type Cache = IORef (Ht, Integer)
- setCache :: Cache -> IO ()
- newCache :: IO (Ht, Integer)
- syncCache :: IO ()
- setConditions :: IO () -> IO () -> IO ()
- clearSyncCache :: (Integer -> Integer -> Integer -> Bool) -> Int -> IO ()
- numElems :: IO Int
- statElems :: IO (Int, Int, Int)
- syncWrite :: SyncMode -> IO ()
- data SyncMode
- = Synchronous
- | Asynchronous { }
- | SyncManual
- clearSyncCacheProc :: Int -> (Integer -> Integer -> Integer -> Bool) -> Int -> IO ThreadId
- defaultCheck :: Integer -> Integer -> Integer -> Bool
- onNothing :: Monad m => m (Maybe b) -> m b -> m b
Inherited from STM
and variations
atomically :: STM a -> IO a #
Perform a series of STM actions atomically.
Using atomically
inside an unsafePerformIO
or unsafeInterleaveIO
subverts some of guarantees that STM provides. It makes it possible to
run a transaction inside of another transaction, depending on when the
thunk is evaluated. If a nested transaction is attempted, an exception
is thrown by the runtime. It is possible to safely use atomically
inside
unsafePerformIO
or unsafeInterleaveIO
, but the typechecker does not
rule out programs that may attempt nested transactions, meaning that
the programmer must take special care to prevent these.
However, there are functions for creating transactional variables that
can always be safely called in unsafePerformIO
. See: newTVarIO
,
newTChanIO
,
newBroadcastTChanIO
,
newTQueueIO
,
newTBQueueIO
, and
newTMVarIO
.
Using unsafePerformIO
inside of atomically
is also dangerous but for
different reasons. See unsafeIOToSTM
for more on this.
atomicallySync :: STM a -> IO a Source #
Perform a synchronization of the cache with permanent storage once executed the STM transaction
when syncWrite
policy is Synchronous
A monad supporting atomic memory transactions.
Instances
Alternative STM | Since: base-4.8.0.0 |
Applicative STM | Since: base-4.8.0.0 |
Functor STM | Since: base-4.3.0.0 |
Monad STM | Since: base-4.3.0.0 |
MonadPlus STM | Since: base-4.3.0.0 |
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 a Source #
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
DBRef
s 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 flushed
to and from the cache automatically depending on the cache handling policies and the access needs.
DBRefs
are univocally identified by its referenced object keys, so they can be compared, ordered, checked for equality, and so on.
The creation of a DBRef, though getDBRef
is pure. This permits an efficient lazy access to the
registers through their DBRefs by lazy marshalling of the register content on demand.
Example: Car registers have references to Person registers.
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 through the owner field.
To permit persistence and being referred 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 Cars 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 referenced, cached object is looked up in the cache and found at creation, do not perform any further cache lookup afterwards, so reads and writes from/to DBRefs are faster than *Resource(s) calls, which perform cache lookups every time the object is accessed.
DBRefs and *Resource(s)
primitives are completely interoperable. The latter operate implicitly with DBRefs
getDBRef :: (Typeable a, IResource a) => String -> DBRef a Source #
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 property is useful because deserialization
of objects with unused embedded DBRef
s do not need to marshall them eagerly.
This also avoids unnecessary cache lookups of the referenced objects.
keyObjDBRef :: DBRef a -> String Source #
Return the key of the object referenced 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.insert 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.
readDBRefs :: (IResource a, Typeable a) => [DBRef a] -> STM [Maybe a] Source #
Read multiple DBRefs in a single request using the new readResourcesByKey
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 classes for file persistence.
class IResource a where Source #
Must be defined for every object to be cached.
:: 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 within 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.
readResourcesByKey :: [String] -> IO [Maybe a] Source #
hopefully optimized read of many objects by key.
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.
writeResources :: [a] -> IO () Source #
multiple write (hopefully) in a single request. That is up to you and your backend . Defined by default as 'mapM_ writeResource'
delResource :: a -> IO () Source #
Delete the resource. It is called syncronously. So it must commit
delResources :: [a] -> IO () Source #
Instances
(Typeable a, Indexable a, Serializable a) => IResource a Source # | |
Defined in Data.TCache.DefaultPersistence keyResource :: a -> String Source # readResourceByKey :: String -> IO (Maybe a) Source # readResourcesByKey :: [String] -> IO [Maybe a] Source # readResource :: a -> IO (Maybe a) Source # writeResource :: a -> IO () Source # writeResources :: [a] -> IO () Source # delResource :: a -> IO () Source # delResources :: [a] -> IO () Source # |
Operations with cached objects
Implement inversion of control primitives where the user defines the objects to retrieve. The primitives then call the defined function that determines how to transform the retrieved objects, which are sent back to the storage and a result is returned.
In this example "buy" is a transaction where the user buys 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) instanceIndexable
Data wherekey
User{uid=id}= idkey
Item{iid=id}= id userbuy
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"
Resources data definition used by withSTMResources
:: (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 cachetoDelete
: the content of this field will be removed from the cache and from permanent storagetoReturn
: the content of this field will be returned bywithSTMResources
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= doaddTrigger
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 referenced object from the cache, not the database (see delDBRef
)
useful for cache invalidation when the database is modified by other processes.
invalidateKey :: String -> STM () Source #
label the object as not existent in database
setCache :: Cache -> IO () Source #
Set the cache. this is useful for hot loaded modules that will update an existing cache. Experimental
Force the atomic write of all cached objects modified since the last save into permanent storage. Cache writes allways save a coherent state. As always, 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 syncCache
this call deletes some elems from 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.
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
s
may not have the referenced object loaded. It's O(n).
statElems :: IO (Int, Int, Int) Source #
Retuns some statistical information for the DBRefs in the cache (for debugging) This returns a tuple containing: total : count of the total elements in cache dirty : the elements which need to be written to the persistent storage loaded : the elements which are currently hold in memory
syncWrite :: SyncMode -> IO () Source #
Specify the cache synchronization policy with permanent storage. See SyncMode
for details
Synchronous | sync state to permanent storage when |
Asynchronous | |
SyncManual | use |
:: 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. |
-> 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 indirectly 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
:: Integer | current time in seconds |
-> Integer | last access time for a given object |
-> Integer | last cache synchronization (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 b Source #
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