no continuations

dvanhorn at emba.uvm.edu dvanhorn at emba.uvm.edu
Fri Jan 9 12:17:18 EST 2004


Ashley Yakeley wrote:
> In article <20040102051625.053B1AB8D at Adric.metnet.navy.mil>,
>  oleg at pobox.com wrote:
> 
>>Similarly, R5RS obligates any Scheme implementation to resort to
>>assignments when processing a letrec form.
> 
> Not mine! I do use a polyvariadic fixed-point function.
>
>>An implementation may not
>>use a (polyvariadic) Y to implement letrec, unless the implementation
>>can prove that the difference is unobservable for the form in
>>question.
> 
> Do you have an example of use of Y for letrec where a program would 
> violate R5RS?

http://groups.google.com/groups?selm=976rij%24jd1%241%40news.gte.com

In this post to c.l.scheme, Dorai Sitaram writes:

   letrec with set! is certainly different from letrec with Y,
   and you don't need call/cc to distinguish the two.

   (define *keep-track* '())

   (letrec ((fact (lambda (n) 
                    (set! *keep-track* (cons fact *keep-track*))
                    (if (= n 0) 1
                        (* n (fact (- n 1)))))))
     (fact 8))

   and then do

   (eq? (car *keep-track*) (cadr *keep-track*))

   If letrec is set!-based (as in Scheme), the
   result is #t.  If it is Y-based, the result is #f.  Why
   this is should be obvious if you mentally (or with
   pencil) trace what Y does.

   Scheme's letrec defines recursive procedures by making
   the lexical variable bound to a recursive procedure
   whose body contains the references to the same lexical
   variable.   In other words, data recursion in the
   underlying environment is used to represent the
   recursive procedure perceived by the user.  The
   fixed-point approach does not (and clearly
   cannot) do that.  

   There is no "wrong choice" in the sense that
   alternative choices were cut off.  Users have enough
   machinery to define their preferred version of letrec
   using syntactic extension.  But the letrec that
   comes with Scheme is an extremely good and pragmatic
   one, and is more efficient than a Y-based letrec could
   be expected to be. 

   --d

HTH,
/david


More information about the Haskell-Cafe mailing list