How to compose effect handlers with Eio

I am trying to build a module allowing scoped access to some global state. It allows setting and getting the state as well as waiting for updates of said state.

I assumed that in the following program, the Get effect would be handled by my effect handler because of the nesting but alas it doesn’t happen.

I intuitively understand why - since I’m using shallow handlers the first time an eio effect is raised (on both) Eio handles the effect and resumes the continuation in a context where my effect handler is no longer in scope so to speak.

Nonetheless it’s a bit surprising and I’m having a hard time understanding how I should’ve built this and how effect handlers compose. I would appreciate pointing out where my mental model (or lack thereof :wink: ) is incorrect.

module type State = sig
  type t

  val run_with_eio : (unit -> unit) -> init:t -> unit
  val get : unit -> t
  val update : (t -> t) -> unit
  val wait_for_update : unit -> unit
end

module Make (S : sig
  type t
end) : State with type t = S.t = struct
  open Effect
  open Effect.Shallow

  type t = S.t
  type _ Effect.t += Get : t Effect.t
  type _ Effect.t += Update : (t -> t) -> unit Effect.t
  type _ Effect.t += Wait_for_update : unit Effect.t

  let get () = 
    print_endline "performing Get";
    perform Get

  let update f = perform (Update f)
  let wait_for_update () = perform Wait_for_update

  let run_with_eio =
    let rec loop :
        type a r.
        t ->
        (a, r) continuation ->
        a ->
        (unit Eio.Promise.t * unit Eio.Promise.u) ref ->
        r =
     fun state k x p ->
      print_endline "resume continuation";
      continue_with k x
        {
          retc =
            (fun result ->
              print_endline "returning";
              result);
          exnc = (fun e -> raise e);
          effc =
            (fun (type b) (eff : b Effect.t) ->
              match eff with
              | Get ->
                  print_endline "handling Get";
                  Some (fun (k : (b, r) continuation) -> loop state k state p)
              | Update updater ->
                  Some
                    (fun (k : (b, r) continuation) ->
                      print_endline "handling Update";
                      let next_state = updater state in
                      let () =
                        if next_state != state then
                          let resolver = snd p.contents in
                          let () = Eio.Promise.resolve resolver () in
                          p := Eio.Promise.create ()
                      in
                      loop next_state k () p)
              | Wait_for_update ->
                  print_endline "handling Wait_for_update";
                  Some
                    (fun (k : (b, r) continuation) ->
                      let () = Eio.Promise.await (p.contents |> fst) in
                      loop state k () p)
              | eff -> 
                  print_endline (Printexc.to_string (Effect.Unhandled eff));
                  None);
        }
    in
    fun f ~init ->
      let p = ref (Eio.Promise.create ()) in
      loop init (fiber f) () p
end

let%expect_test "Cooperative scheduling" =
  let module IntState = Make (struct
    type t = int
  end) in
  Eio_main.run (fun _ ->
      IntState.run_with_eio ~init:0 (fun () ->
          Eio.Fiber.both
            (fun () ->
              print_endline "yielding";
              Eio.Fiber.yield ();
              IntState.update (fun x -> x + 1);
              print_newline ();
              print_endline "back to first";
              print_int (IntState.get ()))
            (fun () ->
              print_newline ();
              print_endline "trying to get new state";
              print_int (IntState.get ());
              IntState.wait_for_update ();
              print_newline ();
              print_int (IntState.get ()))));
  [%expect ""]

