[Haskell-cafe] M1 + M2 = M3 where both computations in M1 and M2 can be used?

sam lee skynare at gmail.com
Mon May 12 09:51:17 EDT 2008


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.


More information about the Haskell-Cafe mailing list