M1 + M2 = M3 where both computations in M1 and M2 can be used?

Hi. I want to compose two monads to build another monad where computations of the two monads can be used inside. I have: - MonadTypeInfer : interface (class) for TypeInfer monad - TypeInfer : a monad that has Map String Type (association of names and types) - TypeInferT : transformer of above monad - MonadEval : interface (class) for Eval monad - Eval : a monad that has Map String Expr (association of names and code/function body) - EvalT : transformer of Eval - tInfer :: Expr -> TypeInfer Type -- given expr, returns type of it in TypeInfer monad - eval :: Expr -> Eval Expr -- given expr, returns normalized expr in Eval monad Problem: in repl, when user defines a function, it should type check and register type of the function to TypeInfer monad's Map String Type. Also, it should store the expression of the function in Eval monad. I build REPL monad using TypeInferT and EvalT.
newtype REPL a = REPL { runREPL :: TypeInferT (EvalT IO) a } deriving(Monad, Functor, MonadIO, MonadTypeInfer, MonadEval) repl :: REPL () repl = do input <- prompt ">>> " case parse input of Left err -> -- handle error Right expr -> do t <- tInfer expr -- BAD!! tInfer :: TypeInfer Type println (show t) result <- eval expr -- BAD!! eval :: Eval Expr println (show result) repl
Should I make tInfer :: REPL Type, eval :: REPL Expr? Is there a way to build a monad where you could use sub-monads' (monads used to build current monad) computations? I prefer keeping tInfer :: TypeInfer Type, eval :: Eval Expr because tInfer never uses actions in Eval monad and vice versa. It seems like what I am asking is to break the type system. Maybe I should just make them run in REPL monad. Thank you. Sam.

sam lee wrote:
Hi.
I want to compose two monads to build another monad where computations of the two monads can be used inside.
I have:
- MonadTypeInfer : interface (class) for TypeInfer monad - TypeInfer : a monad that has Map String Type (association of names and types) - TypeInferT : transformer of above monad - MonadEval : interface (class) for Eval monad - Eval : a monad that has Map String Expr (association of names and code/function body) - EvalT : transformer of Eval - tInfer :: Expr -> TypeInfer Type -- given expr, returns type of it in TypeInfer monad - eval :: Expr -> Eval Expr -- given expr, returns normalized expr in Eval monad
Is there a way to build a monad where you could use sub-monads' (monads used to build current monad) computations?
A solution to this problem is to use type classes, and in particular MonadTrans. You can then give an instance of MonadTypeInfer for EvalT m where m is an instance of MonadTypeInfer, and similarly an instance MonadEval for TypeInferT m. How this is implemented depends on the Monads in question, but if you use the monad transformer library with newtype deriving you can just add "deriving MonadTrans". class Monad m => MonadTypeInfer m where -- functions -- tiStuff :: X -> m Whatever class Monad m => MonadEval m where -- functions -- instance Monad m => MonadTypeInfer (TypeInferT m) where -- implementation -- tiStuff = ... instance Monad m => MonadEval (EvalT m) where -- implementation -- instance MonadEval m => MonadTypeInfer (EvalT m) where -- lift the functions from TypeInfer through the EvalT type, -- MonadTrans from the mtl might help here tiStuff x = lift (tiStuff x) tInfer :: MonadTypeInfer m => Expr -> m Type eval :: MonadEval m => Expr -> m Expr Twan

tInfer :: MonadTypeInfer m => Expr -> m Type eval :: MonadEval m => Expr -> m Expr
That solves!
I should've left out type annotation.
On Mon, May 12, 2008 at 10:38 AM, Twan van Laarhoven
sam lee wrote:
Hi.
I want to compose two monads to build another monad where computations of the two monads can be used inside.
I have:
- MonadTypeInfer : interface (class) for TypeInfer monad - TypeInfer : a monad that has Map String Type (association of names and
types)
- TypeInferT : transformer of above monad - MonadEval : interface (class) for Eval monad - Eval : a monad that has Map String Expr (association of names and code/function body) - EvalT : transformer of Eval - tInfer :: Expr -> TypeInfer Type -- given expr, returns type of it in TypeInfer monad - eval :: Expr -> Eval Expr -- given expr, returns normalized expr in Eval monad
Is there a way to build a monad where you could use sub-monads' (monads used to build current monad) computations?
A solution to this problem is to use type classes, and in particular MonadTrans. You can then give an instance of MonadTypeInfer for EvalT m where m is an instance of MonadTypeInfer, and similarly an instance MonadEval for TypeInferT m. How this is implemented depends on the Monads in question, but if you use the monad transformer library with newtype deriving you can just add "deriving MonadTrans".
class Monad m => MonadTypeInfer m where -- functions -- tiStuff :: X -> m Whatever
class Monad m => MonadEval m where -- functions --
instance Monad m => MonadTypeInfer (TypeInferT m) where -- implementation -- tiStuff = ...
instance Monad m => MonadEval (EvalT m) where -- implementation --
instance MonadEval m => MonadTypeInfer (EvalT m) where -- lift the functions from TypeInfer through the EvalT type, -- MonadTrans from the mtl might help here tiStuff x = lift (tiStuff x)
tInfer :: MonadTypeInfer m => Expr -> m Type eval :: MonadEval m => Expr -> m Expr
Twan

On Mon, May 12, 2008 at 6:51 AM, sam lee
Hi.
I want to compose two monads to build another monad where computations of the two monads can be used inside.
Twan's suggestion seems like a natural way to continue with the existing code you have described (based on monad transformers). If you would like to understand this issue in some depth, I recommend the following paper which presents a general way to combine two monads that is not biased towards having one "contained" in the other. - Composing monads using coproducts. C L=FCth, N Ghani. ICFP 2002. - http://www.mcs.le.ac.uk/~ng13/papers/icfp02.ps.gz I just tried it out the other day, so if you'll excuse the self-promotion here is a demonstration http://www.kennknowles.com/blog/2008/05/10/debugging-with-open-recursion-mix... - Kenn
participants (3)
-
Kenn Knowles
-
sam lee
-
Twan van Laarhoven