module Concurrent.Cache (CachedData, fetch, createCache) where
import Data.Maybe (isNothing)
import Control.Concurrent (forkIO, threadDelay, killThread, MVar, modifyMVar_, readMVar, ThreadId, newMVar)
import Control.Monad (when, liftM)
data CachedData a = TimedCachedData (Int, (MVar (Maybe ThreadId, IO a, Maybe a))) | ReadOnceCachedData (MVar (Either (IO a) a))
fetch :: CachedData a
-> IO (a)
fetch (ReadOnceCachedData mvar) = go where
go = readMVar mvar >>= \cached -> do
case cached of
Left _ -> do
modifyMVar_ mvar $ \cached' -> case cached' of
Left x -> do liftM Right x
Right x -> return $ Right x
go
Right value -> return value
fetch (TimedCachedData (timeout, mvar)) = go where
go = readMVar mvar >>= \(thread,_,value) -> do
case value of
Nothing -> do
modifyMVar_ mvar $ \mvar'@(threadId', action', value') -> case value' of
Nothing -> do newVal <- action'
return (threadId', action', Just newVal)
Just x -> return $ mvar'
go
Just value' -> do
when (not $ isNothing thread) $ let Just thread' = thread in killThread thread'
modifyMVar_ mvar $ \(_, action', value') -> do
newThreadId <- forkIO $ do
threadDelay timeout
putStrLn "Deleting"
modifyMVar_ mvar $ \(_, action'', _) -> return (Nothing, action'', Nothing)
return (Just newThreadId, action', value')
return value'
createCache :: Int
-> IO (a)
-> IO (CachedData a)
createCache 0 action = do
var <- newMVar $ Left action
return $ ReadOnceCachedData var
createCache timeout action = do
var <- newMVar (Nothing, action, Nothing)
return $ TimedCachedData (timeout, var)