module Data.Acid.Core
( Core(coreMethods)
, Method(..)
, MethodContainer(..)
, Tagged
, mkCore
, closeCore
, closeCore'
, modifyCoreState
, modifyCoreState_
, withCoreState
, lookupHotMethod
, lookupColdMethod
, runHotMethod
, runColdMethod
, MethodMap
, mkMethodMap
) where
import Control.Concurrent ( MVar, newMVar, withMVar
, modifyMVar, modifyMVar_ )
import Control.Monad ( liftM )
import Control.Monad.State ( State, runState )
import qualified Data.Map as Map
import Data.ByteString.Lazy as Lazy ( ByteString )
import Data.ByteString.Lazy.Char8 as Lazy ( pack, unpack )
import Data.Serialize ( runPutLazy, runGetLazy )
import Data.SafeCopy ( SafeCopy, safeGet, safePut )
import Data.Typeable ( Typeable, TypeRep, typeRepTyCon, typeOf )
import Unsafe.Coerce ( unsafeCoerce )
#if MIN_VERSION_base(4,5,0)
import Data.Typeable ( tyConModule )
#else
import Data.Typeable.Internal ( tyConModule )
#endif
#if MIN_VERSION_base(4,4,0)
showQualifiedTypeRep :: TypeRep -> String
showQualifiedTypeRep tr = tyConModule con ++ "." ++ show tr
where con = typeRepTyCon tr
#else
showQualifiedTypeRep :: TypeRep -> String
showQualifiedTypeRep tr = show tr
#endif
class ( Typeable ev, SafeCopy ev
, Typeable (MethodResult ev), SafeCopy (MethodResult ev)) =>
Method ev where
type MethodResult ev
type MethodState ev
methodTag :: ev -> Tag
methodTag ev = Lazy.pack (showQualifiedTypeRep (typeOf ev))
data Core st
= Core { coreState :: MVar st
, coreMethods :: MethodMap st
}
mkCore :: [MethodContainer st]
-> st
-> IO (Core st)
mkCore methods initialValue
= do mvar <- newMVar initialValue
return Core{ coreState = mvar
, coreMethods = mkMethodMap methods }
closeCore :: Core st -> IO ()
closeCore core
= closeCore' core (\_st -> return ())
closeCore' :: Core st -> (st -> IO ()) -> IO ()
closeCore' core action
= modifyMVar_ (coreState core) $ \st ->
do action st
return errorMsg
where errorMsg = error "Access failure: Core closed."
modifyCoreState :: Core st -> (st -> IO (st, a)) -> IO a
modifyCoreState core action
= modifyMVar (coreState core) $ \st -> do (!st', a) <- action st
return (st', a)
modifyCoreState_ :: Core st -> (st -> IO st) -> IO ()
modifyCoreState_ core action
= modifyMVar_ (coreState core) $ \st -> do !st' <- action st
return st'
withCoreState :: Core st -> (st -> IO a) -> IO a
withCoreState core = withMVar (coreState core)
runColdMethod :: Core st -> Tagged Lazy.ByteString -> IO Lazy.ByteString
runColdMethod core taggedMethod
= modifyCoreState core $ \st ->
do let (a, st') = runState (lookupColdMethod core taggedMethod) st
return ( st', a)
lookupColdMethod :: Core st -> Tagged Lazy.ByteString -> State st Lazy.ByteString
lookupColdMethod core (storedMethodTag, methodContent)
= case Map.lookup storedMethodTag (coreMethods core) of
Nothing -> missingMethod storedMethodTag
Just (Method method)
-> liftM (runPutLazy . safePut) (method (lazyDecode methodContent))
lazyDecode :: SafeCopy a => Lazy.ByteString -> a
lazyDecode inp
= case runGetLazy safeGet inp of
Left msg -> error msg
Right val -> val
missingMethod :: Tag -> a
missingMethod tag
= error msg
where msg = "This method is required but not available: " ++ show (Lazy.unpack tag) ++
". Did you perhaps remove it before creating a checkpoint?"
runHotMethod :: Method method => Core (MethodState method) -> method -> IO (MethodResult method)
runHotMethod core method
= modifyCoreState core $ \st ->
do let (a, st') = runState (lookupHotMethod (coreMethods core) method) st
return ( st', a)
lookupHotMethod :: Method method => MethodMap (MethodState method) -> method
-> State (MethodState method) (MethodResult method)
lookupHotMethod methodMap method
= case Map.lookup (methodTag method) methodMap of
Nothing -> missingMethod (methodTag method)
Just (Method methodHandler)
->
unsafeCoerce methodHandler method
type Tag = Lazy.ByteString
type Tagged a = (Tag, a)
data MethodContainer st where
Method :: (Method method) => (method -> State (MethodState method) (MethodResult method)) -> MethodContainer (MethodState method)
type MethodMap st = Map.Map Tag (MethodContainer st)
mkMethodMap :: [MethodContainer st] -> MethodMap st
mkMethodMap methods
= Map.fromList [ (methodType method, method) | method <- methods ]
where
methodType :: MethodContainer st -> Tag
methodType m = case m of
Method fn -> let ev :: (ev -> State st res) -> ev
ev _ = undefined
in methodTag (ev fn)