Experiments for Process

This commit is contained in:
Alexander Granin 2019-05-08 12:02:09 +07:00
parent ee6e92ee7b
commit 947152498a
5 changed files with 7 additions and 12 deletions

View File

@ -9,6 +9,5 @@ import Hydra.Prelude
import qualified Hydra.Core.Runtime as R
class Evaluable m where
-- type EvalM m :: * -> *
-- evaluate :: EvalM m a -> R.CoreRuntime -> IO a
evaluate :: m a -> R.CoreRuntime -> IO a
data EvalM m :: * -> *
evaluate :: EvalM m a -> R.CoreRuntime -> IO a

View File

@ -12,7 +12,7 @@ import Hydra.Core.Logger.FTL as L
import Hydra.Core.Random.FTL as L
import qualified Hydra.Core.State.Language as L
class (Evaluable m, L.ControlFlowL m, L.RandomL m, L.LoggerL m) => LangL m where
class (L.ControlFlowL m, L.RandomL m, L.LoggerL m) => LangL m where
evalStateAtomically :: L.StateL a -> m a
instance LangL m => L.StateIO m where

View File

@ -11,8 +11,6 @@ import qualified Hydra.Core.Runtime as R
import qualified Hydra.Core.State.Interpreter as Impl
import qualified Hydra.Core.State.Language as L
import Hydra.Core.Evaluable
instance L.LangL (ReaderT R.CoreRuntime IO) where
evalStateAtomically action = do
coreRt <- ask
@ -22,9 +20,6 @@ instance L.LangL (ReaderT R.CoreRuntime IO) where
liftIO $ R.flushStmLogger stateRt loggerRt
pure res
instance Evaluable (ReaderT R.CoreRuntime IO) where
evaluate = runReaderT
-- Compiles but wrong.
-- class Monad m => LangL m where
-- atomically :: StateL m => m a -> m a

View File

@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
@ -10,8 +11,8 @@ import qualified Hydra.Core.Domain as D
import Hydra.Core.Evaluable
class (Monad m) => ProcessL m where
forkProcess :: Evaluable m' => m' a -> m (D.ProcessPtr a)
class (Evaluable m', Monad m) => ProcessL m' m where
forkProcess :: EvalM m' a -> m (D.ProcessPtr a)
-- killProcess :: D.ProcessPtr a -> m ()
-- tryGetResult :: D.ProcessPtr a -> m (Maybe a)
-- awaitResult :: D.ProcessPtr a -> m a

View File

@ -14,7 +14,7 @@ import qualified Hydra.Core.Runtime as R
import Hydra.Core.Evaluable
import Hydra.Core.Lang.FTLI ()
instance L.ProcessL (ReaderT R.CoreRuntime IO) where
instance Evaluable m' => L.ProcessL m' (ReaderT R.CoreRuntime IO) where
forkProcess action = do
coreRt <- ask
let processRt = coreRt ^. RLens.processRuntime