I was excited to see that 5.3.0 brought simplified syntax for deep effect handlers, as I hoped this would help ease the pain of implementing generators (coroutines) in OCaml user code. Unfortunately, I have not figured out a way to do this with deep effect handlers due to the fact that I can’t recurse/resume conditionally. Instead, I’ve only come up with some complicated hacks using shallow handlers and are not as general as I would like. The general goal is to produce something that can be used as an external iterator, but is implemented with “straight-line” recursive code on the generating side. I’m picturing an effect called Yield or similar which essentially behaves as yield in Python (both accepting a value and marking a cooperative yield point, as well as optionally returning a value from the effect handler).
Can anybody point me to work that has been done in this area? I’m interested on ergonomic solutions on both the producer and consumer side. Outside of effects, the cleanest solutions I’ve come up with so far for external iteration are all based on Seq.t or similar patterns, but this requires rewriting everything in explicit continuation-passing style and makes the control flow much harder to follow.
One way in which Python-style generators can be translated into OCaml is to use communication “channels” (as in the Event module of OCaml). A toy example of such a system can fit in a single post
open Effect
open Effect.Deep
type 'a channel =
{ senders: ('a * (unit, unit) continuation) Queue.t;
receivers: ('a, unit) continuation Queue.t }
let new_channel () =
{ senders = Queue.create(); receivers = Queue.create() }
type _ eff +=
| Spawn : (unit -> unit) -> unit eff
| Send : 'a channel * 'a -> unit eff
| Recv : 'a channel -> 'a eff
let spawn f = perform (Spawn f)
let send ch v = perform (Send(ch, v))
let recv ch = perform (Recv ch)
let suspended : (unit -> unit) Queue.t = Queue.create()
let suspend f = Queue.add f suspended
let restart () =
match Queue.take_opt suspended with
| None -> ()
| Some f -> f ()
let rec run (f: unit -> unit) =
match f () with
| () -> restart ()
| effect (Spawn f), k -> suspend (fun () -> run f); continue k ()
| effect (Send(ch, v)), k ->
begin match Queue.take_opt ch.receivers with
| Some rc -> suspend (continue k); continue rc v
| None -> Queue.add (v, k) ch.senders; restart ()
end
| effect (Recv ch), k ->
begin match Queue.take_opt ch.senders with
| Some(v, sn) -> suspend (continue sn); continue k v
| None -> Queue.add k ch.receivers; restart ()
end
Given this you can write, for example:
let rec generator ch i =
send ch i;
generator ch (i+1)
let main () =
let ch = new_channel () in
spawn (fun () -> generator ch 1);
for i = 1 to 20 do
Printf.printf " %i" (recv ch)
done;
print_newline ()
let () = run main
which will output 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20, with both the generator and the consumer written in direct style.
There is this make_iterator function, which uses shallow handlers to do something similar to ECMAScript and python generators, using delimited continuations: it’s a sort-of delimited version of call/cc. Generator functions can yield at yield points and values can be returned both ways. (You can ignore the await function for this purpose, that does something else.)
The main issue is typing the yield operation, since we somehow need to learn what type is produced and what is expected to be received in exchange. This makes it hard to have a single Yield effect covering all potential types, unless we accept an extra argument to carry that type information (e.g. channels). As an alternative to the single effect definition, we can instead pass to the producer the ability to yield:
type ('a, 'b, 'c) coroutine =
| Terminated of 'c
| Yielded of 'a * ('b -> ('a, 'b, 'c) coroutine)
let coroutine : type a b c. (yield:(a -> b) -> c) -> (a, b, c) coroutine = fun fn ->
let open struct
type _ Effect.t += Yield : a -> b Effect.t
end in
let yield v = Effect.perform (Yield v) in
match fn ~yield with
| result -> Terminated result
| effect (Yield v), k -> Yielded (v, fun c -> Effect.Deep.continue k c)
The consumer can then control the execution and respond to yield events, with the coroutine type resembling a generalized Seq.t:
let range ~yield start stop =
for i = start to stop do
let x = yield i in
Format.printf "got %S@." x
done ;
"the end"
let rec print_all = function
| Terminated r -> r
| Yielded (i, next) ->
Format.printf "yielded %i@." i;
print_all (next (string_of_int i))
let () =
let co = coroutine (range 1 10) in
let res = print_all co in
Format.printf "terminated %S@." res
open Effect
open Effect.Deep
let invert (type a) ~(iter : (a -> unit) -> unit) : a Seq.t =
let module M = struct
type _ Effect.t += Yield : a -> unit t
end in
let yield v = perform (M.Yield v) in
fun () ->
match iter yield with
| () -> Seq.Nil
| effect M.Yield v, k -> Seq.Cons (v, continue k)
let range start stop yield =
for i = start to stop do
yield i
done
let rec print_all seq =
match seq () with
| Seq.Nil -> ()
| Seq.Cons (i, next) ->
Format.printf "yielded %i@." i;
print_all next
let () = print_all @@ invert ~iter:(range 0 10)
Thanks @JohnJ for posting this solution. Of course, if one really wants a Python-style imperative generator, it’s easy to turn a sequence into such a generator, using either Seq.to_dispenser or the code below for an even more Python-ish experience.
type 'a generator = 'a Seq.t ref
let generator_of_sequence (s: 'a Seq.t) : 'a generator = ref s
exception StopIteration
let next (g: 'a generator): 'a =
match !g () with
| Seq.Nil -> raise StopIteration
| Seq.Cons(n, s) -> g := s; n
I also agree with @bsidhom that shallow handlers give a more direct way to implement imperative generators. For reference, here is one such implementation. It’s actually the most convincing use case for shallow handlers that I know of.
The code monomorphic in the type of values produced by the generator (int in the example), but polymorphism can be recovered using a functor, for instance.
open Effect
open Effect.Shallow
type 'a eff += Yield : int -> unit eff
type generator = { mutable next: (unit, unit) continuation }
let make_generator (f: unit -> unit) = { next = fiber f }
let yield n = perform (Yield n)
exception StopIteration
let next g =
continue_with g.next ()
{ retc = (fun x -> raise StopIteration);
exnc = (fun e -> raise e);
effc = (fun (type c) (eff: c eff) ->
match eff with
| Yield n ->
Some (fun (k: (c,_) continuation) -> g.next <- k; n)
| _ ->
None) }
None) }
An example of use:
type tree = Leaf of int | Node of tree * tree
let rec iter_tree = function
| Leaf n -> yield n
| Node(l, r) -> iter_tree l; iter_tree r
let _ =
let t = Node(Leaf 1, Node(Node(Leaf 2, Leaf 3), Leaf 4))) in
let g = makegen (fun () -> iter_tree t) in
assert (next g = 1);
assert (next g + next g = 5)
Note the recursion in iter_tree: there’s no need for Python’s yield from since effects naturally support so-called stackful generators.
Yes, the lack of polymorphism is precisely the issue I was having and which @art-w pointed out as well. However, your implementation is substantially shorter and more readable than what I had come up with. Is the only way around monomorphization functors?
Yes, I did consider this. The dispenser converters are very nice on the receiving side but require CPS within the generator itself. I much prefer your solution below with shallow effect handlers. The missing piece was using exceptions to signal returns, which clean up the implementation but make it a bit harder on the consumer side. I do like that this also allows you to also pack a return value into the exception itself.
What I’m gathering so far from the above discussion is that the only way to get polymorphic send/receive is to invert control by passing in a consumer function or else use some sort of abstraction (queue/channels) to wrap the hand-off.
I know typed effect handlers are far off, but are the implementations being considered amenable to this use case?
The functor-based solution is just to generate yield/next functions at the type you’re interested in:
module Makegen(X: sig type t end)
: sig type value = X.t
type generator
val make: (unit -> unit) -> generator
val yield: value -> unit
val next_opt: generator -> value option
val next: generator -> value
exception StopIteration
end
= struct
type value = X.t
type 'a eff += Yield : value -> unit eff
...
So you’d need to instantiate it once per type of interest, and then you can write Pythonic code:
module Intgen = Makegen(struct type t = int end)
... Intgen.yield 42 ... Intgen.next g + 8 ...
But it’s also possible to parameterize the generating function over the yield operation, as in the invert code posted by @JohnJ, and identify the generator with its next function:
let make_generator (type a) (f: yield: (a -> unit) -> unit) : unit -> a =
let module X = struct type 'a eff += Yield : a -> unit eff end in
let g = ref (fiber (fun () -> f ~yield:(fun n -> perform (X.Yield n)))) in
fun () ->
continue_with !g ()
{ retc = (fun x -> raise StopIteration);
exnc = (fun e -> raise e);
effc = (fun (type c) (eff: c eff) ->
match eff with
| X.Yield n ->
Some (fun (k: (c,_) continuation) -> g := k; n)
| _ ->
None) }
Example of use:
let g = make_generator (fun ~yield -> List.iter yield [1;2;3;4;5;6]);;
g() + g();;
It’s completely polymorphic, but not exactly the same programming style as in Python.
I was trying to eliminate the need for the explicit ~yield argument int the last make_generator, in an attempt to make it even more ergonomic. I came up with
let rearrange (iterator : ('a -> unit) -> 'b -> unit) collection =
fun ~yield -> iterator yield collection
let make_generator_variant it coll = make_generator (rearrange it coll)
which appears to work fine, like this:
make_generator_variant List.iter [1;2]
but has a possibly unsatisfactory type:
val make_generator_variant : (('a -> unit) -> 'b -> unit) -> 'b -> unit -> 'a
which hides the fact that 'a is an element in the collection 'b