[Haskell-cafe] Re: Re: implementing recursive let

Ben Franksen ben.franksen at online.de
Thu Nov 26 16:48:15 EST 2009


Derek Elkins wrote:
> On Wed, Nov 25, 2009 at 3:48 PM, Ben Franksen <ben.franksen at online.de>
>> What am I missing?
> 
> The problem is the liftM2 in the Let branch of eval.  You are
> executing the body while making the bindings, so you are trying to
> look up x while you are still trying to bind it.  One solution is to
> move the execution of the body after the binding as in:
> 
> eval (Let decls body) = mdo
>  let (names,exprs) = unzip decls
>      updateEnv env = foldr (uncurry M.insert) env $ zip names values
>  values <- local updateEnv $ mapM eval exprs
>  local updateEnv $ eval body

I already tried that :( It works for non-recursive expressions
like 'example', but not for recursive ones; not even non-recursive ones
that merely use a variable before it is defined like this one

> example2 = Let [("y", Var "x"),("x", Const 1)] (Var "y")

which again makes eval loop. However, if I use your lazy version

> eval (Var x)   = gets (fromJust . M.lookup x)

_or_ remove the ErrorT from the monad stack (see my other message) eval does
not loop, even with mutually recursive definitions.

*some time later*

Ok, it seems I have a version that does what I want. It is not very elegant,
I have to manually wrap/unwrap the ErrorT stuff just for the Val case, but
at least it seems to work. Here it goes:

> eval (Var x) = Eval $ ErrorT $ do
>   env <- get
>   v <- case M.lookup x env of
>     Just v -> return v
>     Nothing -> do
>       warning ("reference to undefined variable " ++ show x)
>       let v = Data ""
>       modify (M.insert x v)
>       return v
>   return (Right v)
> 
> warning s = tell $ ["Warning: " ++ s]

I suspect what is needed to avoid this is a combinator that convinces ErrorT
that a computation is really going to succeed, no matter what. Hmm, now
that I think about it this should be possible using catchError. I will
investigate.

Cheers
Ben



More information about the Haskell-Cafe mailing list