[Haskell-cafe] Problem with continuations and typing

2005-12-04 Thread tpledger
Jerzy Karczmarczuk wrote:
 :
 | zeros fc sc = sc 0 zeros
 |
 | fails to compile as well. *I do not ask why, I know*.
 |
 | But I would like to continue this exercice along these
lines, without too much
 | exotism (no monads, yet...), for my students. Do you have
any simple work-around?
 | Introduce some algebraic constructors? Perhaps
higher-rank polymorphism could do
 | something (but then I would have to explain it to my
folk...)
 :


How about this for a non-exotic algebraic type?

> newtype G a b = G{ unG :: b -> (a -> G a b -> b) -> b }
> glist g   = unG g [] (\b g' -> b : glist g')
> zeros = G (\no yes -> yes 0 zeros)
> disj  g1 g2   = G (\no yes -> unG g1 (unG g2 no yes)
>  (\b g1' -> yes b
(disj g1' g2)))

I haven't had much practice with continuations, so don't
know whether I've just lost some generality there.

But it does support *some* avoidance of higher-rank
polymorphism, through the use of good old partial
application.  For example, the type of the state variable s
doesn't leak into the result type of unfold:

> unfold f s= G (\no yes -> case f s of
>     Nothing  -> no
>     Just (s', b) -> yes b (unfold f
s'))

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


[Haskell-cafe] Problem with continuations and typing

2005-12-01 Thread oleg

Jerzy Karczmarczuk wrote:

> I tried to cook-up a simple version of nondeterministic computations
> using the two-continuation model. I got stuck on an 'infinite type'
> error, and my question is: have you seen a *concrete* (really
> concrete) Haskell implementation of a similar model, I could inspire
> myself on? (I know a few theoretical works on that).

Yes, of course: the code for the LogicT paper

http://pobox.com/~oleg/ftp/packages/LogicT.tar.gz

(please see SFKT.hs) and

  http://www.haskell.org/pipermail/haskell/2005-October/016577.html
  http://www.haskell.org/pipermail/haskell/2005-October/016696.html

As we can see, FR stream indeed takes success and the failure
continuations. This is emphasized at the beginning of the first
article.


> But I would like to continue this exercice along these lines, without
> too much exotism (no monads, yet...), for my students. Do you have any
> simple work-around Introduce some algebraic constructors? Perhaps
> higher-rank polymorphism could do something (but then I would have to
> explain it to my folk...)

You're correct on both counts. We can emulate equi-recursive types
with iso-recursive ones: e.g., plain Haskell list. Or, you may choose
to use higher-ranked type (the FR stream). There is a third solution:
use a small typing hole in Haskell to sneak in the real equi-recursive
type. I have a feeling though you might not wish to explain the latter
method to your students.

This present question is actually related to your previous inquiry
about expressing a predecessor in a simply-typed lambda-calculus. It
cannot be expressed. We need either a recursive or higher-ranked
type: predecessor is 'car'.

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


[Haskell-cafe] Problem with continuations and typing

2005-12-01 Thread Jerzy Karczmarczuk

I resend a posting which has been blocked by some daemon according to whom
I am not a memeber of this list (and which has not been cleared by Simon M.)
==


I tried to cook-up a simple version of nondeterministic computations using the
two-continuation model. I got stuck on an 'infinite type' error, and my question
is: have you seen a *concrete* (really concrete) Haskell implementation of a
similar model, I could inspire myself on? (I know a few theoretical works on
that).
(And for pedagogical reasons I wanted to work this until the end without ever
using the magic word "monad"... No >>= nor other similar abominations.)

A generator is something which takes two continuations
* Failure continuation, a parameter-less function, for example

failure () = error "No more solutions"

* Success continuation, a function which takes two parameters
   *  a value which it may return
   *  another generator which may return further values. (This is a particular
  version of the model. There are others).

A trivial success continuation returns the intercepted value.

accept x gen = x  -- (or:  accept = const)

The trivial generators are the one which fails, and one which returns just one
fixed value:

nogen fcnt scnt = fcnt ()
unit x fcnt scnt = scnt x nogen

Getting the next generator (skipping the first value) may be obtained with

next gen fc sc = gen fc (\_ nxt -> nxt fc sc)

Of course   next (unit x) =-=> nogen.

Alternative. Here I got stuck.
Now, try to define the  (disj gen1 gen2). This is a generator which launches 
gen1
and if it fails, it launches gen2. But if gen1 succeeds, the 'next' generator it
provides should also invoke gen2 in the case of failure, and this is recursive.
So:

disj gen1 gen2 fc sc =
  gen1 (\_ -> gen2 fc sc) (\x nxt -> sc x (disj nxt gen2))

Intuitively it is OK, (e.g. works in Scheme). But Haskell protests,
(disj nxt gen2) cannot be typed. I do not ask why, I see myself...

An attempt to collect all the generated instances in a list fails as well
for the same reason:

glist gen =
  gen (\_->[]) (\x nxt -> x : glist nxt)

Even simpler, a generator which never fails, and returns zeros

zeros fc sc = sc 0 zeros

fails to compile as well. *I do not ask why, I know*.

But I would like to continue this exercice along these lines, without too much
exotism (no monads, yet...), for my students. Do you have any simple 
work-around?
Introduce some algebraic constructors? Perhaps higher-rank polymorphism could do
something (but then I would have to explain it to my folk...)
I would hate this...

Gracias.

Jerzy Karczmarczuk


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