no continuations

Ben Rudiak-Gould benrg at dark.darkweb.com
Tue Dec 30 10:38:33 EST 2003


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



More information about the Haskell mailing list