Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

letrec

27 views
Skip to first unread message

Abc Def

unread,
Feb 18, 2001, 8:10:26 AM2/18/01
to
I'd appreciate discussion and pointers concerning letrec.
Can letrec be expressed in terms of lambdas and singleton
letrecs (ie, a function may refer to itself) if we assume
all bindings are immutable? This is different from saying
"without using set!". Bindings for the same value are
permitted to be distinct. I hunted for a bit, but either:
the material was too formal for my understanding without
extensive studying (which wouldn't hurt either); set! was
used, as in r5rs; the compiler representation included a
native letrecness.

Thanks much, [Ag] Andy Gaynor sil...@quadrix.com

In addition, can someone recommend a real news server?
This web-based interface I'm using sucks.
(I'd prefer to keep this off-topic stuff in email.)

Bruce Hoult

unread,
Feb 18, 2001, 6:03:58 PM2/18/01
to
In article <3AC6...@MailAndNews.com>, Abc Def
<stupid_em...@MailAndNews.com> wrote:

> I'd appreciate discussion and pointers concerning letrec.
> Can letrec be expressed in terms of lambdas and singleton
> letrecs (ie, a function may refer to itself) if we assume
> all bindings are immutable?

I suspect not, but I think you should be able to generalize the Y
combinator to define more than one function at a time. I think you'll
need multi-value function results, or else convert it into CPS though.

-- Bruce

Daniel C. Wang

unread,
Feb 18, 2001, 11:22:04 PM2/18/01
to

Bruce Hoult <br...@hoult.org> writes:

No you just need records to generalize to the mutually recursive case.
And since records can be encoded as functions. You can in theory do with out
it.

Bruce Hoult

unread,
Feb 19, 2001, 1:20:13 AM2/19/01
to
In article <r8tk86n...@chinstrap.CS.Princeton.EDU>, "Daniel C.
Wang" <danwan...@cs.princeton.edu> wrote:

Perpas you could demonstrate. I don't see how you'd do it as records
(encoded as functions) that wouldn't also let you do it using
multi-value results (encoded using CPS).

-- Bruce

Eli Barzilay

unread,
Feb 19, 2001, 2:38:24 AM2/19/01
to
Bruce Hoult <br...@hoult.org> writes:

> In article <r8tk86n...@chinstrap.CS.Princeton.EDU>, "Daniel C.
> Wang" <danwan...@cs.princeton.edu> wrote:
>
> > Bruce Hoult <br...@hoult.org> writes:
> >
> > > I suspect not, but I think you should be able to generalize the Y
> > > combinator to define more than one function at a time. I think you'll
> > > need multi-value function results, or else convert it into CPS though.
> >
> > No you just need records to generalize to the mutually recursive case.
> > And since records can be encoded as functions. You can in theory do with
> > out
> > it.
>
> Perpas you could demonstrate. I don't see how you'd do it as
> records (encoded as functions) that wouldn't also let you do it
> using multi-value results (encoded using CPS).

I think that Daniel is talking about the standard impl., something
like the following (where Y is the standard one):

| (define Y
| (lambda (f)
| ((lambda (x) (f (lambda (y) ((x x) y))))
| (lambda (x) (f (lambda (y) ((x x) y)))))))
|
| (define (pair x y) (lambda (s) (s x y)))
| (define (1st p) (p (lambda (x y) x)))
| (define (2nd p) (p (lambda (x y) y)))
|
| (define even/odd?
| (Y (lambda (s)
| (pair (lambda (n) (if (zero? n) #t ((2nd s) (sub1 n))))
| (lambda (n) (if (zero? n) #f ((1st s) (sub1 n))))))))
| (define even? (1st even/odd?))
| (define odd? (2nd even/odd?))

--
((lambda (x) (x x)) (lambda (x) (x x))) Eli Barzilay:
http://www.barzilay.org/ Maze is Life!

erik hilsdale

unread,
Feb 19, 2001, 3:21:13 PM2/19/01
to
[Warning: long, and possibly pointless]

It looks like others have already answered with the obligatory
references to the Y-combinator. Here's an alternate approach that is
also intricately linked to the Y-combinator, but (not very well)
camoflaged in macrology. It also has a constructive bent. Your
mileage may vary.

First, allow me to restrict your problem a tad. In order to make the
forms in this message readable, I've assumed one expression per lambda
body. That's not Scheme, but relaxing this particular restriction is
easy.

Not as easy is relaxing a restriction that the other posters already
assumed. Dealing with real Scheme letrec is a pain, because any old
expression can sit on the right hand side of a letrec decl. Since
your question deals with scoping issues rather than evaluation-order
issues, I think it fair to restrict right-hand values of a letrec
expression to lambda expressions. So we assume all letrecs look like
this:

(letrec ((Var (lambda (Formal ...) ProcBody))
...)
Body)

If you're unfamilliar with r5rs macro syntax, read '...' as kleene
star. So a letrec has zero or more decls, each of which has a Var
followed by a lambda expression. Here's the prototypical example:

(letrec ((even? (lambda (x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (x) (if (zero? x) #f (even? (- 1 x))))))
(odd? 42))

So you're asking whether there's a transformation from any such letrec
expression to an expression only involving lambda (and reflexive
letrec, but you don't actually need that).

For clarity, I'll also use let, but that's safe because

(let ((Var Exp) ...) Body) -->
((lambda (Var ...) Body) Exp ...)

So let's start working out the transformation. We'll start with an
identity transformation and work until we have a transformation with
the right properties. After the general transformation, I'll show how
the transformation effects our prototypical example.

(letrec ((Var (lambda (Formal ...) ProcBody))
...)
Body)
-->
(letrec ((Var (lambda (Formal ...) ProcBody))
...)
Body)

(letrec ((even? (lambda (x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (x) (if (zero? x) #f (even? (- 1 x))))))
(odd? 42))
-->
(letrec ((even? (lambda (x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (x) (if (zero? x) #f (even? (- 1 x))))))
(odd? 42))

The first thing we need to get rid of is that letrec. But we still
want to bind the variables, so how about just using let?

;vvv
(let ((Var (lambda (Formal ...) ProcBody))
...)
Body)

;vvv
(let ((even? (lambda (x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (x) (if (zero? x) #f (even? (- 1 x))))))
(odd? 42))

This satisfies your constraints (only lambda), but of course it
doesn't work. Now, any reference to one of the 'Var's in 'ProcBody'
will escape. We need to capture these references. Luckily, we can
capture them by adding them to the formals list of all the lambda
expressions.

;vvvvvvv
(let ((Var (lambda (Var ... Formal ...) ProcBody))
...)
Body)

;vvvvvvvvvv
(let ((even? (lambda (even? odd? x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (even? odd? x) (if (zero? x) #f (even? (- 1 x))))))
(odd? 42)) ;^^^^^^^^^^

Great. We've prevented the recursive references to the 'Var's from
escaping. Hooray. Unfortunately, we've also generated a whole bunch
of "wrong number of arguments" errors, including one from the body,
which before now wasn't giving us any trouble. Let's fix that one
first.

(let ((Var (lambda (Var ... Formal ...) ProcBody))
...)
(let ((Var (lambda (Formal ...) (Var Var ... Formal ...))) ; <<<
...) ; <<<
Body))

(let ((even? (lambda (even? odd? x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (even? odd? x) (if (zero? x) #f (even? (- 1 x))))))
(let ((even? (lambda (x) (even? even? odd? x))) ; <<<
(odd? (lambda (x) (odd? even? odd? x)))) ; <<<
(odd? 42)))

How did we fix it? By providing a _new_ definition for each Var, one
that takes in just enough arguments to fill the old formals, and then
delegates the work to the new procedure, which takes in all the
recursive functions in addition to the arguments. We could do that
because all the 'Var's were in scope for the new let we placed in the
body.

Of course, the transformation still has nasty "wrong number of
arguments" errors from the ProcBody forms inside the letrec. But we
can do the exact delegation trick there.

(let ((Var (lambda (Var ... Formal ...)
(let ((Var (lambda (Formal ...) ; <<<
(Var Var ... Formal ...))) ; <<<
...) ; <<<
ProcBody)))
...)
(let ((Var (lambda (Formal ...) (Var Var ... Formal ...)))
...)
Body))

(let ((even? (lambda (even? odd? x)
(let ((even? (lambda (x) (even? even? odd? x))) ; <<<
(odd? (lambda (x) (odd? even? odd? x)))) ; <<<
(if (zero? x) #t (odd? (- 1 x))))))
(odd? (lambda (even? odd? x)
(let ((even? (lambda (x) (even? even? odd? x))) ; <<<
(odd? (lambda (x) (odd? even? odd? x)))) ; <<<
(if (zero? x) #f (even? (- 1 x)))))))
(let ((even? (lambda (x) (even? even? odd? x)))
(odd? (lambda (x) (odd? even? odd? x))))
(odd? 42)))

And we're done. How do we know we're done? Because we can try it
out. Let's define letrec^ to be a syntactic form that expands
according to our expansion.

(define-syntax letrec^
(syntax-rules (lambda)
((letrec^ ((Var (lambda (Formal ...) ProcBody))
...)
Body)
(let ((Var (lambda (Var ... Formal ...)
(let ((Var (lambda (Formal ...)
(Var Var ... Formal ...)))
...)
ProcBody)))
...)
(let ((Var (lambda (Formal ...) (Var Var ... Formal ...)))
...)
Body)))))

And we can try it out:

> (letrec^ ((even? (lambda (x) (if (zero? x) #t (odd? (- 1 x)))))
(odd? (lambda (x) (if (zero? x) #f (even? (- 1 x))))))
(odd? 42))
#f

-erik

--
erik hilsdale (ehil...@cs.indiana.edu)
http://www.cs.indiana.edu/~ehilsdal/

Alamazookay Petrofsky

unread,
Feb 19, 2001, 8:37:51 PM2/19/01
to
ehil...@cs.indiana.edu (erik hilsdale) writes:
> [Warning: long, and possibly pointless]

But I enjoyed it. I offer an improved letrec definition below that
supports arbitrary init values (not just lambdas). As already
stipulated, this breaks in the presence of mutation or side-effects.
There are also problems with eqv?, e.g. with standard letrec the
expression (letrec ((f (lambda () f))) (eqv? f (f))) must return #t,
but in both of our implementations it may return #f.

I believe your use of syntax-rules is not legal in r5rs because the
pattern variable Var has ellipses depth of one in the pattern, but a
depth of up to three in the template. This version avoids using that
extension.

(define-syntax letrec
(syntax-rules ()
((letrec ((var val) ...) body ...)
(let ((var val) ...)
(let ((dispatch
(lambda (dispatch which . args)
(let ((var (if (procedure? val)
(lambda args
(apply dispatch dispatch 'var args))
val))
...)
(if which
(apply (case which ((var) val) ...) args)
(begin body ...))))))
(dispatch dispatch #f))))))


Here's a sample expansion:

(letrec ((even? (lambda (n) (if (zero? n) #t (odd? (- n 1)))))
(odd? (lambda (n) (if (zero? n) #f (even? (- n 1)))))
(num 42))
(even? num))
=>
(let ((even? (lambda (n) (if (zero? n) #t (odd? (- n 1)))))
(odd? (lambda (n) (if (zero? n) #f (even? (- n 1)))))
(num 42))
(let ((dispatch
(lambda (dispatch which . args)
(let ((even? (if (procedure? even?)
(lambda args
(apply dispatch dispatch 'even? args))
even?))
(odd? (if (procedure? odd)
(lambda args (apply dispatch dispatch 'odd? args))
odd?))
(num (if (procedure? num)
(lambda args (apply dispatch dispatch 'num args))
num)))
(if which
(apply
(case which
((even?) (lambda (n) (if (zero? n) #t (odd? (- n 1)))))
((odd?) (lambda (n) (if (zero? n) #f (even? (- n 1)))))
((num) 42))
args)
(begin (even? num)))))))
(dispatch dispatch #f)))

-al

erik hilsdale

unread,
Feb 20, 2001, 12:29:05 PM2/20/01
to
Alamazookay Petrofsky <Alama...@Petrofsky.Berkeley.CA.US> writes:

> ehil...@cs.indiana.edu (erik hilsdale) writes:
> > [Warning: long, and possibly pointless]
> But I enjoyed it.

Thank you.

> I offer an improved letrec definition below that supports arbitrary
> init values (not just lambdas).

Dealing with general Scheme letrec really is tricky. Your solution,
for example, breaks in the presence of first-class procedures:

(letrec ((even? (list (lambda (n) (if (zero? n) #t ((car odd?) (- n 1))))))
(odd? (list (lambda (n) (if (zero? n) #f ((car even?) (- n 1))))))
(num 42))
((car even?) num))
-->
Error in car: #<procedure even?> is not a pair.

> I believe your use of syntax-rules is not legal in r5rs because the
> pattern variable Var has ellipses depth of one in the pattern, but a
> depth of up to three in the template. This version avoids using
> that extension.

Ah, the infamous

Pattern variables that occur in subpatterns followed by one or
more instances of the identifier ... are allowed only in
subtemplates that are followed by as many instances of ....

from R5RS 4.3.2. I tend to read "as many" meaning "as many or more"
rather than "exactly as many". If any authors are still reading the
list they could probably clarify. It never bothers me enough to go
look at Kohlbecker's thesis, but it probably should.

-erik

------------------------------
Previously, Alamazookay Petrofsky <Alama...@Petrofsky.Berkeley.CA.US> writes:


ehil...@cs.indiana.edu (erik hilsdale) writes:
> [Warning: long, and possibly pointless]

But I enjoyed it. I offer an improved letrec definition below that

-al

--

ol...@pobox.com

unread,
Feb 20, 2001, 10:41:58 PM2/20/01
to

There appears to be a way to replace letrec with a let. The body of
the letrec will have to be modified, but only slightly. The solution
is purely functional. Like Erik Hilsdale, we assume that the right-hand
side of letrec bindings are lambda expressions.

The idea is a transformation of an expression

(letrec
((my-odd? (lambda (x) (if (zero? x) #f (my-even? (- x 1)))))
(my-even? (lambda (x) (if (zero? x) #t (my-odd? (- x 1)))))
)
(my-even? 42))

into the following:

(apply
(lambda (my-odd? my-even?) (my-even? 42))
((lambda (fff)
((lambda (x) (x x))
(lambda (p)
(fff
(lambda y
(apply (lambda (odd? even?) (apply odd? y)) (p p)))
(lambda y
(apply (lambda (odd? even?) (apply even? y)) (p p)))))))
(lambda (my-odd? my-even?)
(let ((my-odd? (lambda (x) (if (zero? x) #f (my-even? (- x 1)))))
(my-even? (lambda (x) (if (zero? x) #t (my-odd? (- x 1))))))
(list my-odd? my-even?))))
)

As you can see, the last few lines are the bindings of the original
letrec form without any modification. The letrec form became a let
form, as promised.

The solution can be generalized:

(define-macro (letrec^ bindings body1 . body-other)
(let ((vars (map car bindings)))
`(apply
(lambda ,vars ,body1 ,@body-other)
((lambda (fff)
((lambda (x) (x x))
(lambda (p)
(fff
,@(map
(lambda (var)
`(lambda y
(apply (lambda ,vars (apply ,var y)) (p p))))
vars)))))
(lambda ,vars
(let ,bindings
(list ,@vars)))))
))

This is a hygienic macro: new bindings for fff, p, y, and x are introduced
within an isolated, restricted scope. No name clashes and free
variable captures are possible.

(letrec^
((my-odd? (lambda (x) (if (zero? x) #f (my-even? (- x 1)))))
(my-even? (lambda (x) (if (zero? x) #t (my-odd? (- x 1)))))
)
(my-odd? 1997))
==> #t

(letrec^
((fact (lambda (n) (if (zero? n) 1 (* n (fact (- n 1)))))))
(fact 5))
==> 120


(letrec^
((triple? (lambda (x) (or (zero? x) (triple2? (- x 1)))))
(triple1? (lambda (x) (and (not (zero? x))
(or (= x 1) (triple? (- x 1))))))
(triple2? (lambda (x) (or (= x 2)
(and (> x 2)
(triple1? (- x 1)))))))
(map
(lambda (x)
(list (triple? x) (triple1? x) (triple2? x)))
`(0 1 2 3 4 5 6 7 8 9 10 11)))
==>
((#t #f #f) (#f #t #f) (#f #f #t) (#t #f #f) (#f #t #f) (#f #f #t)
(#t #f #f) (#f #t #f) (#f #f #t) (#t #f #f) (#f #t #f) (#f #f #t))

Actually I like Erik Hilsdale's solution better: it implicitly relies
on a U fixpoint combinator:
(define (U f) (f f))
which appears simpler and more comprehensible than the Y fixpoint
combinator.


--
Posted from cs.nps.navy.mil [131.120.10.2]
via Mailgate.ORG Server - http://www.Mailgate.ORG

Joe Marshall

unread,
Feb 21, 2001, 10:45:38 AM2/21/01
to

There is an interesting quirk about the RnRS definition of letrec. It
seems that with the appropriate call-with-current-continuation magic
you can expose the implicit SET!s that occur between when a value is
computed and when it is assigned to the letrec variable. Thus even in
a `purely functional' Scheme, if you have letrec and
call-with-current-continuation, you can create side-effects.

I haven't spent much time considering it, but I wonder if one of these
`fixed-point' versions of letrec would behave in the same way.


-----= Posted via Newsfeeds.Com, Uncensored Usenet News =-----
http://www.newsfeeds.com - The #1 Newsgroup Service in the World!
-----== Over 80,000 Newsgroups - 16 Different Servers! =-----

Dorai Sitaram

unread,
Feb 21, 2001, 11:19:08 AM2/21/01
to
In article <pugcdo...@content-integrity.com>,

Joe Marshall <j...@content-integrity.com> wrote:
>
>There is an interesting quirk about the RnRS definition of letrec. It
>seems that with the appropriate call-with-current-continuation magic
>you can expose the implicit SET!s that occur between when a value is
>computed and when it is assigned to the letrec variable. Thus even in
>a `purely functional' Scheme, if you have letrec and
>call-with-current-continuation, you can create side-effects.
>
>I haven't spent much time considering it, but I wonder if one of these
>`fixed-point' versions of letrec would behave in the same way.

That would be a major result.

Charles Martin

unread,
Feb 21, 2001, 1:27:50 PM2/21/01
to
Do you mean something like the following?

(define test
(lambda ()
(letrec ((foo (call-with-current-continuation (lambda (c) (cons 1 c)))))
(display foo) (newline)
(if (< (car foo) 10)
((cdr foo) (cons (+ (car foo) 1) (cdr foo)))))))

That's incredibly cool! Thanks for pointing it out...

Joe Marshall

unread,
Feb 21, 2001, 1:44:29 PM2/21/01
to
Charles Martin <joe...@yahoo.REMOVE.com> writes:

> Do you mean something like the following?
>
> (define test
> (lambda ()
> (letrec ((foo (call-with-current-continuation (lambda (c) (cons 1 c)))))
> (display foo) (newline)
> (if (< (car foo) 10)
> ((cdr foo) (cons (+ (car foo) 1) (cdr foo)))))))
>
> That's incredibly cool! Thanks for pointing it out...

Credit to Alan Bawden and Jonathan Rees (if I remember correctly) who
first pointed this out circa 1986?

>
> Joe Marshall <j...@content-integrity.com> writes:
> > There is an interesting quirk about the RnRS definition of letrec. It
> > seems that with the appropriate call-with-current-continuation magic
> > you can expose the implicit SET!s that occur between when a value is
> > computed and when it is assigned to the letrec variable. Thus even in
> > a `purely functional' Scheme, if you have letrec and
> > call-with-current-continuation, you can create side-effects.

Boris Smilga

unread,
Feb 21, 2001, 2:14:40 PM2/21/01
to
Joe Marshall <j...@content-integrity.com> writes:

> > (define test
> > (lambda ()
> > (letrec ((foo (call-with-current-continuation (lambda (c) (cons 1 c)))))
> > (display foo) (newline)
> > (if (< (car foo) 10)
> > ((cdr foo) (cons (+ (car foo) 1) (cdr foo)))))))

Wow! That's really a jewel of code. Should be somewhere near the top
of the hypothetical "Beauty of Scheme" list.

> Credit to Alan Bawden and Jonathan Rees (if I remember correctly) who
> first pointed this out circa 1986?

Could you provide an exact reference?

-Boris

Joe Marshall

unread,
Feb 21, 2001, 5:30:33 PM2/21/01
to
Boris Smilga <bo...@bhasha.com> writes:

I think it was posted to the scheme mailing list at the time. I'm not
sure anything formal was published.

Jonathan and Alan came up with an implementation of cells

(make-cell initial-value)
(cell-value cell)
(set-cell-value! cell new-value)

that used this trick. The code was *very* complicated (and I can't
reconstruct it off the top of my head).

If either of them are reading this, perhaps they will dig up the
implementation. Otherwise, I guess it will be `left to the reader as
an exercise'. I'll try to reconstruct it tonight.

ol...@pobox.com

unread,
Feb 21, 2001, 5:55:37 PM2/21/01
to

> (define test
> (lambda ()
> (letrec ((foo (call-with-current-continuation (lambda (c) (cons 1 c)))))
> (display foo) (newline)
> (if (< (car foo) 10)
> ((cdr foo) (cons (+ (car foo) 1) (cdr foo)))))))

That example will give the same result if you replace letrec with
let. Thus it doesn't appear to show Joe's point. However, the
following example does:

(define test
(lambda ()
(letrec ((foo (call-with-current-continuation

(lambda (c) (cons 1 (cons foo c))))))


(display foo) (newline)
(if (< (car foo) 10)

((cddr foo) (cons (+ (car foo) 1) (cdr foo)))))))

If you run (test) under Gambit 3.0, you get:

(1 #<void> . #<procedure #x2055656>)
(2 #<void> . #<procedure #x2055656>)
(3 #<void> . #<procedure #x2055656>)
(4 #<void> . #<procedure #x2055656>)
(5 #<void> . #<procedure #x2055656>)
(6 #<void> . #<procedure #x2055656>)
(7 #<void> . #<procedure #x2055656>)
(8 #<void> . #<procedure #x2055656>)
(9 #<void> . #<procedure #x2055656>)
(10 #<void> . #<procedure #x2055656>)

Each line is the value of 'foo', an improper list. The second element
of the improper list is also the value of foo. We clearly see that
Gambit initializes letrec values with #<void>. If we run this code
under Bigloo 2.2b, we get

(1 #unspecified . #<procedure:816c054.-1>)
...
(10 #unspecified . #<procedure:816c054.-1>)

If we use SCM 5d2, we get a problem: unbound variable foo.

Furthermore, to observe Joe's effect, we don't seem to need
call/cc. Consider the following expression:
(letrec ((f f)) (display f))
Under Gambit, it prints #<void>, Bigloo prints #unspecified, and SCM
reports the error. Note, both Erik and I assumed that the initializing
expression of letrec bindings is a lambda-form.

ol...@pobox.com

unread,
Feb 21, 2001, 6:06:30 PM2/21/01
to
>There is an interesting quirk about the RnRS definition of letrec. It
>seems that with the appropriate call-with-current-continuation magic
>you can expose the implicit SET!s that occur between when a value is
>computed and when it is assigned to the letrec variable. Thus even in
>a `purely functional' Scheme, if you have letrec and
>call-with-current-continuation, you can create side-effects.
>

Exactly. This article shows how to emulate set! if we don't have one,
but we do have call/cc.

First, consider a piece of imperative code:

(define i 0)
(let for ()
(if (< i 5)
(begin
(display i) (display " ")
(set! i (+ i 1))
(display i) (newline)
(for)
)))

It's obvious what it prints. Now consider the following
"pure-functional" code:

(define (define-mutable-value val)
(letrec ((make-val
(lambda (val k k-return)
(list val k-return
(lambda (new-val k-return-further)
(k (make-val new-val k k-return-further)))))))
(call-with-current-continuation
(lambda (k)
(make-val val k #f)))))

(define (get-val mutable-value)
(car mutable-value))

(define (set-val mutable-value new-value)
(call-with-current-continuation
(lambda (k-return)
((caddr mutable-value) new-value k-return))))

(define (fixup mutable-value)
(if (cadr mutable-value) ((cadr mutable-value) #f)))

(letrec ((i (define-mutable-value 0)))
;(display "after def: ") (display i) (newline)
(fixup i)
(let for1 ()
(if (< (get-val i) 5)
(begin
(display (get-val i)) (display " ")
(set-val i (+ (get-val i) 1))
(display (get-val i)) (newline)
(for1)
))))

The latter piece of code prints the same result as the imperative code
above. Note, you may _NOT_ replace (letrec ((i (define-mutable-value
0))) with let! the code won't work: it will loop forever. Tested on
Gambit, Bigloo and SCM.

Boris Smilga

unread,
Feb 21, 2001, 7:30:39 PM2/21/01
to
ol...@pobox.com writes:

> That example will give the same result if you replace letrec with
> let. Thus it doesn't appear to show Joe's point. However, the
> following example does:
>
> (define test
> (lambda ()
> (letrec ((foo (call-with-current-continuation
> (lambda (c) (cons 1 (cons foo c))))))
> (display foo) (newline)
> (if (< (car foo) 10)
> ((cddr foo) (cons (+ (car foo) 1) (cdr foo)))))))

> Furthermore, to observe Joe's effect, we don't seem to need


> call/cc. Consider the following expression:
> (letrec ((f f)) (display f))
> Under Gambit, it prints #<void>, Bigloo prints #unspecified, and SCM
> reports the error. Note, both Erik and I assumed that the initializing
> expression of letrec bindings is a lambda-form.

To me it looks like a violation of the R5RS restriction that "it must
be possible to evaluate each <init> without assigning or referring to
the value of any <variable>" (4.2.2, 12 left). This is an error, but
not one that should necessarily be signaled. Judging from the examples
above, neither Gambit nor Bigloo do that. SCM does, and so does Scheme
48 that prints "Error: LETREC variable used before its value has been
produced" thus being the most honest of all 'em implementations.

Actually, this norm also exists in both R[34]RS. R3RS is the oldest
Report I've got access to, so I'd like to ask somebody who knows that
better: when was the restriction imposed (and, more generally, how old
is letrec)? Was it in RRRS? RRS? AI Memo 349? any collateral
documentation?

Thanks in advance.
-Boris

Alfalfa Petrofsky

unread,
Feb 21, 2001, 8:24:28 PM2/21/01
to
ehil...@cs.indiana.edu (erik hilsdale) writes:

> Alamazookay Petrofsky <Alama...@Petrofsky.Berkeley.CA.US> writes:
>
> > I offer an improved letrec definition below that supports arbitrary
> > init values (not just lambdas).
>
> Dealing with general Scheme letrec really is tricky. Your solution,
> for example, breaks in the presence of first-class procedures:

Oops, you're right.

Transforming an arbitrary letrec into an all-lambas letrec is not too
complicated conceptually. Unless I'm utterly wrong again, we need
only wrap each value in a zero-arg lambda and add a pair of
parentheses to each variable reference, i.e.:

(letrec ((even? (list (lambda (n)
(if (zero? n) #t ((car odd?) (- n 1))))))
(odd? (list (lambda (n)
(if (zero? n) #f ((car even?) (- n 1))))))
(num 42))
((car even?) num))

==>
(letrec ((even? (lambda ()
(list (lambda (n)
(if (zero? n) #t ((car (odd?)) (- n 1)))))))
(odd? (lambda ()
(list (lambda (n)
(if (zero? n) #f ((car (even?)) (- n 1)))))))
(num (lambda () 42)))
((car (even?)) (num)))

The only problem is that we need to understand the syntax of all the
code used in the letrec to know if there are any occurrences of the
identifiers that are not variable references, e.g.:

(letrec ((foo (lambda (foo) foo)))
(foo (quote foo)))
==>
(letrec ((foo (lambda () (lambda (foo) foo))))
((foo) (quote foo)))

Not only do we have to understand lambda and quote, we would also need
to know what any other macros used in the letrec would do with their
arguments. Alas, determining which foos to wrap is therefore
impossible.

However, a simple extension to the macro system would make writing
this macro straightforward. In R5RS, uses of an identifier with a
syntactic binding are only allowed at the start of a list. Uses of a
bare macro identifier with no parentheses are errors. If these naked
macro uses were instead considered valid macro calls, and the
restrictions on syntax-rules patterns were loosened accordingly, then
we could do things like this:

(let-syntax ((five (syntax-rules () (five 5))))
(+ five 1)) ==> 6

Then, once you've defined letrec-all-lambdas using one of the versions
in previous posts, you could define generic letrec like so:

(define-syntax letrec
(syntax-rules) ()


((letrec ((var val) ...) body ...)

(letrec-all-lambdas
((var (let-syntax
((var (syntax-rules ()
((var . args) ((var) . args))
(var (var))))
...)
(lambda () val)))
...)
(let-syntax
((var (syntax-rules ()
((var . args) ((var) . args))
(var (var))))
...)
body ...))))


I wonder why naked macro uses were disallowed by the rnrs authors.
Hey, they're good enough for cpp...

-al

ol...@pobox.com

unread,
Feb 21, 2001, 10:42:58 PM2/21/01
to

Preceding messages on this thread showed three pure-functional
implementations of letrec. As Erik Hilsdale pointed out, none of them
can deal with the case when an initializing expression
in a letrec binding is not a procedural value per se (but contains a
procedural value). This article shows an implementation of letrec
that is free from that drawback. It can handle arbitrary initializing
expressions. We have to make one assumption though -- an implicit
forcing. If an argument to a strict operation is a promise, this
promise is assumed forced before operation commences. 'apply' is a
strict operation with respect to its first argument. Implicit forcing
is explicitly allowed in R5RS.

The proposed solution is close to letrec^ given in the previous
message, which is quoted below for reference:

(define-macro (letrec^ bindings body1 . body-other)
(let ((vars (map car bindings)))
`(apply
(lambda ,vars ,body1 ,@body-other)
((lambda (fff)
((lambda (x) (x x))
(lambda (p)
(fff
,@(map
(lambda (var)
`(lambda y
(apply (lambda ,vars (apply ,var y)) (p p))))
vars)))))
(lambda ,vars
(let ,bindings
(list ,@vars)))))
))

Here's the general implementation:

(define-macro (letrec^^ bindings body1 . body-other)


(let ((vars (map car bindings)))
`(apply
(lambda ,vars ,body1 ,@body-other)
((lambda (fff)
((lambda (x) (x x))
(lambda (p)
(fff
,@(map
(lambda (var)

`(delay
(apply (lambda ,vars ,var) (apply fff (p p)))))


vars)))))
(lambda ,vars
(let ,bindings
(list ,@vars)))))
))

As you see, it is indeed similar: some lambdas are replaced with
delays. The code above implicitly constructs a lazy, multiple-valued
fixed-point combinator, over terms that are not necessarily
abstractions.

(letrec^^
((od? (lambda (x) (if (zero? x) #f ((force ev?) (- x 1)))))
(ev? (lambda (x) (if (zero? x) #t ((force od?) (- x 1))))))
(od? 1997))
==> #t

That was an easy test. Since a Gambit interpreter does not do the
implicit forcing, we have to force ourselves. The rule of thumb is
that every occurrence of a letrec-bound-variable in initializing
expressions has to be "forced." Note, in Gambit (force x) is x if x is
not a promise; R5RS allows that. Bigloo and SCM report an error if the
argument of force is not the result of a delay. On such systems,
please replace 'force' above with an m-force, defined as
(define (m-force x) (if (promise? x) (force x) x))


(letrec^^
((od? (lambda (x) (if (zero? x) #f ((force ev?) (- x 1)))))
(ev? (lambda (x) (if (zero? x) #t ((force od?) (- x 1)))))
(n 41))
(od? n))
==> #t

Note that n was bound to a non-procedural value, a number.

Erik Hilsdale's test:

(letrec^^
((even? (list (lambda (n) (if (zero? n) #t ((car (force odd?)) (- n 1))))))
(odd? (list (lambda (n) (if (zero? n) #f ((car (force even?)) (- n 1))))))


(num 42))
((car even?) num))

==> #t

It passes. Finally,

(letrec^^ ((f (force f))) (display f))
loops forever, which feels is a more "correct" behavior than
printing #void or #unspecified.

Now the question Joe Marshall posed:

> Thus even in a `purely functional' Scheme, if you have letrec and
> call-with-current-continuation, you can create side-effects.

> I haven't spent much time considering it, but I wonder if one of these
> `fixed-point' versions of letrec would behave in the same way.


For one thing,


(define test
(lambda ()
(letrec ((foo (call-with-current-continuation
(lambda (c) (cons 1 (cons foo c))))))
(display foo) (newline)
(if (< (car foo) 10)
((cddr foo) (cons (+ (car foo) 1) (cdr foo)))))))

(test)

works the same if the letrec above is replaced with letrec^ or
letrec^^. In the latter case, it prints:

(1 #<promise #x206D8AE> . #<procedure #x206D8BE>)
...
(10 #<promise #x206D8AE> . #<procedure #x206D8BE>)

The big question of course is about emulating mutable cells in a
functional language with letrec and call/cc. The previous message on
this thread showed one such code. Amr Sabry has posted a more general
and elegant code to that effect. Alas, neither of these pieces of code
work if you replace letrec with either letrec^ or letrec^^.

Juliusz Chroboczek

unread,
Feb 22, 2001, 9:39:16 AM2/22/01
to
AD> Can letrec be expressed in terms of lambdas and singleton
AD> letrecs (ie, a function may refer to itself) if we assume
AD> all bindings are immutable?

The other answers have theoretical significance. This one doesn't.

Start with the usual

(letrec ((odd? (lambda (x)
(if (zero? x)
#f
(even? (- x 1)))))
(even? (lambda (x)
(if (zero? x)
#t
(odd? (- x 1))))))
...)

Add an explicit binding to make beta-reduction valid:

(letrec ((odd? (lambda (x)
(if (zero? x)
#f
(let ((y (- x 1)))
(even? y)))))
(even? (lambda (x)
(if (zero? x)
#t
(odd? (- x 1))))))
...)

Beta-reduce:

(letrec ((odd? (lambda (x)
(if (zero? x)
#f
(let ((y (- x 1)))
(if (zero? y)
#t
(odd? (- y 1)))))))
(even? (lambda (x)
(if (zero? x)
#t
(odd? (- x 1))))))
...)

Now odd? no longer refers to even?, so we may as well put it in its
own binder:

(letrec ((odd? (lambda (x)
(if (zero? x)
#f
(let ((y (- x 1)))
(if (zero? y)
#t
(odd? (- y 1))))))))
(let ((even? (lambda (x)
(if (zero? x)
#t
(odd? (- x 1))))))
...))

I believe this is a fully general transformation; I've once thought
about using it in implementing a compiler (for a lazy purely functio-
nal toy language, so beta was valid there), but finally decided for
lazy pattern matching instead.

Juliusz

Joe Marshall

unread,
Feb 22, 2001, 12:52:52 PM2/22/01
to
ol...@pobox.com writes:

> > Thus even in a `purely functional' Scheme, if you have letrec and
> > call-with-current-continuation, you can create side-effects.
> > I haven't spent much time considering it, but I wonder if one of these
> > `fixed-point' versions of letrec would behave in the same way.
>

> The big question of course is about emulating mutable cells in a
> functional language with letrec and call/cc. The previous message on
> this thread showed one such code. Amr Sabry has posted a more general
> and elegant code to that effect. Alas, neither of these pieces of code
> work if you replace letrec with either letrec^ or letrec^^.

I'll have to go find that article.

I've never liked the implicit assignment in letrec. If it has been
shown that any purely functional implementation of letrec could mimic
side-effects given the appropriate interaction with
call-with-current-continuation (i.e., the implicit assignment in
letrec is unavoidable), I'd be happier about it.

Dorai Sitaram

unread,
Feb 22, 2001, 1:44:34 PM2/22/01
to
In article <vgq2d2...@content-integrity.com>,

Joe Marshall <j...@content-integrity.com> wrote:
>ol...@pobox.com writes:
>
>> > Thus even in a `purely functional' Scheme, if you have letrec and
>> > call-with-current-continuation, you can create side-effects.
>> > I haven't spent much time considering it, but I wonder if one of these
>> > `fixed-point' versions of letrec would behave in the same way.
>>
>> The big question of course is about emulating mutable cells in a
>> functional language with letrec and call/cc. The previous message on
>> this thread showed one such code. Amr Sabry has posted a more general
>> and elegant code to that effect. Alas, neither of these pieces of code
>> work if you replace letrec with either letrec^ or letrec^^.
>
>I'll have to go find that article.
>
>I've never liked the implicit assignment in letrec. If it has been
>shown that any purely functional implementation of letrec could mimic
>side-effects given the appropriate interaction with
>call-with-current-continuation (i.e., the implicit assignment in
>letrec is unavoidable), I'd be happier about it.

AFAIK, this is not possible, unless Amr or someone else
has come up with something, in which case it would be a
great event indeed in programming language theory. The
idea is that state and control are orthogonal
imperative accretions atop a functional core, and
neither can express the other. Callcc can ferret out
the set! in a letrec, but getting a set! that wasn't
there in the first place is another thing entire.

It is probably a good thing that state and
control are orthogonal (though not a coincidence, since
higher-order control operators were explicitly
fashioned to capture a semantic register that wasn't
being captured elsewhere), for if they were not, the
research effort would be to refashion whatever obtained
in their stead so that we do get cleanly orthogonal and
mutually inexpressible pieces from it.

--d

Alpine Petrofsky

unread,
Feb 22, 2001, 1:56:27 PM2/22/01
to
ol...@pobox.com writes:
> In article <pugcdo...@content-integrity.com>,
> Joe Marshall <j...@content-integrity.com> wrote:
> >
> >There is an interesting quirk about the RnRS definition of letrec. It
> >seems that with the appropriate call-with-current-continuation magic
> >you can expose the implicit SET!s that occur between when a value is
> >computed and when it is assigned to the letrec variable. Thus even in
> >a `purely functional' Scheme, if you have letrec and
> >call-with-current-continuation, you can create side-effects.
> >
>
> Exactly. This article shows how to emulate set! if we don't have one,
> but we do have call/cc.

That is enviably tricky.

The semantics of letrec have always explicitly stated that it makes
assignments. The reason it could be considered a purely functional
construction is that it disallowed uses of the variables until after
all the assignments. For this to remain the case in the presence of
call/cc, the restriction on uses of the variables would need to be
reworded. R5RS says:

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.

To make letrec suitable for inclusion in a functional subset of the
language that includes call/cc, its spec would have to be changed to
something like this:

One restriction on letrec is very important: it is an error to
assign or refer to the value of any <variable> before the
evaluation of all the <init>s has completed. Furthermore, once an
assignment or reference to any of the <variable>s has been made,
it is an error for the evaluation of any of the <init>s to
complete again (which could result from the invocation of a
captured continuation).

-al

Joe Marshall

unread,
Feb 22, 2001, 1:26:29 PM2/22/01
to
Boris Smilga <bo...@bhasha.com> writes:

> Actually, this norm [that letrec values must be able to be evaluated
> without attempting to reference a letrec variable] without also


> exists in both R[34]RS. R3RS is the oldest Report I've got access
> to, so I'd like to ask somebody who knows that better: when was the
> restriction imposed

I *think* R3RS was the first place it was spelled out explicitly.

> (and, more generally, how old is letrec)?

Letrec is derived from LABELS, which was in AIM-349. However, it is
noted that:

``We have decided not to use the traditional LABEL primitive in this
interpreter because it is difficult to define several mutually
recursive functions using only LABEL. The solution, which Hewitt
[Smith and Hewitt] also uses, is to adopt an ALGOLesque block
syntax...''

Bruce Hoult

unread,
Feb 22, 2001, 4:55:59 PM2/22/01
to
In article <dh34rxm...@remote.dcs.ed.ac.uk>, Juliusz Chroboczek
<j...@remote.dcs.ed.ac.uk> wrote:

> I believe this is a fully general transformation

What if even? referred to itself as well as to odd?

-- Bruce

Bruce G. Stewart

unread,
Feb 22, 2001, 11:12:13 PM2/22/01
to

Joe Marshall wrote:

> I've never liked the implicit assignment in letrec. If it has been
> shown that any purely functional implementation of letrec could mimic
> side-effects given the appropriate interaction with
> call-with-current-continuation (i.e., the implicit assignment in
> letrec is unavoidable), I'd be happier about it.

This is analogous to saying "I don't like the implicit goto in a
do-while loop." It's avoidable, if you're willing to make the program
big enough, (unbounded in size, in fact.)

Aloha Petrofsky

unread,
Feb 23, 2001, 3:13:53 AM2/23/01
to
Joe Marshall <j...@content-integrity.com> writes:
> There is an interesting quirk about the RnRS definition of letrec. It
> seems that with the appropriate call-with-current-continuation magic
> you can expose the implicit SET!s that occur between when a value is
> computed and when it is assigned to the letrec variable.
>
> I haven't spent much time considering it, but I wonder if one of these
> `fixed-point' versions of letrec would behave in the same way.

No. The assignment-exploiting code relies on the evaluation of a
letrec init expression returning multiple times. The functional
letrec implementations of Oleg and Hilsdale assumed that all init
expressions were lambdas, which can only return once. The general
transformation I suggested -- enclosing each init in a zero-arg lambda
and wrapping each variable reference in a pair of parentheses --
breaks if an init expression evaluation returns multiple times. This
is not much of a limitation, because in a pure functional program it
doesn't make sense for a continuation to be used twice: that always
represents an infinite loop, and what's the point of an infinite loop
if there are no side effects? (If there is no mutation, then the
"entire future" for the second time through a continuation must be
identical to what it was the first time, so it will inevitably lead to
a third time...)

In another article you wrote:
> Jonathan [Rees] and Alan [Bawden] came up with an implementation of cells


>
> (make-cell initial-value)
> (cell-value cell)
> (set-cell-value! cell new-value)

I've made the necessary tweaks to Oleg's code to provide that
interface:

(define (make-cell init)
(letrec
((state
(call-with-current-continuation
(lambda (letrec-initializer-return)
(let new-state ((val init) (set!-return #f))
(list val
set!-return
(lambda (new-val new-set!-return)
(letrec-initializer-return
(new-state new-val new-set!-return)))))))))
(if (cadr state)
((cadr state) (car state))
(lambda (message)
(case message
((get) (car state))
((set!) (lambda (new-val)
(call-with-current-continuation
(lambda (set!-return)
((caddr state) new-val set!-return))))))))))

(define (cell-value cell)
(cell 'get))

(define (set-cell-value! cell new-val)
((cell 'set!) new-val))


-al

Albuquerke Petrofsky

unread,
Feb 23, 2001, 2:10:02 PM2/23/01
to
As my brain cleared in the shower this morning, I realized that I had
made make-cell more complicated than necessary. Here's a simpler
version:

(define (make-cell init)
;; state is a list of three elements:
;; 1. The current value of the cell.
;; 2. The continuation of the last call to set!.
;; 3. The continuation of state's initializer. This is the
;; continuation that sets state to the value passed to it and then
;; executes the body of the letrec.
(letrec
((state (call/cc (lambda (c) (list init #f c)))))
(define (get-val) (car state))
(define (get-set!-cont) (cadr state))
(define (get-init-cont) (caddr state))
(if (get-set!-cont)
((get-set!-cont) (get-val))
(lambda (message)
(case message
((get) (get-val))
((set!) (lambda (new-val)
(call/cc
(lambda (c)
((get-init-cont)
(list new-val c (get-init-cont))))))))))))

Joe Marshall

unread,
Feb 23, 2001, 4:32:20 PM2/23/01
to

I think you misunderstand me.

R5RS explicitly states that variables in letrec are assigned to. Now
it is the case that internal definitions could be handled in a purely
functional manner by finding a fixed-point. But it *might* be the
case that an implementation that did so would detectably differ from
one that did assignments.

If letrec implemented by finding a fixed-point is *different* from
letrec implemented via assignment, then I think the language has taken
the wrong choice of introducing an assignment where none is logically
necessary.

However, if letrec implemented by finding a fixed-point is *identical*
to letrec implemented via assignment, then I can consider the
assignment implementation to simply be a more tractable expression of
what is going on.

Incidentally, I don't mind gotos. After all, if function calls are
gotos that pass arguments, then gotos are function calls that don't.

I also don't mind programs that are unbounded in size, provided I
don't have to execute the entire thing.

Joe Marshall

unread,
Feb 23, 2001, 4:35:54 PM2/23/01
to
Aloha Petrofsky <Al...@Petrofsky.Berkeley.CA.US> writes:

> Joe Marshall <j...@content-integrity.com> writes:
> > There is an interesting quirk about the RnRS definition of letrec. It
> > seems that with the appropriate call-with-current-continuation magic
> > you can expose the implicit SET!s that occur between when a value is
> > computed and when it is assigned to the letrec variable.
> >
> > I haven't spent much time considering it, but I wonder if one of these
> > `fixed-point' versions of letrec would behave in the same way.
>
> No. The assignment-exploiting code relies on the evaluation of a
> letrec init expression returning multiple times. The functional
> letrec implementations of Oleg and Hilsdale assumed that all init
> expressions were lambdas, which can only return once. The general
> transformation I suggested -- enclosing each init in a zero-arg lambda
> and wrapping each variable reference in a pair of parentheses --
> breaks if an init expression evaluation returns multiple times. This
> is not much of a limitation, because in a pure functional program it
> doesn't make sense for a continuation to be used twice: that always
> represents an infinite loop, and what's the point of an infinite loop
> if there are no side effects? (If there is no mutation, then the
> "entire future" for the second time through a continuation must be
> identical to what it was the first time, so it will inevitably lead to
> a third time...)

That is only true if you invoke the continuation with the same value
each time. If you invoke the continuation with *different* values,
then you can avoid the loop.

Matthias Blume

unread,
Feb 23, 2001, 5:12:55 PM2/23/01
to
Joe Marshall wrote:
>
> "Bruce G. Stewart" <Bruce....@Verizon.net> writes:
>
> > Joe Marshall wrote:
> >
> > > I've never liked the implicit assignment in letrec. If it has been
> > > shown that any purely functional implementation of letrec could mimic
> > > side-effects given the appropriate interaction with
> > > call-with-current-continuation (i.e., the implicit assignment in
> > > letrec is unavoidable), I'd be happier about it.
> >
> > This is analogous to saying "I don't like the implicit goto in a
> > do-while loop." It's avoidable, if you're willing to make the program
> > big enough, (unbounded in size, in fact.)
>
> I think you misunderstand me.
>
> R5RS explicitly states that variables in letrec are assigned to.

I have not looked at R5RS in a long time, but if it really is the case
that it explicitly says so, then I hope that this was not the _intention_
of the authors!

I can see no utility in _requiring_ assignment semantics for letrec. My guess
is that giving the rewrite rule using assignment was just the simplest way of
explaining the (gist of the) intended meaning of letrec -- ignoring those nasty
corners of that meaning that could be explored using call/cc.

> If letrec implemented by finding a fixed-point is *different* from
> letrec implemented via assignment, then I think the language has taken
> the wrong choice of introducing an assignment where none is logically
> necessary.

Right. And, as I said, I think that doing so was not actually intended by the
authors. (Authors: Correct me if I am wrong.)

> Incidentally, I don't mind gotos. After all, if function calls are
> gotos that pass arguments, then gotos are function calls that don't.

Incidentally, I hope you see the flaw in your logic here.
(Just because an elephant is an animal that is big does not mean that
an animal is an elephant that is small.)

> I also don't mind programs that are unbounded in size, provided I
> don't have to execute the entire thing.

If you don't have to execute the whole thing, then it isn't unbounded
in size.

Regards,
Matthias

Joe Marshall

unread,
Feb 23, 2001, 5:49:46 PM2/23/01
to
Matthias Blume <bl...@research.bell-labs.com> writes:

> I have not looked at R5RS in a long time, but if it really is the case
> that it explicitly says so, then I hope that this was not the _intention_
> of the authors!

Section 4.2.2 explains the semantics of letrec thus:

The <variable>s are bound to fresh locations holding undefined
values, the <init>s are evaluated in the resulting environment (in
some unspecified order), each <variable> is assigned to the result
of the corresponding <init>, the <body> is evaluated in the
resulting environment...

> I can see no utility in _requiring_ assignment semantics for letrec. My guess
> is that giving the rewrite rule using assignment was just the simplest way of
> explaining the (gist of the) intended meaning of letrec -- ignoring those nasty
> corners of that meaning that could be explored using call/cc.

I hope this is the case.

> > Incidentally, I don't mind gotos. After all, if function calls are
> > gotos that pass arguments, then gotos are function calls that don't.
>
> Incidentally, I hope you see the flaw in your logic here.
> (Just because an elephant is an animal that is big does not mean that
> an animal is an elephant that is small.)

Yes. The gotos that litter languages such as C or Basic are quite
different from the tail calls in Scheme.

> > I also don't mind programs that are unbounded in size, provided I
> > don't have to execute the entire thing.
>
> If you don't have to execute the whole thing, then it isn't unbounded
> in size.

Not necessarily. If I don't specify how much I intend to execute
beforehand, then I could exceed any arbitrary bound. If I never
execute the whole thing, then it finite in size, but not necessarily
bounded.

Dorai Sitaram

unread,
Feb 23, 2001, 6:26:11 PM2/23/01
to
In article <ae7dqe...@content-integrity.com>,

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

Joe Marshall

unread,
Feb 23, 2001, 8:29:01 PM2/23/01
to
ds...@goldshoe.gte.com (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.

Not necessarily. The compiler would be allowed to fold the instances.

For instance, if I do this in MIT Scheme:

(define-integrable (Y f)
((lambda (d) (d d))
(lambda (x) (f (lambda () (x x))))))

(define *keep-track* '())

(define (test x)
(let ((fact (y (lambda (fact)
(lambda (x)
(set! *keep-track* (cons (fact) *keep-track*))
(if (zero? x)
1
(* x ((fact) (- x 1)))))))))
(fact x)))

(test 8)

(eq? (car *keep-track*) (cadr *keep-track*)) => #t

> 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.

Not necessarily.

Bruce G. Stewart

unread,
Feb 23, 2001, 9:35:34 PM2/23/01
to

Dorai Sitaram wrote:

> 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.

I realize that this may seem like hair-splitting, but here goes.

Is it not the case that the result under the Y model could be either #t
or #f? ((car *keep-track*) x) and ((cadr *keep-track*) x) yield
identical results for all x, so they are possibly indistinguishable.

The real difference is that the method specified by R5RS dictates a
(partial) order of evaluation that precludes reference to bound values
while computing bound values. A pure-functional Y removes this
restriction, at the cost of requiring "normal-order" evaluation.

ol...@pobox.com

unread,
Feb 23, 2001, 9:58:23 PM2/23/01
to

Dorai Sitaram wrote:
> 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.

This test is not dependable as it relies on eq? of procedures. R5RS
says, that "Eq? and eqv? are guaranteed to have the same behavior on
... procedures ..." R5RS does not completely specify behavior of eqv?
on procedures. R5RS only requires that (eqv? obj1 obj2) return #f if
"obj1 and obj2 are procedures that would behave differently (return
different value(s) or have different side effects) for some
arguments." It appears that (car *keep-track*) (cadr *keep-track*) are
both stateless procedures that behave the same way (to be more
precise, the proof of this statement never terminates: to see if these
procedures are "the same" we must determine if the effect of the
internal set! is the same, which leads to the original question). The
result of comparing these procedures with eqv? is therefore
unspecified and cannot be relied upon.

If mutations are permitted, a definite test can be designed that tells
between the functional and conventional implementations of letrec. For
example,

(letrec
((fact
(cons #f
(lambda (n)
(set-car! fact #t)
(if (zero? n) 1
(* n ((cdr fact) (- n 1))))))))
(let* ((before (car fact))
(res ((cdr fact) 5)))
(list before res (car fact))))
==> (#f 120 #t)

However,

(letrec^^
((fact
(cons #f
(lambda (n)
(set-car! (force fact) #t)
(if (zero? n) 1
(* n ((cdr (force fact)) (- n 1))))))))
(let* ((before (car fact))
(res ((cdr fact) 5)))
(list before res (car fact))))

==> (#f 120 #f)

Can we tell the difference between the letrecs if mutations are not
allowed and if the equivalence of procedures is considered unreliable?
The answer for the functional letrec implementations given so far is
yes. set-cell-value! would NOT work if you replace letrec with
letrec^ or letrec^^. We can reply in affirmative to Joe Marshall's
question:

> If letrec implemented by finding a fixed-point is *different* from
> letrec implemented via assignment, then I think the language has taken
> the wrong choice of introducing an assignment where none is logically
> necessary.

Yes, so far. Scheme's letrec cannot be emulated in a call-by-value
lambda-calculus. Furthermore, it seems that I can show that Scheme's
letrec cannot be emulated in a call-by-value lambda calculus with
call/cc.

Juliusz Chroboczek

unread,
Feb 24, 2001, 11:56:37 AM2/24/01
to
Bruce Hoult <br...@hoult.org>:

>> I believe this is a fully general transformation

BH> What if even? referred to itself as well as to odd?

You're right of course. The first let that you introduce needs to be
a letrec. In the even/odd example, it then gets converted into a let
by a generic source-level optimisation.

Recall that the only goal of the exercice was only to quickly
implement general letrec in a compiler that already had support for
single-value letrec. Lazy pattern matching eventually provided a more
elegant and more efficient solution.

Regards,

Juliusz

Dorai Sitaram

unread,
Feb 25, 2001, 4:10:18 PM2/25/01
to
In article <bsrsq3...@content-integrity.com>,

Is there a special way to load these definitions into
MIT Scheme to get the #t result? I'm getting ()
(which is equivalent to #f) on version 7.5.12 of MIT
Scheme on Red Hat Linux 7.

--d

Jeffrey Siegal

unread,
Feb 25, 2001, 9:42:41 PM2/25/01
to
Dorai Sitaram wrote:
> Is there a special way to load these definitions into
> MIT Scheme to get the #t result? I'm getting ()
> (which is equivalent to #f) on version 7.5.12 of MIT
> Scheme on Red Hat Linux 7.

Just guessing but maybe you have to use the compiler.

Joe Marshall

unread,
Feb 26, 2001, 11:28:16 AM2/26/01
to
ds...@goldshoe.gte.com (Dorai Sitaram) writes:

> Is there a special way to load these definitions into
> MIT Scheme to get the #t result? I'm getting ()
> (which is equivalent to #f) on version 7.5.12 of MIT
> Scheme on Red Hat Linux 7.

I tried to post over the weekend, but I don't see it. Apologies if
this shows up twice.

Here is the code I used:

(declare (usual-integrations))

(define-integrable (Y f)
((lambda (d) (d d))
(lambda (x) (f (lambda () (x x))))))

(define *bar* '())

(define (test x)
(let ((fact (y (lambda (fact)
(lambda (x)

(set! *bar* (cons (fact) *bar*))


(if (zero? x)
1
(* x ((fact) (- x 1)))))))))
(fact x)))

Make sure you have an image with the compiler in it (the interpreter
is not clever enough to figure this out), and do (cf "filename")
Then load the resulting file.

Joe Marshall

unread,
Feb 26, 2001, 11:36:31 AM2/26/01
to
ol...@pobox.com writes:

> We can reply in affirmative to Joe Marshall's question:
>
> > If letrec implemented by finding a fixed-point is *different* from
> > letrec implemented via assignment, then I think the language has taken
> > the wrong choice of introducing an assignment where none is logically
> > necessary.
>
> Yes, so far. Scheme's letrec cannot be emulated in a call-by-value
> lambda-calculus. Furthermore, it seems that I can show that Scheme's
> letrec cannot be emulated in a call-by-value lambda calculus with
> call/cc.

And of course I now find a flaw in my argument. The R5RS spec
mentions the idea of `locations' being associated with procedures.
This is so you can use EQ? in a `reasonable' manner on procedures.
(And as Dorai Sitaram pointed out, it is in this equivalence of
procedures that we find the difference.)

I remember that there was a debate over whether (and how) EQ? should
work on procedures, and I think I'm in the camp that likes to test
EQ?ness on procedures.

So now I seem to be left with the distasteful choice of wanting letrec
to be `pure' (more specifically, I'd rather the spec not require it to
be impure) *or* wanting to be able to use `eq?' on procedures.

Abc Def

unread,
Feb 26, 2001, 12:42:46 PM2/26/01
to
Thank you one and all for the responses. I'll reply as I can.

erik hilsdale (ehil...@cs.indiana.edu) wrote:
> (let ((even? (lambda (even? odd? x)
> (let ((even? (lambda (x) (even? even? odd? x)))
> (odd? (lambda (x) (odd? even? odd? x))))


> (if (zero? x) #t (odd? (- x 1))))))

> (odd? (lambda (even? odd? x)
> (let ((even? (lambda (x) (even? even? odd? x)))
> (odd? (lambda (x) (odd? even? odd? x))))
> (if (zero? x) #f (even? (- x 1)))))))
> (let ((even? (lambda (x) (even? even? odd? x)))
> (odd? (lambda (x) (odd? even? odd? x))))
> (odd? 42)))

This is what I was using. I posted because a nice optimizer like Stalin
wasn't
proving that all the e and o were the same, which led me to believe that
there
were better ways.

Eli Barzilay (e...@barzilay.org) wrote:
> (define Y
> (lambda (f)
> ((lambda (x) (f (lambda (y) ((x x) y))))
> (lambda (x) (f (lambda (y) ((x x) y)))))))
> (define (pair x y) (lambda (s) (s x y)))
> (define (1st p) (p (lambda (x y) x)))
> (define (2nd p) (p (lambda (x y) y)))
> (define even/odd?
> (Y (lambda (s)
> (pair (lambda (n) (if (zero? n) #t ((2nd s) (sub1 n))))
> (lambda (n) (if (zero? n) #f ((1st s) (sub1 n))))))))
> (define even? (1st even/odd?))
> (define odd? (2nd even/odd?))

Y is pretty damn cool! I feel like a kid with a new toy. Using the
functional
records is annoying, so I'll play around with y a bit.

(define y (lambda (f)
((lambda (x) (f (lambda (y) ((x x) y))))
(lambda (x) (f (lambda (y) ((x x) y)))))))

(define s (y (lambda (s) ;; summation
(lambda (n)
(if (= n 0)
0
(+ n (s (- n 1))))))))

(s 10)

55

I'm renaming a few of those variables in y. These seem more sensible to me.

(define y (lambda (f)
((lambda (yf) (f (lambda (x) ((yf yf) x))))
(lambda (yf) (f (lambda (x) ((yf yf) x)))))))

A little factoring...

(define y (lambda (f)
(let ((yf (lambda (yf) (f (lambda (x) ((yf yf) x))))))
(yf yf))))

For a tail-recursive version of summation, I want multiple arguments. I'll
use
a rest parameter and apply instead of fixed parameters and call.

(define y (lambda (f)
(let ((yf (lambda (yf) (f (lambda x (apply (yf yf) x))))))
(yf yf))))

(define s (y (lambda (s)
(lambda (n sum)
(if (= n 0)
sum
(s (- n 1) (+ sum n)))))))

(s 10 0)

55

I'd like to use this for making definitions for a body, so I'll pass the
result
to a continuation function. I'll put k first in anticipation of many
functions.

(define y (lambda (k f)
(let ((yf (lambda (yf) (f (lambda x (apply (yf yf) x))))))
(k (yf yf)))))

(y (lambda (s)
(s 10 0))
(lambda (s)
(lambda (n sum)
(if (= n 0)
sum
(s (- n 1) (+ sum n))))))

55

I'll work it out for two and see what it looks like. After some toil...

(define y (lambda (k f g)
(let ((yf (lambda (yf yg) (f (lambda x (apply (yf yf yg) x))
(lambda x (apply (yg yf yg)
x)))))
(yg (lambda (yf yg) (g (lambda x (apply (yf yf yg) x))
(lambda x (apply (yg yf yg)
x))))))
(k (yf yf yg) (yg yf yg)))))

(y (lambda (s1 s2)
(list (s1 10) (s2 10 0)))
(lambda (s1 s2)
(lambda (n)
(if (= n 0)
0
(+ n (s1 (- n 1))))))
(lambda (s1 s2)
(lambda (n sum)
(if (= n 0)
sum
(s2 (- n 1) (+ sum n))))))

(55 55)

There an obvious pattern which can be factored out.

(define y (lambda (k f g)
(let ((kk (lambda (k yf yg)
(k (lambda x (apply (yf yf yg) x))
(lambda x (apply (yg yf yg) x))))))
(let ((yf (lambda (yf yg) (kk f yf yg)))
(yg (lambda (yf yg) (kk g yf yg))))
(kk k yf yg)))))

Expand the lets, let's see what this really looks like.

(define y (lambda (k f g)
((lambda (kk)
((lambda (yf yg) (kk k yf yg))
(lambda (yf yg) (kk f yf yg))
(lambda (yf yg) (kk g yf yg))))
(lambda (k yf yg)
(k (lambda x (apply (yf yf yg) x))
(lambda x (apply (yg yf yg) x)))))))

This looks like a fine type of form for macro to generate, as below.
(Sorry,
I
don't have time to fatoots with syntax-rules just now.) The apply
evaporates
in favor of knowledge of the parameters.

;;;; (y* ((name1 lambda1) ...) . body)
;;
;; Y the definitions together for body.

(defmacro y* (cs . b)

;; c/lause n/ame a/alias p/arameter-section b/ody v/alue
(let loop ((cs cs) (ns '()) (as '()) (ps '()) (bs '()))

(if (not (null? cs))

(apply* (n v) ((car cs))
(apply* (syntactor p . b) (v)
(or (eq? syntactor 'lambda) (error "No soap -- radio!"))
(loop (cdr cs) (cons n ns) (cons (gentemp) as) (cons p ps)
(cons
b bs))))

(let ((kk (gentemp)))
`((lambda (,kk)
((lambda ,as (,kk (lambda ,ns . ,b) . ,as))
. ,(map* (p b) (ps bs)
`(lambda ,as (,kk (lambda ,ns (lambda ,p . ,b)) .
,as)))))
(lambda (k . ,as)
(k . ,(map* (p a) (ps as)
`(lambda ,p ((,a . ,as) . ,p))))))))))

A couple little ditties that the macro uses:

;;;; (apply* parameters arguments . body)
;;
;; (apply* (a b . c) (1 '(2 3 4 5))
;; (vector a b c))
;;
;; #(1 2 (3 4 5))

(defmacro apply* (parameters arguments . body)
`(apply (lambda ,parameters . ,body) . ,arguments))

;;;; (map* parameters values . body)
;;
;; (map* (a b c) ('(1 2) '(3 4) '(5 6))
;; (+ a b c))
;;
;; (9 12)

(defmacro map* (parameters values . body)
`(map (lambda ,parameters . ,body) . ,values))

This input generated something like that code which evaluated to those
values.

(y* ((e (lambda (n) (if (zero? n) #t (o (- n 1)))))
(o (lambda (n) (if (zero? n) #f (e (- n 1)))))
(s (lambda (n sum) (if (zero? n) sum (s (- n 1) (+ sum n))))))
(list (e 21) (s 10 0)))

((lambda (kk$)
((lambda (s$ o$ e$)
(kk$ (lambda (s o e)
(list (e 21) (s 10 0))) s$ o$ e$))
(lambda (s$ o$ e$)
(kk$ (lambda (s o e)
(lambda (n sum)
(if (zero? n) sum (s (- n 1) (+ sum n))))) s$ o$ e$))
(lambda (s$ o$ e$)
(kk$ (lambda (s o e)
(lambda (n)
(if (zero? n) #f (e (- n 1))))) s$ o$ e$))
(lambda (s$ o$ e$)
(kk$ (lambda (s o e)
(lambda (n)
(if (zero? n) #t (o (- n 1))))) s$ o$ e$))))
(lambda (k s$ o$ e$)
(k (lambda (n sum) ((s$ s$ o$ e$) n sum))
(lambda (n) ((o$ s$ o$ e$) n))
(lambda (n) ((e$ s$ o$ e$) n)))))

(#f 55)

Returning to generalizing y, I left off with:

(define y (lambda (k f g)
((lambda (kk)
((lambda (yf yg) (kk k yf yg))
(lambda (yf yg) (kk f yf yg))
(lambda (yf yg) (kk g yf yg))))
(lambda (k yf yg)
(k (lambda x (apply (yf yf yg) x))
(lambda x (apply (yg yf yg) x)))))))

I see that kk can be expressed in arbitrary terms without mucking with the
rest, so I'll do kk and test. Rests, maps, and applies, oh my.

(define y (lambda (k f g)
((lambda (kk)
((lambda (yf yg) (kk k yf yg))
(lambda (yf yg) (kk f yf yg))
(lambda (yf yg) (kk g yf yg))))
(lambda (k . yfyg)
(apply k (map (lambda (yq)
(lambda x (apply (apply yq yfyg) x)))
yfyg))))))

The same for y's parameters and body:

(define y (lambda (k . fg)
((lambda (kk)
(apply (lambda yqs
(apply kk k yqs))
(map (lambda (q)
(lambda yqs (apply kk q yqs)))
fg)))
(lambda (k . yqs)
(apply k (map (lambda (yq)
(lambda x (apply (apply yq yqs) x)))
yqs))))))

The y above appears to work, and I don't know what else to do to it. Sample
test code follows.

(y (lambda (s1 s2 qqq)
(list (s1 10) (s2 10 0) (qqq)))
(lambda (s1 s2 qqq)
(lambda (n)
(if (= n 0)
0
(+ n (s1 (- n 1))))))
(lambda (s1 s2 qqq)
(lambda (n sum)
(if (= n 0)
sum
(s2 (- n 1) (+ sum n)))))
(lambda (s1 s2 qqq)
(lambda ()
-69)))

(55 55 -69)

Did I blow anything?

Stalin still isn't catching the ydentities -- each function is seeing
distcint
s1, s2, and qqq. But I'm not going to dive into that this second.

Still, though, Y is pretty damned neat.

v q r c
More to come, [Ag] Andy Gaynor s l e @ u d i . o
i r a x m

I haven't posted in a while.
I can't believe how much spam I got last time!
I'm surprised that this antisocial activity,
easily provable as such, is so well tolerated.
Which complaint agency do we prefer again? Thanks.

Joe Marshall

unread,
Feb 26, 2001, 6:40:52 PM2/26/01
to
Abc Def <stupid_em...@MailAndNews.com> writes:

> I haven't posted in a while.
> I can't believe how much spam I got last time!
> I'm surprised that this antisocial activity,
> easily provable as such, is so well tolerated.

Who says it is tolerated?

> Which complaint agency do we prefer again ?

The one in charge.

ol...@pobox.com

unread,
Feb 28, 2001, 10:00:43 PM2/28/01
to

This article attempts to show why call/cc by itself is insufficient to
emulate set! in a call-by-value lambda-calculus. The latter is
well-represented by a pure functional subset of Scheme without
letrec. We will rely on a denotational semantics of call/cc and of the
pure functional subset of Scheme under consideration. We will use
Scheme itself to represent and reason about its own denotational
semantics.

We will conclude by proposing a new continuation-capture primitive,
which lets us represent mutations of bindings in a pure functional
way, without the the concept of a store.

Let's first consider a general model of code with a mutation, which
includes: (A) initialization of a mutable cell, (B) code that uses the
value of the cell, (C) mutation (D) more code that uses the (changed)
value of the cell. We can write this sequence as A B C D. For example,

(let ((i 0))
(cons i
(begin
(set! i (+ i 1))
(cons i '()))))

(let ((i 0)) ...) is point A, the first cons is point B, set! is
obviously at point C, and the second cons is at point D. Without loss
of generality, we assume that no bindings are created at point B.

The previous fragment explicitly mentioned set!, which we forbid in
our subset of Scheme. We will try to emulate this set! however, by
jumping from point C back to point A (where the binding was
initialized) and initialize the binding with a new value. We can
always perform such a jump if we noted the continuation of the
initialization expression at point A. If we let the code continue
after the jump, the control will come to B. But we don't want B to
evaluate again. We want to skip B and wind back to D: only D should be
executed with the new value of the binding, not B. To do such a skip,
we need to remember the continuation at point C, and insert a fixup
code between A and B to jump to such a continuation. Here's the rub:
the continuation at point C captures the environment which existed at
this point. When we jump to this continuation, the corresponding
environment is restored.

Let's consider the sequence A B C D formally, as
(call-with-values
(lambda () (values (void) E))
(compose-values A B C D))

where A, B, C and D are functions that take two values and return two
values. The first of these values is the result yielded by a previous
function, and the second one is the environment. compose-values is a
multiple-value composition combinator, defined as follows

(define (compose-values . functions)
(cond
((null? functions)
(lambda args (apply values args)))
((null? (cdr functions))
(car functions))
(else
(lambda args
(call-with-values
(lambda () (apply (car functions) args))
(apply compose-values (cdr functions)))))))

We will re-write our example to match this form as

(let ((i 0)) ; A
(call-with-values (lambda () (values #f))
(compose-values
(lambda (dummy) (let ((i i)) (lambda (rest) (cons i rest)))) ; B
(lambda (res-B)
(set! i (+ i 1)) ; C
res-B)
(lambda (res) ; D
(res (cons i '()))))))

or, by introducing an environment
(define (make-env) '())
(define (extend-env env symbol value) (cons (cons symbol value) env))
(define (lookup-env env symbol)
(cond ((assq symbol env) => cdr)
(else (error "Unbound: " symbol))))
(define (mutate-env! env symbol new-value)
(cond ((assq symbol env) =>
(lambda (binding) (set-cdr! binding new-value)))
(else (error "Unbound: " symbol))))

(call-with-values
(lambda () (values (void) (make-env)))
(compose-values
(lambda (dummy env) ; A
(values (void) (extend-env env 'i 0)))
(lambda (dummy env) ; B
(values (let ((i (lookup-env env 'i)))
(lambda (res) (cons i res)))
env))
(lambda (res env) ; C
(mutate-env! env 'i 1)
(values res env))
(lambda (res env) ; D
(values (res (cons (lookup-env env 'i) '()))
env))))

But, of course we want do get by without mutate-env!.

As we agreed, point A creates a binding: it initializes a mutable cell
we want to emulate. Point A evaluates an initialization expression and
_creates a new environment_. We can express the semantics of point A
in more detail as

(define (A dummy-val E)
(values (void) (extend-env E 'i init0))

where function (void) returns #f or some other "unspecified" value,
and extend-env is a function that takes the environment, a new symbol,
and its value, and extends the environment with the new binding. We
also remember a continuation at point of evaluating the initialization
expression of A:

(define (cont-A hole an-env)
(call-with-values
(lambda () (values (void) (extend-env E 'i hole)))
(compose-values B C D)))

where E is bound to the environment at the beginning of the sequence.

The semantics of a code fragment A B will be then:
(compose-values A B)
==>
(lambda (dummy E)
(call-with-values
(lambda () (values (void) (extend-env E 'i init0)))
(lambda (dummy E1)
(values (compute-B dummy E1) E1))))

Note, in a pure functional language, bindings are immutable. Since B
does not create its own bindings by our assumption, the environment at
the beginning of B is the environment at the end of B. compute-B is
a function that computes the result of B. In our example,

(define (compute-B dummy env)
(let ((i (lookup-env env 'i)))
(lambda (res) (cons i res))))

We now reach point C. First thing off, we remember its
continuation. But what is the continuation of C? The set! statement
does not create new bindings. Barring mutations, which we want to
emulate rather than to perform, the environment at the beginning of C
is the same as that at the end of C:

(define (cont-C hole an-env)
(call-with-values
(lambda () (values hole (extend-env E 'i init0)))
D))

where hole determines the place where the value passed to the
continuation will be plugged in.

At point C we invoke the continuation remembered at point A. Thus
fragment A will be re-executed and return
(values (void) (extend-env E 'i init1))
If we let the code run, B will be re-executed and return the value
(values
(compute-B (void) (extend-env E 'i init1))
(extend-env E 'i init1))

But we don't want B to be re-executed, we want to skip it. Our fixup
code, which we implicitly inserted before B, will apply cont-C to the
value when cont-C was taken -- (compute-B (void) (extend-env E 'i
init0)) -- and the effective environment at the fixup point:
(extend-env E 'i init1). Keeping in mind the definition of cont-C,
we find out the semantics (i.e., the result) of the continuation to be

(call-with-values
(lambda () (values
(compute-B (void) (extend-env E 'i init0))
(extend-env E 'i init0)))
D)

This is the same result as if C was an identity function. We see that
after the jump to the continuation of C, 'i is bound to init0 -- the
old, unchanged value. The mutation trick didn't work: the binding of
'i to init1 has disappeared. The reason for that is the semantics of
call/cc and of creation of a continuation. As cont-C makes it clear,
a continuation remembers the environment it was created in. When the
continuation is applied, it disregards its environment at the point of
invocation and restores the environment remembered at the point of
capture.

How then has Scheme's letrec allowed our trick to work? We have
to consider the semantics of (letrec ((i init)) rest), which is

(define (letrec-sem dummy E)
(call-with-values
(lambda () (values (void) (extend-env E 'i (void))))
(compose-values
(lambda (dummy env) ; init does not affect the env
(values (compute-init dummy env) env))
(lambda (init-val env)
(values (void) (mutate-env! env 'i init-val)))
(lambda (dummy env)
(rest dummy env)))))

If point A was (letrec ((i 0)) ...), then the continuation of the
initialization expression will be

(define (cont-letrec-A hole an-env)
(call-with-values
(lambda () (values (void) (mutate-env! env 'i hole)))
rest))
where env is bound to the environment that existed when the
initialization expression was evaluated first.

Thus when cont-A was followed, it created a new environment -- a new
binding for 'i. When cont-letrec-A is followed, no new environment is
created. Instead, the existing binding is mutated. When cont-C is
later followed, it finds that 'i is now bound to a new value _in the
environment it remembered_.


As Amr Sabry kindly pointed out, Andrzej Filinski
(http://www.brics.dk/~andrzej) showed that it is possible to emulate
mutable cells using shift/reset -- which in turn can be implemented
with call/cc -- _and_ set!.


call/cc is often considered the least functional feature of Scheme
(pun intended). call/cc got a bad rap, not entirely undeservingly. Yet
as it turns out, call/cc is functional but letrec is imperative. Who
would've thought: LETREC: the Ultimate Imperative.

Of course there is always an option of cheating. Let us consider
a hypothetical function call-with-adjoining-binding-continuation (better
called call/abc). This function would leave a hole not only for a
value but for the environment as well.
call/abc PROC
where PROC is a procedure of one argument. This argument is a
procedure
(lambda (hole eff-env)
(call-with-values
(lambda () (values hole (adjoin-env capt-env eff-env)))
continuation))
where capt-env is the environment at the point call/abc was executed
(at the point of capture), 'continuation' is the meaning of the
computation after call/abc, and eff-env is the environment in effect
when the captured abc-continuation is evaluated.

With call/abc, set!, letrec, the outer define, fluid-let, etc. become
_library_ syntax. They are no longer fundamental primitives: they
all can be expressed in terms of call/abc. For example:

(set! i new-val)
can be represented as

(call/abc
(lambda (k)
(let ((i i))
(let ((i new-val))
(k (void))))))
The first let ((i i)) was to make sure a binding to i already exists.

(fluid-let ((i new-val)) rest)

can be implemented as
(let ((i i))
(call/abc
(lambda (k)
(let ((i new-val))
(k (void)))))
rest)

A notable feature of this definition is the lack of explicit saving or
restoration of the "fluid" value. We don't have to worry if the 'rest'
escapes by invoking a regular continuation captured before fluid-let
was entered. The old binding of 'i is restored automagically -- in
fact, it hasn't been changed. Since this implementation of fluid-let
mutates no binding, it may be beneficial in a multi-threaded
environment.

The outer define is especially simple:

(define i val)
becomes
(call/abc
(lambda (k)
(let ((i val)) (k (void)))))


We can use call/abc can to implement partially-opened closures. We can
also use call/abc to implement mutable cells -- not only mutable
bindings but "mutable values" so to speak. The latter point is obvious
as call/abc can implement set!, set! can implement letrec, and the
letter along with call/cc can emulate mutable cells in the way shown
previously in this thread.

call/abc does not do away with the lexical scoping. If
abc-continuations are not captured, the lexical scoping rules remain
in effect. A compiler can be sure that the the bindings in effect at
run-time at any point in a program are exactly the same bindings that
can be seen at compile time. call/abc complicates the matter -- just
as call/cc does. When call/cc is used, exited frames cannot simply be
popped off the stack. call/cc causes complications in the way
parameters are passed to functions and argument lists are formed. Some
people do live with those complications.

call/abc is a pure functional way to represent mutations.

At this point I have to stop and really read the report by Amr Sabry and
Daniel P. Friedman. I have a hunch they have already explained what
I've written in this article.


--
Posted from taurus.cs.nps.navy.mil [131.120.10.2]

0 new messages