Skip to content

Commit

Permalink
added cachedbyKeySTM, inproved memoization
Browse files Browse the repository at this point in the history
  • Loading branch information
agocorona committed May 13, 2013
1 parent 304eb8d commit 539b65f
Show file tree
Hide file tree
Showing 5 changed files with 40 additions and 22 deletions.
5 changes: 2 additions & 3 deletions Data/TCache/IndexQuery.hs
Original file line number Diff line number Diff line change
Expand Up @@ -283,9 +283,8 @@ instance SetOperations (JoinData a a') [DBRef a'] (JoinData a a') where
return [(zs, union xs ys) | (zs,xs) <- xss]


-- | return all the (indexed) registers which has this field
indexOf :: (Queriable reg a )
=> (reg -> a) -> STM [(a,[DBRef reg])]
-- | return all the (indexed) values which this field has and a DBRef pointer to the register
indexOf :: (Queriable reg a) => (reg -> a) -> STM [(a,[DBRef reg])]
indexOf selector= do
let [one, two]= typeRepArgs $! typeOf selector
let rindex= getDBRef $! keyIndex one two
Expand Down
30 changes: 18 additions & 12 deletions Data/TCache/Memoization.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@
, ExistentialQuantification
, FlexibleInstances
, TypeSynonymInstances #-}
module Data.TCache.Memoization (writeCached,cachedByKey,flushCached,cachedp,addrStr,Executable(..))
module Data.TCache.Memoization (writeCached,cachedByKey,cachedByKeySTM,flushCached,cachedp,addrStr,Executable(..))

where
import Data.Typeable
Expand Down Expand Up @@ -64,7 +64,7 @@ instance (Indexable a) => IResource (Cached a b) where

writeResource _= return ()
delResource _= return ()
readResourceByKey k= error $ "access By key is undefined for cached objects.key= " ++ k
readResourceByKey k= return Nothing -- error $ "access By key is undefined for cached objects.key= " ++ k


readResource (Cached a f _ _)=do
Expand Down Expand Up @@ -95,24 +95,27 @@ writeCached a b c d=


cached :: (Indexable a,Typeable a, Typeable b, Executable m,MonadIO m) => Int -> (a -> m b) -> a -> m b
cached time f a= do
cached time f a= liftIO . atomically $ cachedSTM time f a

cachedSTM time f a= do
let prot= Cached a f undefined undefined
cho@(Cached _ _ b t) <- liftIO $ getResource prot `onNothing` fillIt prot
let ref= getDBRef $ keyResource prot
cho@(Cached _ _ b t) <- readDBRef ref `onNothing` fillIt ref prot
case time of
0 -> return b
_ -> do
TOD tnow _ <- liftIO $ getClockTime
if tnow - t > fromIntegral time
TOD tnow _ <- unsafeIOToSTM $ getClockTime
if tnow - t >= fromIntegral time
then do
liftIO $ deleteResource cho
cached time f a
Cached _ _ b _ <- fillIt ref prot
return b
else return b
where
-- has been invalidated by flushCached
fillIt proto= do
r <- return . fromJust =<< (readResource proto) -- !> "fillIt"
withResources [] $ const [r]
return r
fillIt ref proto= do
let r = unsafePerformIO $return . fromJust =<< readResource proto -- !> "fillIt"
writeDBRef ref r
return r

-- | Memoize the result of a computation for a certain time. A string 'key' is used to index the result
--
Expand All @@ -121,6 +124,9 @@ cached time f a= do
cachedByKey :: (Typeable a, Executable m,MonadIO m) => String -> Int -> m a -> m a
cachedByKey key time f = cached time (\_ -> f) key

cachedByKeySTM :: (Typeable a, Executable m) => String -> Int -> m a -> STM a
cachedByKeySTM key time f = cachedSTM time (\_ -> f) key

-- Flush the cached object indexed by the key
flushCached :: String -> IO ()
flushCached k= atomically $ invalidateKey $ cachedKeyPrefix ++ k -- !> "flushCached"
Expand Down
2 changes: 1 addition & 1 deletion TCache.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: TCache
version: 0.10.0.5
version: 0.10.0.6
cabal-version: >= 1.6
build-type: Simple
license: BSD3
Expand Down
10 changes: 4 additions & 6 deletions demos/DynamicSample.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,11 +15,9 @@ example of IDynamic usage.
--two objects with two different datatypes: Int and String

instance Indexable Int where
key x= show x
key = show





instance Indexable String where
key x= take 2 x

Expand Down Expand Up @@ -52,8 +50,8 @@ main= do
-- to use heterogeneous data in the same transaction,
-- use DBRef's:
s <- atomically $ do
let refInt = getDBRef $ keyResource x :: DBRef Int
refString = getDBRef $ keyResource "ho" :: DBRef String
let refInt = getDBRef $ key x :: DBRef Int
refString = getDBRef $ key "ho" :: DBRef String
i <- readDBRef refInt
writeDBRef refString $ "hola, the retrieved value of x is " ++ show i
s <- readDBRef refString
Expand Down
15 changes: 15 additions & 0 deletions demos/memoization.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
import Data.TCache.Memoization
import Data.TCache.DefaultPersistence
import Control.Concurrent
import System.Time



main= do
cachedByKey "" 4 f >>= print
threadDelay 1000000
main

f= do
TOD t _ <- getClockTime
return t

0 comments on commit 539b65f

Please sign in to comment.