{-# LANGUAGE RecursiveDo #-}
module Simulation.Aivika.Branch.Internal.BR
(BRParams(..),
BR(..),
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 BR m a = BR { forall (m :: * -> *) a. BR m a -> BRParams -> m a
unBR :: BRParams -> m a
}
data BRParams =
BRParams { BRParams -> Int
brId :: !Int,
BRParams -> IORef Int
brIdGenerator :: IORef Int,
BRParams -> Int
brLevel :: !Int,
BRParams -> Maybe BRParams
brParent :: Maybe BRParams,
BRParams -> IORef ()
brUniqueRef :: IORef ()
}
instance Monad m => Monad (BR m) where
{-# INLINE (>>=) #-}
(BR BRParams -> m a
m) >>= :: forall a b. BR m a -> (a -> BR m b) -> BR m b
>>= a -> BR m b
k = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps ->
BRParams -> m a
m BRParams
ps forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a ->
let m' :: BRParams -> m b
m' = forall (m :: * -> *) a. BR m a -> BRParams -> m a
unBR (a -> BR m b
k a
a) in BRParams -> m b
m' BRParams
ps
instance Applicative m => Applicative (BR m) where
{-# INLINE pure #-}
pure :: forall a. a -> BR m a
pure = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE (<*>) #-}
(BR BRParams -> m (a -> b)
f) <*> :: forall a b. BR m (a -> b) -> BR m a -> BR m b
<*> (BR BRParams -> m a
m) = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps -> BRParams -> m (a -> b)
f BRParams
ps forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BRParams -> m a
m BRParams
ps
instance Functor m => Functor (BR m) where
{-# INLINE fmap #-}
fmap :: forall a b. (a -> b) -> BR m a -> BR m b
fmap a -> b
f (BR BRParams -> m a
m) = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. BRParams -> m a
m
instance MonadIO m => MonadIO (BR m) where
{-# INLINE liftIO #-}
liftIO :: forall a. IO a -> BR m a
liftIO = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
instance MonadTrans BR where
{-# INLINE lift #-}
lift :: forall (m :: * -> *) a. Monad m => m a -> BR m a
lift = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
instance MonadFix m => MonadFix (BR m) where
mfix :: forall a. (a -> BR m a) -> BR m a
mfix a -> BR m a
f =
forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps ->
do { rec { a
a <- forall (m :: * -> *) a. BRParams -> BR m a -> m a
invokeBR BRParams
ps (a -> BR m a
f a
a) }; forall (m :: * -> *) a. Monad m => a -> m a
return a
a }
instance MonadException m => MonadException (BR m) where
catchComp :: forall e a. Exception e => BR m a -> (e -> BR m a) -> BR m a
catchComp (BR BRParams -> m a
m) e -> BR m a
h = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps ->
forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
catchComp (BRParams -> m a
m BRParams
ps) (\e
e -> forall (m :: * -> *) a. BR m a -> BRParams -> m a
unBR (e -> BR m a
h e
e) BRParams
ps)
finallyComp :: forall a b. BR m a -> BR m b -> BR m a
finallyComp (BR BRParams -> m a
m1) (BR BRParams -> m b
m2) = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps ->
forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
finallyComp (BRParams -> m a
m1 BRParams
ps) (BRParams -> m b
m2 BRParams
ps)
throwComp :: forall e a. Exception e => e -> BR m a
throwComp e
e = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps ->
forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throwComp e
e
invokeBR :: BRParams -> BR m a -> m a
{-# INLINE invokeBR #-}
invokeBR :: forall (m :: * -> *) a. BRParams -> BR m a -> m a
invokeBR BRParams
ps (BR BRParams -> m a
m) = BRParams -> m a
m BRParams
ps
runBR :: MonadIO m => BR m a -> m a
{-# INLINABLE runBR #-}
runBR :: forall (m :: * -> *) a. MonadIO m => BR m a -> m a
runBR BR m a
m =
do BRParams
ps <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO BRParams
newRootBRParams
forall (m :: * -> *) a. BR m a -> BRParams -> m a
unBR BR m a
m BRParams
ps
newBRParams :: BRParams -> IO BRParams
newBRParams :: BRParams -> IO BRParams
newBRParams BRParams
ps =
do Int
id <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef (BRParams -> IORef Int
brIdGenerator BRParams
ps) forall a b. (a -> b) -> a -> b
$ \Int
a ->
let b :: Int
b = Int
a forall a. Num a => a -> a -> a
+ Int
1 in Int
b seq :: forall a b. a -> b -> b
`seq` (Int
b, Int
b)
let level :: Int
level = Int
1 forall a. Num a => a -> a -> a
+ BRParams -> Int
brLevel BRParams
ps
IORef ()
uniqueRef <- forall a. a -> IO (IORef a)
newIORef ()
forall (m :: * -> *) a. Monad m => a -> m a
return BRParams { brId :: Int
brId = Int
id,
brIdGenerator :: IORef Int
brIdGenerator = BRParams -> IORef Int
brIdGenerator BRParams
ps,
brLevel :: Int
brLevel = Int
level seq :: forall a b. a -> b -> b
`seq` Int
level,
brParent :: Maybe BRParams
brParent = forall a. a -> Maybe a
Just BRParams
ps,
brUniqueRef :: IORef ()
brUniqueRef = IORef ()
uniqueRef }
newRootBRParams :: IO BRParams
newRootBRParams :: IO BRParams
newRootBRParams =
do IORef Int
genId <- forall a. a -> IO (IORef a)
newIORef Int
0
IORef ()
uniqueRef <- forall a. a -> IO (IORef a)
newIORef ()
forall (m :: * -> *) a. Monad m => a -> m a
return BRParams { brId :: Int
brId = Int
0,
brIdGenerator :: IORef Int
brIdGenerator = IORef Int
genId,
brLevel :: Int
brLevel = Int
0,
brParent :: Maybe BRParams
brParent = forall a. Maybe a
Nothing,
brUniqueRef :: IORef ()
brUniqueRef = IORef ()
uniqueRef
}
branchLevel :: Monad m => BR m Int
{-# INLINABLE branchLevel #-}
branchLevel :: forall (m :: * -> *). Monad m => BR m Int
branchLevel = forall (m :: * -> *) a. (BRParams -> m a) -> BR m a
BR forall a b. (a -> b) -> a -> b
$ \BRParams
ps -> forall (m :: * -> *) a. Monad m => a -> m a
return (BRParams -> Int
brLevel BRParams
ps)