module Simulation.Aivika.Branch.Internal.Br
(BrParams(..),
BrIO(..),
invokeBr,
runBr,
newBrParams,
newRootBrParams,
branchLevel) where
import Data.IORef
import Data.Maybe
import Control.Applicative
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Fix
import Control.Exception (throw, catch, finally)
import Simulation.Aivika.Trans.Exception
newtype BrIO a = Br { unBr :: BrParams -> IO a
}
data BrParams =
BrParams { brId :: !Int,
brIdGenerator :: IORef Int,
brLevel :: !Int,
brParent :: Maybe BrParams,
brUniqueRef :: IORef ()
}
instance Monad BrIO where
return = Br . const . return
(Br m) >>= k = Br $ \ps ->
m ps >>= \a ->
let m' = unBr (k a) in m' ps
instance Applicative BrIO where
pure = return
(<*>) = ap
instance Functor BrIO where
fmap f (Br m) = Br $ fmap f . m
instance MonadIO BrIO where
liftIO = Br . const . liftIO
instance MonadFix BrIO where
mfix f =
Br $ \ps ->
do { rec { a <- invokeBr ps (f a) }; return a }
instance MonadException BrIO where
catchComp (Br m) h = Br $ \ps ->
catch (m ps) (\e -> unBr (h e) ps)
finallyComp (Br m1) (Br m2) = Br $ \ps ->
finally (m1 ps) (m2 ps)
throwComp e = Br $ \ps ->
throw e
invokeBr :: BrParams -> BrIO a -> IO a
invokeBr ps (Br m) = m ps
runBr :: BrIO a -> IO a
runBr m =
do ps <- newRootBrParams
unBr m ps
newBrParams :: BrParams -> IO BrParams
newBrParams ps =
do id <- atomicModifyIORef (brIdGenerator ps) $ \a ->
let b = a + 1 in b `seq` (b, b)
let level = 1 + brLevel ps
uniqueRef <- newIORef ()
return BrParams { brId = id,
brIdGenerator = brIdGenerator ps,
brLevel = level `seq` level,
brParent = Just ps,
brUniqueRef = uniqueRef }
newRootBrParams :: IO BrParams
newRootBrParams =
do genId <- newIORef 0
uniqueRef <- newIORef ()
return BrParams { brId = 0,
brIdGenerator = genId,
brLevel = 0,
brParent = Nothing,
brUniqueRef = uniqueRef
}
branchLevel :: BrIO Int
branchLevel = Br $ \ps -> return (brLevel ps)