Re: [Haskell-cafe] Re: Delimited continuations: please comment

2009-02-13 Thread Cristiano Paris
On Fri, Feb 13, 2009 at 2:05 AM, Chung-chieh Shan
ccs...@post.harvard.edu wrote:
 ...
 It's not unheard of for the scheduler to react in different ways to the
 same system call -- I'm thinking of reading from a file, for example.

Sure, I went implementing something slitghtly different to double
check my understanding of delconts.

 You clearly understand the whole idea, and your code demonstrates it in
 a nice way.  Oleg and I have found this programming style particularly
 convenient when we need to
  - fork processes (i.e., backtrack in the monad),
  - run the same processes under different schedulers (e.g., a debugger),
  - nest the applications of schedulers (i.e., provide virtualization).

Thanks for your feedback.

Cristiano
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Delimited continuations: please comment

2009-02-12 Thread Chung-chieh Shan
Cristiano Paris cristiano.pa...@gmail.com wrote in article 
afc62ce20902120855i77acf725p1069aab21037a...@mail.gmail.com in 
gmane.comp.lang.haskell.cafe:
 In effect, this is a bit different from the syscall service routine
 described by Oleg, as the scheduler function reacts in different ways
 for subsequent calls (the first time feeds Hello!, the second one
 World!, in a nice monad style). Yet, I liked the separation between
 the scheduler and the job, which are two completely different values
 and which I tried to keep.

It's not unheard of for the scheduler to react in different ways to the
same system call -- I'm thinking of reading from a file, for example.

 As this is (almost) my first time using delconts, could you provide
 feedback, comments, opinions about my piece of code and the topic in
 general (convenience, performances, alternatives and so on)?

You clearly understand the whole idea, and your code demonstrates it in
a nice way.  Oleg and I have found this programming style particularly
convenient when we need to
 - fork processes (i.e., backtrack in the monad),
 - run the same processes under different schedulers (e.g., a debugger),
 - nest the applications of schedulers (i.e., provide virtualization).

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
Attending a mathematics lecture is like walking through a
thunderstorm at night. Most of the time you are lost, wet
and miserable but at rare intervals there is a flash of
lightening and the whole countryside is lit up. - Tom Koerner

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-12 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 I wrote:

 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-12 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-11 Thread oleg


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.


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-09 Thread dvanhorn
Ashley Yakeley wrote:
 In article [EMAIL PROTECTED],
  [EMAIL PROTECTED] 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
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: no continuations

