
On Tuesday, December 30, 2003 5:04 PM, Kevin S. Millikin [SMTP:kmillikin@atcorp.com] wrote:
Oh, sure. I didn't mean to quibble with the idea that continuations are computational effects. Just wanted to point out that (I think) you can't macro express mutation with call/cc, unless you've already got mutation anyway.
[snip]
Yup. If you do that, you can use d as your setter and c as your getter:
(define c (make-cell)) (define d c) ((d 'set) 9) (c 'get) 9 ((d 'set) 17) (c 'get) 17
It sure looks like the example contradicts the assertion, but I happen to know that there is a set! (or some other assignment) in the macro expansion of define. I'm just using call/cc to get at that, rather than getting at the one in the expansion of letrec. Moved to Haskell Cafe.

Kevin S. Millikin wrote:
It sure looks like the example contradicts the assertion, but I happen to know that there is a set! (or some other assignment) in the macro expansion of define. I'm just using call/cc to get at that, rather than getting at the one in the expansion of letrec.
In Scheme 'define' is normally a primitive because in most of the systems a top-level 'define' must create a top-level variable binding, and there is no other R5RS form that can do that. Still, you're right about set!. R5RS says: "5.2.1. Top level definitions At the top level of a program, a definition (define variable expression) has essentially the same effect as the assignment expression (set! variable expression) if variable is bound. If variable is not bound, however, then the definition will bind variable to a new location before performing the assignment... Some implementations of Scheme use an initial environment in which all possible variables are bound to locations, most of which contain undefined values. Top level definitions in such an implementation are truly equivalent to assignments." Similarly, R5RS obligates any Scheme implementation to resort to assignments when processing a letrec form. 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. Incidentally, one can easily observe how letrec is implemented. For example, in Ocaml, the observation says that "let rec" is implemented via an assignment. So, in the examples mentioned earlier, call/cc simply pries open the assignment that was already present in letrec or define. Alone, call/cc cannot emulate assignments. There was a message exactly on the same topic "call/cc is insufficient to emulate set!" posted on comp.lang.scheme two years ago: http://google.com/groups?selm=200103010316.TAA30239%40adric.cs.nps.navy.mil Threads http://google.com/groups?threadm=200102212311.PAA76922%40adric.cs.nps.navy.m... http://google.com/groups?threadm=200102212321.PAA76933%40adric.cs.nps.navy.m... http://google.com/groups?threadm=200102220358.TAA77339%40adric.cs.nps.navy.m... might also be useful.

In article <20040102051625.053B1AB8D@Adric.metnet.navy.mil>, oleg@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. (define circular (letrec ((c (cons 'x c))) c)) (list-head circular 10) => (x x x x x x x x x x) Try it yourself at http://hscheme.sourceforge.net/interpret.php. I also make the fixed-point function available as "call-with-result", it's more or less equivalent to this: (lambda (f) (letrec ((x (f x))) x))
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? -- Ashley Yakeley, Seattle WA

Ashley Yakeley wrote:
In article <20040102051625.053B1AB8D@Adric.metnet.navy.mil>, oleg@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

In article <1073668638.3ffee21e290c4@webmail.emba.uvm.edu>, dvanhorn@emba.uvm.edu wrote:
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.
Does Haskell mfix count as Y? My implementation is mfix-based, and the above code returns 40320 #t. Try it yourself at http://hscheme.sourceforge.net/interpret.php if you don't believe me. I'd be very interested to know if my implementation of Scheme varies from R5RS due to this issue. -- Ashley Yakeley, Seattle WA

Ashley Yakeley 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.
I'm sorry but you don't have the choice in the matter -- if you wish to call your implementation R5RS-compliant. R5RS _requires_ letrec to use assignments. The latter issue has been extensively discussed, on comp.lang.scheme, in Amr Sabry's Technical report "Recursion as a computational effect" and in many other places. Here's the exact quote from R5RS, Section 4.2.2 "Semantics [of letrec]: The variables are bound to fresh locations holding undefined values, the inits are evaluated in the resulting environment (in some unspecified order), each variable is assigned [sic!] to the result of the corresponding init, the body is evaluated in the resulting environment, and the value(s) of the last expression in body is(are) returned."
(define circular (letrec ((c (cons 'x c))) c))
I'm afraid that is not a R5RS compliant code. R5RS states (in the same Section 4.2.2) "One restriction on letrec is very important: it must be possible to evaluate each init without assigning or referring to the value of any variable . If this restriction is violated, then it is an error." In the quoted code, the <init> is (cons 'x c), and it is impossible to evaluate that expression according to the semantics of Scheme without referring to the value of variable c. If it were (define circular (letrec ((c (cons 'x (delay c)))) c)) then there is no contradiction with R5RS.
Do you have an example of use of Y for letrec where a program would violate R5RS?
http://google.com/groups?selm=7eb8ac3e.0304131423.4f103d4f%40posting.google.... The difference between the Y and set! approaches to letrec *is* observable. I must state that the exact conformance to the R5RS semantics of letrec is important -- for example, for the code that uses the non-deterministic choice operator 'amb' or for the code that uses shift/reset. Otherwise, bizarre behavior can occur -- and has occurred. I can send you an example privately.

In article <20040110040353.37C17AB8D@Adric.metnet.navy.mil>, oleg@pobox.com wrote:
(define circular (letrec ((c (cons 'x c))) c))
I'm afraid that is not a R5RS compliant code.
Indeed not, it merely demonstrates fixed-point behaviour. Nevertheless, allowing this as an extension does not make my implementation non-compliant. See section 1.3.2 on this point.
Do you have an example of use of Y for letrec where a program would violate R5RS?
http://google.com/groups?selm=7eb8ac3e.0304131423.4f103d4f%40posting.google.... m
The difference between the Y and set! approaches to letrec *is* observable.
I don't believe you. My implementation uses Haskell's "mfix", which looks like a Y to me. I certainly don't use anything like "set!". But my implementation passes Dorai Sitaram's test: (define *keep-track* '()) (letrec ((fact (lambda (n) (set! *keep-track* (cons fact *keep-track*)) (if (= n 0) 1 (* n (fact (- n 1))))))) (fact 8)) (eq? (car *keep-track*) (cadr *keep-track*)) My implementation returns 40320 #t ...which is apparently correct behaviour for R5RS. Indeed I get exactly the same result in mzscheme and guile. Again, I encourage you to try for yourself at http://hscheme.sourceforge.net/interpret.php (though it's a bit slow). -- Ashley Yakeley, Seattle WA

I tried the following letrec correctness test using your interpret.php, and unfortunately, the interpreter returned no answer. (let ((cont #f)) (letrec ((x (call-with-current-continuation (lambda (c) (set! cont c) 0))) (y (call-with-current-continuation (lambda (c) (set! cont c) 0)))) (if cont (let ((c cont)) (set! cont #f) (set! x 1) (set! y 1) (c 0)) (+ x y)))) Could you tell me what does this test return on your system? Now, why the exact implementation of letrec is important. Let us consider the following code that involves a non-deterministic choice. (define *k* #f) ; A rough-and-dirty ambient combinator. It's easier to write it ; than to look it up... (define (amb alt1 alt2) (call-with-current-continuation (lambda (k) (set! *k* (lambda () (set! *k* #f) (k alt2))) alt1))) (define (fail) (*k*)) (display (letrec ((val1 5) (proc (amb (lambda () (display "In first choice") (newline) (fail)) (lambda () (display "The second choice") (newline) 42))) (val2 7) ) (let ((old-vals (list val1 val2))) (set! val1 '*bad*) (set! val2 '*bad*) (list old-vals (proc))))) So, we bind val1 to 5, val2 to 7, and proc to the first choice. We proceed to evaluate the body of letrec with the first choice. We mutate val1 and val2, and evaluate our first choice, which didn't work out. So, we try the second choice. The correct implementation of letrec (e.g., Petite Chez Scheme, SCM) will *restore* the values of val1 and val2! That is, the changes made during the evaluation of the first choice will be backed out, and we start the second choice using the same original values of val1 and val2. Choices must indeed be evaluated in the same "environment", otherwise, they can't be called non-deterministic. So, if we evaluate the test on a conforming Scheme implementation, we get In first choice The second choice ((5 7) 42) Alas, many Scheme systems do not implement letrec correctly. Therefore, when we try the program on one of these systems (e.g., Gambit, Bigloo, Scheme48), we see In first choice The second choice ((*bad* 7) 42) A sad interaction between the choices.

In article <20040112005635.CB12DAB8D@Adric.metnet.navy.mil>, oleg@pobox.com wrote:
(let ((cont #f)) (letrec ((x (call-with-current-continuation (lambda (c) (set! cont c) 0))) (y (call-with-current-continuation (lambda (c) (set! cont c) 0)))) (if cont (let ((c cont)) (set! cont #f) (set! x 1) (set! y 1) (c 0)) (+ x y))))
Could you tell me what does this test return on your system?
It causes hscheme to exit silently. Very odd. I'll try to fix it, but I suspect it's something fundamental to my design, and connected to precisely these issues. -- Ashley Yakeley, Seattle WA

In article
I don't believe you. My implementation uses Haskell's "mfix", which looks like a Y to me. I certainly don't use anything like "set!".
Actually, on looking at the code for my monad, it turns out I do. I spent awhile trying to figure out how to make a monad that could lift IO, and was also an instance of both MonadCont (so I could do call-with-current-continuation) and MonadFix (so I could do letrec the way I wanted it). I use CPS, and my implementation of mfix actually uses newIORef, writeIORef and readIORef directly. But I'd forgotten... -- Ashley Yakeley, Seattle WA
participants (4)
-
Ashley Yakeley
-
dvanhorn@emba.uvm.edu
-
Kevin S. Millikin
-
oleg@pobox.com