> 1.  It is supposed to be considered an error if an initializer references
   > the value of any binder variable.  This implementation does indeed respect

   Why do you say that? I thought that "letrec" semantics was precisely
   setup to allow mutually recursive references within
   initializers. Though, since Scheme is an applicative language
   (strict), there is no way to actually use a value recursively (or
   mutually recursively) within its definition unless it is a lambda.

  Why do I say that?  Because that's what it says in the Scheme
definition.  The reason binder references work in lambdas is because
the result of a lambda evaluation is a closure, which does not involve 
evaluating the body.  So any references to letrec binders in the body
will get delayed until the closure is activated.

   But it is difficult to check for that dynamically. Most scheme
   interpreters probably won't check that recursion is through a lambda,
   although they might impose a syntactic restriction like "all
   initializers must be lambdas".

  I agree that it is difficult to check for dynamically, and probably
not worthwhile either.  MIT's Scheme48 produces a nameless ("local0") 
exception when you try this.

   Your problem of stack overflow on error is coming precisely because it
   looks like you are doing eager error checking for all the initializer
   values before adding them to the environment.

           (=*=>)       :: [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

   It looks like that you are checking the entire value list "x" for
   being error-free before adding any of its already computed values to
   the recursive environment. That forces the evaluation on all
   initializers even after encountering a first error. 

  Thank you; I think you are exactly right.  Here is the description of
listMaybeErrs from the GHC library:

  `listMaybeErrs' takes a list of `MaybeErrs' and, if they all succeed,
  returns a `Succeeded' of a list of their values.  If any fail, it
  returns a `Failed' of the list of all the errors in the list.

  The reason I wrote the (=*=>) operator in the first place was
essentially since I only cared about the first operator!

  So in fact there were two problems with the code I first presented:

        1) It tries to evaluate all the initializers, even if one
           initializer fails.

        2) I was checking initializers for failure *before* adding
           bindings for their values to the environment.

  I have fixed the first problem, with this little temporary hack:

> 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
>         (=*=>) :: [Robust r e] -> ([r] -> Robust r' e) -> Robust r' e
>         x =*=> k = 
>               case errQ x [] of
>                       OK rs           -> k rs
>                       Throw e         -> throw e
>         errQ :: [Robust r e] -> [r] -> Robust [r] e
>         errQ (OK x:xs)    acc = errQ xs (x : acc)
>         errQ (Throw x:xs) acc = throw x
>         errQ []           acc = ok acc

  errQ checks each value that results from the evaluation of the
initializers, but quits early when it finds an error (Throw pattern).

  However, two problems still remain.  Suppose an initializer is a
lambda-expression.  The evaluation of the initializer produces a closure,
consisting of the formals, the function body and the environment at the time
of the evaluation.  This means that once I evaluate a lambda-expression, I can
never add any more bindings to the closure environment.  But this is precisely
what I need to do to implement the letrec.

  The Scheme definition gives rewrite rules for letrecs.  If we consider the
following example ( I'll represent a closure as a triple (formals, body,
environment) ):

  (letrec (     (x (lambda () (y)))     ; producing closure (,y,e)
                (y (lambda () #t))      ; producing closure (,#t,e)
          )

        (x)     ; using environment e = { x = (,y,e) , y = (,#t,e) }

  )

  this would rewrite to the following expression:

  (let    (     (x undef)               ; producing binding x = undef
                (y undef)               ; producing binding y = undef
          )

        ; current env. e = { x = undef, y = undef }

        (set! x (lambda () (y)))

        ; current env. e' = { x = (,y,e) , y = undef }

        (set! y (lambda () #t))

        ; current env. e'' = { x = (,y,e) , y = (,#t,e')

        (x) ; using env. e''

  )

  where undef = undef (the bottom value).  Notice that in e'', x and y are
bound to closures holding different environments.  In particular, the closure
associated with x is e, which does not hold a valid binding for y.  So you
would expect the application of x in the last statement to fail.  But this
example is not SUPPOSED to fail, so it must be that the environments in the
closures are actually references (pointers), not values.

  But obviously I can't use this approach in Haskell, where there is no
concept of a reference, at least without using monads.  If I used monads, then
the type of the environment, Env, would change to _State Env, which means I
have to using a state monad everywhere else (outside letrec expressions) too,
which seems overkill.

  The other alternative, which I was trying to implement originally, is just
to define the environment recursively, and let Haskell do the knot-untying for
me in a lazy way.  But this won't work either because an initializer may fail.
Evaluating an expression has type:

  eval :: Env -> Exp -> Robust Datum Error

  whereas Env's can only hold Datums.  So I need to check whether or not an
expression evaluated correctly before I can add it to the environment.  In
other words, I have to perform a case analysis on an evaluation result before
I can bind it to anything.  That means that the evaluation gets forced, and so
lazy knot-tying will not work (as far as I can see).

Frank Christoph
[EMAIL PROTECTED]


Reply via email to