First, thanks all for the input on representing lists and avoiding
intermediary data constructors.  I ended up using the proper list/improper
list representation anyways, but it doesn't seem to have made much of a
difference, convenience-wise.  Also, as someone suggested, I realized that I
was unknowingly using Haskell's data constructors as record field labels to
annotate product types; I've since been able to collapse the type tree a great
deal.

  My question is what is the most convenient way to implement recursive lets
in a Scheme-like, interpreted language, i.e., something of the form:

  (letrec       ((var1 init-exp1)
                 (var2 init-exp2)
                 ...
                 (varn init-expn))
        body)

  where the value of the expression is the value of body evaluated in the
environment of the letrec augmented by var1..varn bound to the results of the
initializer expressions init-exp1..init-expn.  The initializer expressions
themselves get evaluated in a mutually recursive environment.

  The code I have now for this is essentially the following:

        -- bindings::(Variable,Exp) and body::Exp
        eval :: Env -> Exp -> Robust Datum Error
        eval env (LetRecExp bindings body) =
          let
                vars  = map fst bindings
                inits = map snd bindings
                OK env' = map (eval env') inits =*=> \vals ->
                          OK (addListToFM env (zip vars vals))
          in
                eval env' body

  where

        data Robust r e = OK r | Throw e
        -- (I renamed GHC's MaybeErr)
  and

        (=*=>)  :: [Robust r e] -> ([r] -> Robust r' e) -> Robust r' e
        x =*=> k = case listMaybeErrs x of
                        OK rs           -> k rs
                        Throw (e:es)    -> Throw e

  and listMaybeErrs :: [Robust r e] -> Robust [r] [e].  (addListToFM
is also straight from GHC's FiniteMap library module.)

  In other words, (=*=>) is only there since I only care about the
first error.

  This code works, except for three (big) problems:

  1.  It is supposed to be considered an error if an initializer references
the value of any binder variable.  This implementation does indeed respect
this specification, but not elegantly; i.e., if someone does do this, the
interpreter will eventually run out of stack space and crash.

  2.  The same stack overflow behavior results when an initializer fails,
throwing an exception, e.g.,

        (letrec ((x (cons 1))) X)

  I expected that I would get an incomplete pattern match error instead of
this behavior.  Does anyone know why this happens?

  In any case, what I would like to do of course is to propogate that
exception upwards instead of having the interpreter just crash with a cryptic
message about stack overflows.

  3.  This code is too lazy.  For example, this expression succeeds with value
#t:

        (letrec ((x (cons 1))) #t)

  It ought to fail because the initializer is incorrect.


  If I try to fix this as follows:

        eval env (LetRecExp bindings body) =
          let
                vars    = map fst bindings
                inits   = map snd bindings
                env'    = env' ==> \env'' ->
                          map (eval env'') inits =*=> \vals ->
                          OK (addListToFM env (zip vars vals))
          in
                env' -> \env'' -> eval env'' body    

  where ==> is the thenMaB operator, nothing works anymore; this is presumably
because every value is demanded on every recursive function call.

  I know how to make this work by injecting an undefined value into the domain
values, binding each binder to that value in the letrec environment, then
evaluating each initializer in that environment and binding those values (if
they succeed) before evaluating the body, but it seems like a waste to use
that approach in Haskell which, after all, could theoretically do all this for
me, via laziness.

  Any helpful comments would be very much appreciated.

Frank Christoph
[EMAIL PROTECTED]

P.S.: BTW, I *did* take a look at GHC's interpreter code, and it looks exactly
like mine, except for the significant difference that there is no need to
check for evaluation exceptions in GHCI because they can type-verify the code
before interpreting it.  (Incidentally, they also used a list generator to
evaluate each var-init pair, which is somewhat neater and clearer than using a
map, I think; but I realized this approach is untenable for me because the
exception-checking gets in the way.  I suppose you could do this in Gofer,
though, if you were using a evaluation and exception monads as proposed in
Jones, et al.'s paper.)


Reply via email to