Here’s the output of my program (never mind the Stdlib.Effect.Unhandled( prefix on each line. I just quickly hacked printing effects using Printexc).

+|[@@expect.uncaught_exn {|
+|  (* CR expect_test_collector: This test expectation appears to contain a backtrace.
+|     This is strongly discouraged as backtraces are fragile.
+|     Please change this test to not include a backtrace. *)
+|
+|  ("Stdlib.Effect.Unhandled(Traffic_controller.State.Make(S).Get)")
+|  Raised at Traffic_controller__State.Make.run_with_eio.loop.(fun) in file "traffic-controller/lib/state.ml", line 44, characters 27-34
+|  Called from Eio_luv.run.(fun) in file "lib_eio_luv/eio_luv.ml", line 1287, characters 18-29
+|  Re-raised at Eio_luv.run in file "lib_eio_luv/eio_luv.ml", line 1298, characters 20-55
+|  Called from Traffic_controller__State.(fun) in file "traffic-controller/lib/state.ml", line 83, characters 2-635
+|  Called from Expect_test_collector.Make.Instance_io.exec in file "collector/expect_test_collector.ml", line 262, characters 12-19
+|
+|  Trailing output
+|  ---------------
+|  resume continuation
+|  Stdlib.Effect.Unhandled(Eio__core__Cancel.Get_context)
+|  Stdlib.Effect.Unhandled(Eio__core__Cancel.Get_context)
+|  Stdlib.Effect.Unhandled(Eio__core__Fiber.Fork(_, _))
+|  yielding
+|  Stdlib.Effect.Unhandled(Eio__core__Cancel.Get_context)
+|  Stdlib.Effect.Unhandled(Eio__core__Fiber.Fork(_, _))
+|
+|  trying to get new state
+|  performing Get
+|  Stdlib.Effect.Unhandled(Eio__core__Cancel.Get_context)
+|  Stdlib.Effect.Unhandled(Eio__core__Suspend.Suspend(_)) |}]
2 Likes

Hmm I think things are quite subtle here. One problem is I think you’re hitting the same thing I was talking about in Escaping Effects which happens with Deep handlers too. I removed the printing of the unhandled effect because I found that a bit misleading (all of the Eio unhandled ones are just not handled by the inner state handler, but are handled by the Eio handler that’s wrapping it). Which just leaves:

resume continuation
yielding

trying to get new state
performing Get
Fatal error: exception Stdlib.Effect.Unhandled(Dune__exe__Main.Make(S).Get)

And this boils down to Eio’s implementation for Fiber.fork which is implicitly called by your Fiber.both. When you fork a function fn:

fn runs immediately, without switching to any other fiber first.

Which means fn is called in Eio’s handler and so you are outside of the scope of IntState handler.

If you simplify the whole thing down a lot more to just:

Eio_main.run (fun _ ->
    IntState.run_with_eio ~init:0 (fun () ->
          Eio.Fiber.both
            (fun () -> print_int (IntState.get ()))
            (fun () -> ())));

You get the exception. If you flip the handlers then you get a working program… but not for long, because if you introduce your Wait_for_update effect you implicitly raise an Eio effect by awaiting the promise and now your inverted handler program raises an exception!

IntState.run_with_eio ~init:0 (fun () ->
    Eio_main.run (fun _ ->
          Eio.Fiber.both
            (fun () -> IntState.wait_for_update ())
            (fun () -> ())));

handling Wait_for_update
Fatal error: exception Stdlib.Effect.Unhandled(Eio__core__Suspend.Suspend(_))

Also see this discussion from a while back Am I wrong about Effects? I see them as a step back - #15 by patricoferris – my conclusion there was composing handlers is tricky so I aim to be somewhat sparing in their use. However, I think some people are looking at how to define generic effects that people could reuse to build things like synchronisation primitives which might help composing that kind of thing, see this talk for more info on that: https://watch.ocaml.org/videos/watch/08ea09a1-e645-47cb-80c4-499dd4d93ac8 (note that’s schedulers and not generic handlers).

However, as I mentioned it’s even subtler than that when you bring in shallow handlers (the above problems are also there for deep handlers). Take this example with inverted handlers (compared to your original):

IntState.run_with_eio ~init:0 (fun () ->
    Eio_main.run (fun env ->
      Eio.Time.sleep env#clock 1.;
      print_int (IntState.get ())
  ))

If we remove the sleep, we get a normal working program. With the sleep (which on all Eio backends performs an effect) we get an unhandled Get again. And actually we can drill down a little deeper and discover it’s actually any Eio function call that performs the Suspend effect!

IntState.run_with_eio ~init:0 (fun () ->
    Eio_main.run (fun env ->
      Effect.perform (Eio.Private.Effects.Suspend (fun _ e -> e (Ok ())));
      print_int (IntState.get ())
  ))

And to be honest I don’t quite follow why this breaks but I think it’s because the fn of the Suspend is called inside the Eio handler which presumably (as you said) is where the shallow handler is no longer in scope… but that’s a bit hand wavy to me ^^" So in retrospect I think that this is the unhandled effect problem you are hitting, but it wouldn’t have been long before you hit the other ones I was talking about. Presumably an effect system would have just not compiled your program and left you to understand why :))

1 Like

Sorry that was quite long but I initially thought it was one problem but then discovered it was the mixture of Suspend and shallow. My conclusion from that is that without an effect system composing completely independent handlers is going to be tricky and require full knowledge of all the possible effects that your program calls and how they impact control flow.

Thank you for the thorough answer. I thought I was missing something obvious.

The thing that surprised me (if you look at my “extra” logs) is that when we perform the Get effect, there are those Eio__core__Cancel.Get_context and Eio__core__Suspend.Suspend performed and they are caught by “my” handler. I don’t understand yet where that is coming from…

Edit: I do now, I checked the implementation of Eio.

One way to look at the issue is that you have two sets of effects interacting: the state effect handler uses Eio effects whereas the Eio effect handler will perform any effects in scope. Due to this circular dependency on the interpretation of the two sets of effects, there are no nestings of the two effect handlers that makes the two sets of effects independents of each other. Consequently, you have to define yourself how the two sets of effects are interacting. I don’t know if Eio allow you to do that easily however.

@talex5 is it possible to define how effects should compose in such case with eio?

Eio already supports global state: use Eio.Fiber.with_binding to provide scoped state, but at the top-level of your program. e.g.

open Eio.Std

let state_key = Fiber.create_key ()

let get_state () = !(Option.get (Fiber.get state_key))
let incr_state () = incr (Option.get (Fiber.get state_key))

let () =
  Eio_main.run @@ fun _env ->
  Fiber.with_binding state_key (ref 0) @@ fun () ->
  traceln "state = %d" (get_state ());
  incr_state ();
  traceln "state = %d" (get_state ())

(I didn’t do the waiting stuff; that’s easy enough and unrelated to the problem here)

Right, but to address the problem more broadly, what about the composition of effects with Eio’s handlers in general? Is it achievable, how? I understand that for this particular case there is a built-in.

1 Like

Composition is fine as long as the two systems are independent. But as others mentioned, here you want the code running under your handler to be able to fork Eio fibers that also inherit the handler, and you want your handler to perform Eio effects.

I’m having a hard time thinking of uses for this.

  • If you want your handler to return a value immediately then the handler is effectively just a function call, and the only problem is getting the function. That’s just the “global state” problem, which Eio already supports.
  • Instead, you might want to schedule the fiber to run later. But having two schedulers doesn’t seem useful. If your code knows about Eio anyway, you might as well let Eio schedule things instead.
1 Like

Let me provide you with a simpler example.

module Echo = struct
  type _ Effect.t += Echo : string -> unit Effect.t

  let run f =
    Effect.Deep.try_with f ()
      {
        effc =
          (fun (type b) (eff : b Effect.t) ->
            match eff with
            | Echo string ->
                Some
                  (fun (k : (b, unit) Effect.Deep.continuation) ->
                    print_endline string;
                    Effect.Deep.continue k ())
            | _ -> None);
      }
end

let main () =
  Echo.run (fun () ->
      Eio_main.run (fun _ ->
          Eio.Fiber.both
            (fun () ->
              Eio.Fiber.yield ();
              Effect.perform (Echo.Echo "world"))
            (fun () ->
              Effect.perform (Echo.Echo "hello"))));

That program crashes as well. This is what I mean about composition wrt large.

1 Like

Oh wait hang on, actually the problem I mentioned above doesn’t exist ^^" (about the suspend etc.). This is actually an issue with the libuv backend in Eio I think ://

The code can be made a bit simpler (to remove any worries about forking) too:

let () =
  Echo.run @@ fun () ->
  Eio_main.run @@ fun _ ->
  Eio.Fiber.yield ();
  Effect.perform (Echo.Echo "world")

On the linux backend this is fine and the luv backend it raises an exception. I think this is because of the use Luv.Async for waking up the scheduler and that’s where we’re losing the outer handler. eio/eio_luv.ml at a36443f48a2f155811ceacf6c46694d1ca49240a · ocaml-multicore/eio · GitHub

3 Likes

I opened an issue to track this, thanks @wokalski for providing examples and helping get to an answer!

Ah, this doesn’t have anything to do with composing effects. You get the same thing without Eio at all:

let () =
  Echo.run @@ fun () ->
  let timer = Luv.Timer.init () |> Result.get_ok in
  Luv.Timer.start timer 0 (fun () ->
      print_endline "Running callback";
      Effect.perform (Echo.Echo "world")
    ) |> Result.get_ok;
  ignore (Luv.Loop.run () : bool)

produces

Running callback
Stdlib.Effect.Unhandled(Dune__exe__Main.Echo.Echo("world"))

The reason (I think) is that you can’t perform effects over C functions. So an effect performed from within the libuv run function can’t be handled by an effect handler outside it.

1 Like

I had similar issues experimenting with mixing Lwt and effects. Essentially, the scoping of the handler is difficult to manage in a context where a concurrency scheduler rejigs your stack or something along those lines.

I’ve then gotten something half working by modifying Lwt’s main function to take effect handlers as argument and to reinstall them at the appropriate points. This solves the circular-dependency issue mentioned in @octachron 's answer. This solution comes with problems of its own; notably in terms of expressivity: you cannot install local handlers. It’s okish (emphasis on the “ish”!) with a few hacks like registering additional handlers in a global reference and using “thread-local keys” to pass locality information to the global mutable handler.

(I’ll try to get back to that experiment and document it better.)

In general, the documentation of effects and effect handlers lacks some more practical tips and tricks. These kind of things tend to appear as blogposts and discuss threads as a feature’s use expands in the community.

1 Like

Following up on this, it seems to me like an API where you can attach effect handlers (“define context”) for fibers in Eio would make a lot of sense and would be consistent with Eio in general.

Could you give an example where it would be useful? As I see it, performing an effect does two things:

  1. Finds a function to call by searching the stack for a caller that provides it.
  2. Suspends the current fiber and lets you resume it later.

You can already do both of these things using the current API, so I’m not sure what benefit it would have.

The only case I see where providing your own effect handler makes sense is to avoid a dependency on Eio, but then having an API in Eio to let you do that isn’t useful.

1 Like

Here’s a possible use-case:

  • You depend on a library which uses effects (say, a logging library loge (log+effect)).
  • This library exposes different effects (so you can do Effect.perform (Loge.Debug …)).
  • Other libraries of the same package expose different effect handlers (so you can do either Effect.Deep.match_with main () Loge_unix.handler or in a different program Effect.Deep.match_with main () Loge_eio.handler).

How does the library implement the Eio-specific effect handler? Wouldn’t it need to perform some of Eio’s own effects? Where should this effect handler be installed?

1 Like

In our project that uses Eio we would also use effects for logging, telemetry and emitting analytics data. Those things that are notoriously tedious if you have to pass something around. Currently it is not a huge issue for us because we can make those things Eio specific leveraging fiber local storage. But it will introduce tight coupling that we’d rather avoid.

1 Like

In the case of the existing Logs library, you set a reporter function when you start your application, and users call it. An Eio application would set a reporter function that used Eio, but Logs itself doesn’t need to know about Eio, and neither do libraries performing logging.

e.g. it works something like this:

let reporter = ref ignore

module Lib = struct
  let run () = !reporter "info: running"
end

let () =
  Eio_main.run @@ fun env ->
  let stdout = Eio.Stdenv.stdout env in
  reporter := (fun msg -> Eio.Flow.copy_string (msg ^ "\n") stdout);
  Lib.run ()

For your effects-based Loge library, it would be the same except it gets the reporter using an effect rather than via a global variable, but Eio doesn’t need to do anything special (except not use a C function for the mainloop, since that blocks effects).

Is “C function for the mainloop blocking effects” considered a bug or missing feature in the effects implementation or is it a constraint that we have to work with? Because if it’s the latter then Eio needs to take it into consideration IMO and provide an escape hatch.