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

2009-11-27 Thread Ben Franksen
Ben Franksen wrote:
 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]

While this works for simple var=constant declarations, it breaks down again
as soon as I add lambdas and application. Same symptoms as before: eval
loops; and it works again if I remove the ErrorT (but then I get a pattern
match failure if I apply a non-function which is of course what I wanted to
avoid with the ErrorT).

This is maddening! There must be some way to get mutual recursion to work
while still allowing for clean handling of failure. What galls me the most
is that it is so unpredictable whether the program will terminate with a
given input or not.

(The code is attached.)

Cheers
Ben
{-# LANGUAGE RecursiveDo, GeneralizedNewtypeDeriving,
TypeSynonymInstances, MultiParamTypeClasses #-}
import Control.Monad
import Control.Monad.State
import Control.Monad.Error
import Control.Monad.Writer
import Control.Monad.Reader
import Control.Monad.Fix
import qualified Data.Map as M

data Expr = Let [(String, Expr)] Expr | Const Int | Var String
  | Lam String Expr | App Expr Expr

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

instance Show Value where
show (Data s) = s

type Env = M.Map String Value

eval :: Expr - Eval Value
eval (Const n) = return (Data (show n))
eval (Var x) = Eval $ noError $ do
  env - get
  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
eval (Let decls body) = mdo
  let (names,exprs) = unzip decls
  updateEnv env = foldr (uncurry M.insert) env $ zip names values
  (values,result) - local updateEnv $ liftM2 (,) (mapM eval exprs) (eval body)
  return result
eval (Lam parm body) = do
  env - ask
  return $ Function (\val - local (\_ - M.insert parm val env) (eval body))
eval (App fun arg) = do
  f - eval fun
  x - eval arg -- call-by-value, so evaluate the arg first
  case f of
Function f - f x

warning s = tell $ [Warning:  ++ s]

newtype Eval a = Eval {
unEval :: ErrorT String (StateT Env (Writer [String])) a
  } deriving (
Monad, MonadFix, MonadWriter [String],
MonadState Env, MonadError String
  )

runEval :: Eval Value - Either String Value
runEval = fst . runWriter . flip evalStateT M.empty . runErrorT . unEval

evaluate = runEval . eval

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

noError ::  (Monad m, Error e) = ErrorT e m a - ErrorT e m a
noError m = ErrorT $ do
  ~(Right r) - runErrorT m
  return (Right r)

-- examples
good1 = Let [(x, Const 1)] (Var x)
good2 = Let [(y, Var x),(x, Const 1)] (Var y)
bad1 = Let [(x, Const 1)] (Var y)
letf = Let [(f,Lam x (Var x))] (App (Var f) (Const 1))
badapp = Let [(f,Lam x (Var x))] (App (Const 1) (Var f))

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-27 Thread Ryan Ingram
The problem is that ErrorT makes any argument to mdo *much* more
strict, and therefore much more likely to loop.

This is because each action needs to know whether the previous action
was successful before it can continue.

Notice that when you got it to work, you *always* return Right v;
that is, you never actually have an error.

If you want to avoid introducing bottoms into your code, I would avoid
using fix/mdo except in cases where you can prove that the code is
non-strict.  You keep running into cases where your code is more
strict than you would like which is introducing the bottoms.

To understand this better, consider the following function:

fixEither :: (a - Either e a) - Either e a
fixEither f = x where
x = f a
(Right a) = x

Here, f *cannot* attempt to do anything with its argument until it is
absolutely known that f is returning a Right value.

Perhaps there is a different way to write this interpreter that avoids
needing to tie the knot so tightly?  Can you split recursive-let into
two stages, one where you construct the environment with dummy
variables and a second where you populate them with the results of
their evaluations?  You might need some sort of mutable thunk that you
can store in the environment, which makes sense to me; in GHC Core,
let means allocate a thunk on the heap.

  -- ryan

On 11/27/09, Ben Franksen ben.frank...@online.de wrote:
 Ben Franksen wrote:
 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]

 While this works for simple var=constant declarations, it breaks down again
 as soon as I add lambdas and application. Same symptoms as before: eval
 loops; and it works again if I remove the ErrorT (but then I get a pattern
 match failure if I apply a non-function which is of course what I wanted to
 avoid with the ErrorT).

 This is maddening! There must be some way to get mutual recursion to work
 while still allowing for clean handling of failure. What galls me the most
 is that it is so unpredictable whether the program will terminate with a
 given input or not.

 (The code is attached.)

 Cheers
 Ben

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2009-11-26 Thread Ben Franksen
Derek Elkins wrote:
 On Wed, Nov 25, 2009 at 3:48 PM, Ben Franksen ben.frank...@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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe