Skip to content

Commit

Permalink
Merge pull request #7 from bbarker/doc_touchup
Browse files Browse the repository at this point in the history
Doc touchup
  • Loading branch information
agocorona authored Feb 15, 2019
2 parents 9610827 + 00e040f commit fe49c7a
Show file tree
Hide file tree
Showing 5 changed files with 145 additions and 158 deletions.
119 changes: 57 additions & 62 deletions Data/TCache.hs
Original file line number Diff line number Diff line change
@@ -1,32 +1,31 @@
{-# LANGUAGE ScopedTypeVariables, ExistentialQuantification, DeriveDataTypeable
, FlexibleInstances, UndecidableInstances #-}

{- | 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 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.
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
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.
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.
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 an straighforwards pure haskell type safe query language based
"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.IndexText" add full text search and content search to the query language.
"Data.TCache.DefaultPersistence" has instances for key indexation , serialization
"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
"Data.Persistent.Collection" implements a persistent, transactional collection with Queue interface as well as indexed access by key.
-}

Expand All @@ -43,33 +42,32 @@ module Data.TCache (
,safeIOToSTM

-- * Operations with cached database references
{-| @DBRefs@ are persistent cached database references in the STM monad
{-| '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,
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
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
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.
@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
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.
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
To permit persistence and being referred with DBRefs, define the 'Indexable' instance
for these two register types:
@
Expand All @@ -79,7 +77,7 @@ 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
>>> let bruce = getDBRef . key $ Person "Bruce" :: DBRef Person
>>> show bruce
>"DBRef \"Person bruce\""
Expand All @@ -89,9 +87,9 @@ Now we create a DBRef to a Person whose name is \"Bruce\"
'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:
Lets create two Cars and its two Car DBRefs with bruce as owner:
>>> cars <- atomically $ mapM newDBRef [Car bruce "Bat Mobile", Car bruce "Porsche"]
>>> cars <- atomically $ mapM newDBRef [Car bruce "Bat Mobile", Car bruce "Porsche"]
>>> print cars
>[DBRef "Car Bat Mobile",DBRef "Car Porsche"]
Expand All @@ -100,29 +98,27 @@ Lets create two Car's and its two Car DBRefs with bruce as owner:
> [Just (Car {owner = DBRef "Person bruce", cname = "Bat Mobile"})
> ,Just (Car {owner = DBRef "Person bruce", cname = "Porsche"})]
try to write with 'writeDBRef'
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
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
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
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 everytime the object is accessed
than *Resource(s) calls, which perform cache lookups every time the object is accessed.
DBRef's and @*Resource(s)@ primitives are completely interoperable. The latter operate implicitly with DBRef's
DBRefs and @*Resource(s)@ primitives are completely interoperable. The latter operate implicitly with DBRefs
-}

Expand All @@ -138,29 +134,29 @@ DBRef's and @*Resource(s)@ primitives are completely interoperable. The latter o
,delDBRef

-- * @IResource@ class
{- | cached objects must be instances of IResource.
Such instances can be implicitly derived trough auxiliary clasess for file persistence
{- | Cached objects must be instances of `IResource`.
Such instances can be implicitly derived trough auxiliary classes for file persistence.
-}
,IResource(..)

-- * 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
{- | 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 buy an item.
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)
instance Indexable Data where
key User{uid=id}= id
key Item{iid=id}= id
instance `Indexable` Data where
`key` User{uid=id}= id
`key` Item{iid=id}= id
user `buy` item= 'withResources'[user,item] buyIt
user `buy` item= 'withResources'[user,item] buyIt
where
buyIt[Just us,Just it]
| stock it > 0= [us',it']
Expand Down Expand Up @@ -345,8 +341,8 @@ newCache =do
return (c,0)

-- | 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).
-- 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).
numElems :: IO Int
numElems= do
(cache, _) <- readIORef refcache
Expand Down Expand Up @@ -457,16 +453,15 @@ instance Eq (DBRef a) where
instance Ord (DBRef a) where
compare (DBRef k _) (DBRef k' _) = compare k k'

-- | Return the key of the object pointed to by the DBRef
-- | Return the key of the object referenced by the DBRef
keyObjDBRef :: DBRef a -> String
keyObjDBRef (DBRef k _)= k


-- | Get the reference to the object in the cache. if it does not exist, the reference is created empty.
-- | 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.
-- 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.
{-# NOINLINE getDBRef #-}
getDBRef :: (Typeable a, IResource a) => String -> DBRef a
getDBRef key= unsafePerformIO $! getDBRef1 $! key where
Expand Down Expand Up @@ -605,8 +600,8 @@ onNothing io onerr= do
Just y -> return y
Nothing -> onerr

-- | Deletes the pointed object from the cache, not the database (see 'delDBRef')
-- useful for cache invalidation when the database is modified by other process
-- | Deletes the referenced object from the cache, not the database (see 'delDBRef')
-- useful for cache invalidation when the database is modified by other processes.
flushDBRef :: (IResource a, Typeable a) =>DBRef a -> STM()
flushDBRef (DBRef _ tv)= writeTVar tv NotRead

Expand Down Expand Up @@ -873,8 +868,8 @@ syncCache = criticalSection saving $ do


data SyncMode= Synchronous -- ^ sync state to permanent storage when `atomicallySync` is invoked
| Asyncronous
{frecuency :: Int -- ^ number of seconds between saves when asyncronous
| Asynchronous
{frequency :: Int -- ^ number of seconds between saves when asynchronous
,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
}
Expand All @@ -893,7 +888,7 @@ syncWrite mode= do
case mode of
Synchronous -> modeWrite
SyncManual -> modeWrite
Asyncronous time check maxsize -> do
Asynchronous time check maxsize -> do
th <- clearSyncCacheProc time check maxsize >> return()
writeIORef tvSyncWrite (mode,Just th)
where
Expand Down
Loading

0 comments on commit fe49c7a

Please sign in to comment.