[Haskell-cafe] implementing recursive let

Ben Franksen ben.franksen at online.de
Tue Nov 24 19:56:03 EST 2009


I am trying to write an interpreter for a very simple untyped functional
language. I have a problem with mutually recursive let expressions, for
which my interpreter loops :(

This is a code snippet from the eval function:

> eval :: Expr -> Eval Value
> eval (Let decls body) = mdo
>   let (names,exprs) = unzip decls
>   let updateEnv env = foldr (uncurry M.insert) env $ zip names values
>   (values,result) <- local updateEnv $ liftM2 (,) (mapM eval exprs) (eval
body)
>   return result

Module M is Data.Map, the environment is a simple map from strings to
values. Values are defined as

> data Value = Data String | Function (Value -> Eval Value)

The Eval monad is defined as

> newtype Eval a = Eval {
>     unEval :: ErrorT String (StateT Env (Writer [String])) a
>   } deriving (
>     Monad,
>     MonadFix,
>     MonadWriter [String], -- for warnings & other messages
>     MonadState Env,
>     MonadError String
>   )

> instance MonadReader Env Eval where
>   ask = get
>   local tr act = do
>     s <- get
>     modify tr
>     r <- act
>     put s
>     return r

When I test this with an extremely simple expression, something like "let x
= 1 in x", the code above loops. I don't understand why, especially since
in a previous version it worked. In the previous version I had a simpler
monad stack that went

> newtype Eval a = Eval {
>     unEval :: ReaderT Env (Writer [String])) a
>   } deriving (
>     Monad,
>     MonadFix,
>     MonadWriter [String],
>     MonadReader Env
>   )

(Replacing reader with state was done so I can add definitions to the
environment at runtime. The ErrorT provides for errors, such as application
of a non-function.)

Expressions not involving let work fine. Also, if I replace the above
definition by one which does not allow recursion (not using mdo, evaluating
the defining expressions before the variable gets added to the
environment), then non-recursive let-expressions (like the simple example
above) work just fine.

I am out of ideas as to what causes this problem. Does the addition of
ErrorT make my monad too strict? How else can I implement mutual recursion?

Cheers
Ben



More information about the Haskell-Cafe mailing list