2004-01-09 Thread Kevin S. Millikin
On Friday, January 09, 2004 2:48 AM, Ashley Yakeley 
[SMTP:[EMAIL PROTECTED] wrote:

 Do you have an example of use of Y for letrec where a program would
 violate R5RS?

Sure, take a look at my implementation of Ben Rudiak-Gould's 
implementation of Alan Bawden's implementation of boxes.

In 4.2.2 of R5RS, it says, re letrec:

Semantics: 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 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. Each binding of a variable has the entire 
`letrec' expression as its region, making it possible to define 
mutually recursive procedures.

The result of the corresponding init is *assigned to* each variable 
(anyone know why the wording is backward above?), and that is after the 
inits are evaluated, which is after the variables are bound.

There was a discussion on comp.lang.scheme a couple of years ago about 
this.

http://groups.google.com/groups?hl=enlr=ie=UTF-8oe=UTF-8th=fdcf3  
554852a3cadseekm=3AC66F16%40MailAndNews.com#link1
http://groups.google.com/groups?hl=enlr=ie=UTF-8oe=UTF-8th=a47e0  
3e456b2dc2aseekm=200102220358.TAA77339%40adric.cs.nps.navy.mil#link1
http://groups.google.com/groups?hl=enlr=ie=UTF-8oe=UTF-8th=58a68  
6525be78d16rnum=1

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-09 Thread oleg

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

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.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2004-01-09 Thread Ashley Yakeley
In article [EMAIL PROTECTED],
 [EMAIL PROTECTED] 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.co
 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: no continuations

2004-01-01 Thread Kevin S. Millikin
On Tuesday, December 30, 2003 5:04 PM, Kevin S. Millikin 
[SMTP:[EMAIL PROTECTED] 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.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: no continuations

2003-12-31 Thread Tomasz Zielonka
On Tue, Dec 30, 2003 at 10:31:57PM -0500, [EMAIL PROTECTED] wrote:
 G'day all.
 
 Quoting Tomasz Zielonka [EMAIL PROTECTED]:
 
  BTW, the factorial example on
http://www.haskell.org/hawiki/MonadicContinuationPassingStyle
  seems rather pointless to me, because it doesn't use any methods
  of MonadCont (like callCC).
 
 The only point of the factorial example is to show how much nicer it
 looks than the version in ContinuationPassingStyle.  Which is useless
 from the point of view of expressivity, but it does show how CPS and
 recursion can work together.
 
 There are reasons for using CPS as an implementation technique which
 have nothing to do with call/cc, though this example doesn't really
 show any of them.

OK. I think I may be getting it now. The point is that MonadCont takes
care of passing the continuation, so you don't have to do it by hand. Is
that right? 

 Cheers,
 Andrew Bromage

Best regards,
Happy New Year,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-31 Thread ajb
G'day all.

Quoting Tomasz Zielonka [EMAIL PROTECTED]:

 OK. I think I may be getting it now. The point is that MonadCont takes
 care of passing the continuation, so you don't have to do it by hand. Is
 that right?

Precisely.

 Happy New Year,

And to you and yours.

Cheers,
Andrew Bromage
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-30 Thread Lennart Augustsson
I'm not sure what your question means.  You can make your
own continuations, so in that sense Haskell has them.
But perhaps you're asking why Haskell lacks something like
call/cc in Scheme which allows you to grab the current
continuation?
This doesn't play very well with graph reduction (which most
Haskell implementations use), since with graph reduction you will
update application nodes with the result of the computation.
If you have call/cc available you can jump back in time and
have a function call return something different, which would
contradict the cached result from the previous call.
It's not an insurmountable problem, but it's pretty hairy.
	-- Lennart

Scott wrote:
Why does Haskell have no continuations?  
(http://www.haskell.org/hawiki/CoMonad)
If continuations are incompatible with non-strict semantics, I'd 
appreciate an explanation.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-30 Thread Tomasz Zielonka
On Tue, Dec 30, 2003 at 07:21:08AM -0600, Scott wrote:
 Why does Haskell have no continuations?  
 (http://www.haskell.org/hawiki/CoMonad)

See http://www.haskell.org/hawiki/MonadCont

BTW, the factorial example on
  http://www.haskell.org/hawiki/MonadicContinuationPassingStyle
seems rather pointless to me, because it doesn't use any methods
of MonadCont (like callCC).

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-30 Thread Ben Rudiak-Gould
On Tue, 30 Dec 2003, Scott wrote:
 Why does Haskell have no continuations?
 (http://www.haskell.org/hawiki/CoMonad)
 If continuations are incompatible with non-strict semantics, I'd 
 appreciate an explanation.

With letrec and unrestricted call/cc you can implement ML-style refs:

  (define (make-cell)   ; Alan Bawden, 1989
(call-with-current-continuation
  (lambda (return-from-make-cell)
(letrec ((state
   (call-with-current-continuation
 (lambda (return-new-state)
   (return-from-make-cell
 (lambda (op)
   (case op
 ((set)
  (lambda (value)
(call-with-current-continuation
  (lambda (return-from-access)
(return-new-state
  (list value return-from-access))
 ((get) (car state)
  ((cadr state) 'done)

Unrestricted call/cc seems to be incompatible with referential
transparency in a very fundamental way, and Haskell is nothing without
referential transparency. On the other hand, it doesn't cause any problems
when the evaluation order is fixed by some monad, whence MonadCont.

In practice, the cool things that call/cc makes possible (backtracking,
cooperative multitasking) can be achieved much more easily with custom
monads: e.g. the list monad

  instance Monad [] where
m = k   = concatMap k m
return x  = [x]
fail s= []

versus the amb form in Scheme, which provides essentially the same
functionality:

  (define amb-fail '())

  (define (initialize-amb-fail)
(set! amb-fail
  (lambda (x)
(error #f amb tree exhausted ;;for petite chez

  (define (fail) (amb))

  (define-syntax amb
(syntax-rules ()
  ((amb argument ...)
   (let ((old-amb-fail amb-fail))
 (call/cc (lambda (return)
(call/cc (lambda (next)
   (set! amb-fail next)
   (return argument)))...
(set! amb-fail old-amb-fail)
(amb-fail #f)))

  (initialize-amb-fail)


-- Ben

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: no continuations

2003-12-30 Thread Kevin S. Millikin
On Tuesday, December 30, 2003 12:39 PM, Ben Rudiak-Gould 
[SMTP:[EMAIL PROTECTED] wrote:

 With letrec and unrestricted call/cc you can implement ML-style refs:

With an *implementation of letrec that uses mutation* and unrestricted 
call/cc, you can implement ML-style ref cells:

Petite Chez Scheme Version 6.0a
Copyright (c) 1998 Cadence Research Systems

 (define-syntax letrec^
(syntax-rules ()
  ((_ ((Var Exp)) Body Bodies ...)
   (let ((Y (lambda (f)
  ((lambda (g) (f (g g)))
   (lambda (g) (f (lambda (x) ((g g) x
 (let ((Var (Y (lambda (Var) Exp
   Body Bodies ...)

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

 (define (make-cell)
(call/cc
 (lambda (return-from-make-cell)
   (letrec^ ((state
   (call/cc
 (lambda (return-new-state)
   (return-from-make-cell
 (lambda (op)
   (case op
 ((set)
  (lambda (value)
(call/cc
  (lambda (return-from-access)
(return-new-state
  (list value 
return-from-access))
 ((get) (car state)
 ((cadr state) 'done)

 (define c (make-cell))

 ((c 'set) 3)

 (c 'get)
3

 ((c 'set) 7)
done

 (c 'get)
3
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: no continuations

2003-12-30 Thread Ben Rudiak-Gould
On Tue, 30 Dec 2003, Kevin S. Millikin wrote:
 On Tuesday, December 30, 2003 12:39 PM, Ben Rudiak-Gould wrote:
  With letrec and unrestricted call/cc you can implement ML-style refs:
 
 With an *implementation of letrec that uses mutation* and unrestricted 
 call/cc, you can implement ML-style ref cells:

 [...]

  (define c (make-cell))
  ((c 'set) 3)
  (c 'get)
 3
  ((c 'set) 7)
 done
  (c 'get)
 3

Interesting.

This still violates referential transparency, though. (c 'get) returns a
value or errors out depending on whether (c 'set) has been called yet.
Here's a more obvious violation:

   (let* ((c (make-cell))
   (d (make-cell)))
   ((c 'set) 1)
   ((d 'set) 2)
   (d 'get))
  2
   (let* ((c (make-cell))
   (d c))
  ((c 'set) 1)
  ((d 'set) 2)
  (d 'get))
  1

And take a look at this!

   (define c (make-cell))
   (define d c)
   ((d 'set) 9)
   (d 'get)

  Error in car: #procedure is not a pair.
  Type (debug) to enter the debugger.

Something very nasty is going on here. I'm not sure exactly what it is,
but I think at least one of the define statements is getting executed at
least twice.

I still think there's a deep antagonism between unrestricted call/cc and
referential transparency, and changing letrec's semantics can't fix it.


-- Ben

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: no continuations

2003-12-30 Thread Kevin S. Millikin
On Tuesday, December 30, 2003 3:10 PM, Ben Rudiak-Gould 
[SMTP:[EMAIL PROTECTED] wrote:
 Interesting.

 This still violates referential transparency, though. (c 'get) 
returns
 a value or errors out depending on whether (c 'set) has been called 
yet.

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.

 And take a look at this!

(define c (make-cell))
(define d c)
((d 'set) 9)
(d 'get)

   Error in car: #procedure is not a pair.
   Type (debug) to enter the debugger.

 Something very nasty is going on here. I'm not sure exactly what it
 is, but I think at least one of the define statements is getting 
executed
 at least twice.

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

Does this help?:

 (define c
(let ((cell (make-cell)))
  (display Hi, Ben.)
  (newline)
  cell))
Hi, Ben.
 (define d c)
 ((d 'set) 9)
Hi, Ben.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-30 Thread Derek Elkins
On Tue, 30 Dec 2003 10:38:33 -0800 (PST)
Ben Rudiak-Gould [EMAIL PROTECTED] wrote:

 On Tue, 30 Dec 2003, Scott wrote:
  Why does Haskell have no continuations?
  (http://www.haskell.org/hawiki/CoMonad)
  If continuations are incompatible with non-strict semantics, I'd 
  appreciate an explanation.

 Unrestricted call/cc seems to be incompatible with referential
 transparency in a very fundamental way, and Haskell is nothing without
 referential transparency. On the other hand, it doesn't cause any
 problems when the evaluation order is fixed by some monad, whence
 MonadCont.

Indeed, the simplest example is probably implementing exceptions with
call/cc.

Assuming a callCC function what does the following return,
callCC (\k - k 1 + k 2)?

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-30 Thread Amr A Sabry
Kevin S. Millikin [EMAIL PROTECTED] 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.

That's right: call/cc alone can't express assignments. 

But shift + reset will give you assignments. See Gunter, Remy, and
Riecke, FPCA 95 for a clever encoding. 

--Amr
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: no continuations

2003-12-30 Thread ajb
G'day all.

Quoting Tomasz Zielonka [EMAIL PROTECTED]:

 BTW, the factorial example on
   http://www.haskell.org/hawiki/MonadicContinuationPassingStyle
 seems rather pointless to me, because it doesn't use any methods
 of MonadCont (like callCC).

The only point of the factorial example is to show how much nicer it
looks than the version in ContinuationPassingStyle.  Which is useless
from the point of view of expressivity, but it does show how CPS and
recursion can work together.

There are reasons for using CPS as an implementation technique which
have nothing to do with call/cc, though this example doesn't really
show any of them.

Cheers,
Andrew Bromage
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell