The status of eio and effects composition

While eio looks very promising, there is a massive showstopper for us (Routine) which is that, in my perception, it is hardly interoperable with other effects. There has been a discussion were I have explained my vision of this, and another one dealing it seems with the same issue. I have not found any other relevant discussion on this topic since that. We’d like to switch to eio in the near future, but this completely blocks adoption for us. Since the conversation dried up in the first topic, I’d like to open this dedicated new one to address the issue (or absence thereof) directly. I will restate my perceived issue with this, and would like to :

  • Be proven wrong wrt the fact I need this, in which case I can happily proceed.
  • Fail to convince that this is indeed a problem, and have to assess other solutions (another scheduler, or yet another homemade one).
  • Be told that this is going to be addressed and to please stay seated until it’s done.
  • Convince that this is a big misfeature, and work together towards a solution.

The issue in a nutshell.

This does not work (tested with eio 1.1) :

(** A dummy effect for demonstration purpose *)
type _ Stdlib.Effect.t += X : unit Stdlib.Effect.t

(** Run [f] while handling our dummy effect *)
let handle_x f =
  Stdlib.Effect.Deep.try_with f ()
    {
      effc =
        (fun (type effect) (effect : effect Effect.t) ->
          match effect with
          | X ->
              Some
                (fun (k : (effect, _) Effect.Deep.continuation) ->
                  Effect.Deep.continue k ())
          | _ -> None);
    }

let () =
  Eio_main.run @@ fun _ ->
  (* Handle our dummy effect from inside eio's run *)
  handle_x @@ fun () ->
  Eio.Fiber.both (fun () -> Stdlib.Effect.perform X) (fun () -> ())

Our effect is not handled like, I think, one could expect:

Fatal error: exception Stdlib.Effect.Unhandled(Dune__exe__Foo.X)

Funnily enough if you swap the arguments to Eio.Fiber.both, it accidentally works, which does not really honor the principle of least suprise. This is because eio sensibly runs the second callback directly instead of forking twice.

If you handle_x above Eio_main.run, this works as expected.

Why I argue this is a very problematic misfeature

  • I fundamentally believe in the composability of features. That is, if an ecosystem has features to solve a problem, these features must all compose to address composite problems and to be able to combine two different libraries that use an arbitrary set of those features.
  • I believe effects are a great flow control feature that must be freely usable. They certainly must not be overused, but in some case I think they are the cleanest most maintainable solution, especially to avoid side effects. I know this opinion is not shared by everyone, and that some would go as far as to say that effects are basically just there to implement eio-like scheduler and that’s it, but no matter where you fall on that spectrum I don’t think it’s the place of a library (eio in this instance) to take that decision for you and take effects away from you.

In our case at hand :

  • Eio is the way to perform asynchronous I/O in direct style.
  • Effects are (IMO) the correct way to perform many control flow operation, such as providing a global context to a call tree, a pure implementation of mutable state without devolving in a nightmarish sub-optimal state monad proliferation, etc. I would happily discuss why I think so, but I’m trying to keep this already loaded conversation clean of it since, as I explained, I don’t think it’s up to eio to decide this for me.
  • All our software stack is based on asynchronous I/O and such effects control flow, so both must compose.

Why it currently doesn’t work

Last time as checked, when forking a fiber, eio sends a Fork effect up to the scheduler (Eio_main.run) which will store in its fiber it for later continuation. By doing so the Fork effects gets out of our effect handler, and the callback it holds will be run and made into a fiber outside of its context, thus explaining the lack of our custom effect handler.

How this could work

Rather than plagiarizing myself, I will point you to my previous implementation, which both reproduces the problem described above and fixes it by creating and continuing the fibers at the fork point, so below the custom effect handler.

It requires to alter the scheduling of eio quite a bit, since now fibers are organized as a tree, not just a flat list with routines loosely waiting on each other. It’s only a proof of concept, so there could be some issues ahead that I missed, and I’m willing to help addressing these.

8 Likes

Thanks for insisting! I’ve been experimenting at GitHub - art-w/eio at nest to understand how your proof-of-concept could work cooperatively in Eio. It’s an early hack so bugs are expected and I may be utterly wrong to believe that this is doable. Your help is more than welcome to test and confirm if it works as intended in more complex scenarios :slight_smile: (atm it’s very likely that I missed some spots and that some continuations could be resumed in the wrong scope, resulting in unhandled effects… hopefully it’s fixable)

You can find some examples at tests/nest.md and it seems to work fairly well on simple tests… I arbitrarily named the feature Fiber.nest in a rush (suggestions welcome), because I didn’t want to add overhead to Switch.run and it turns out that this would have been a breaking change. There are some unintuitive behaviours when forking nested fibers to an outer switch, but this might be a feature rather than a bug (I like what the current behavior permits, but if it is an issue then I’m not sure how to fix it! If anyone wants an effect spaghetti challenge, this one is sauced)

Now, there’s more work required to clean up the hacks and better understand the feature’s limitations before submitting a PR (help welcome!). I don’t know if the Eio’s maintainers would be interested in supporting this as it is a very intrusive change. I still think that fiber-local storage should be preferred over trivial effect handlers Some (fun k -> continue k ...), since their semantics is much simpler with no surprise switch edge-cases.

I’m excited however if this can allow for interoperability with other schedulers, with explicit annotations like lwt_eio at the boundaries. There are some tests at the bottom of tests/nest.md on how to use Eio and Miou together (with no modifications made to Miou). The details are still fuzzy, but if it really works then it might be a best practice for schedulers to support effect handlers like you asked, so as to play nice with the rest of the ecosystem and allow users to mix and match libraries written for different schedulers (unless picos-compatibility is available).

Anyway, let me know if you run into any issue with the prototype!

5 Likes

This is a really interesting proposal and it opens the door to the possibility of using several schedulers without them being subject to the strong vertical constraint of a common base.

An earlier version of Miou included a mechanism where the user could specify an effects handler outside Miou so that Miou could be composed with other libraries that specified their effects. The only rule was (and still is) that all effects (even those not defined by Miou) suspend the calculation (all effects have the behaviour of a Yield). That’s what you’re describing here.

This handler has been removed as I’m not sure what API Miou could offer. My interest in cross-compatibility between schedulers also waned in view of the constraints imposed on me for such an objective and I preferred to focus my use of Miou on other subjects (such as HTTP). However, your demonstration gives me a bit more desire and I’d be delighted if several of us could iterate on this subject :slightly_smiling_face:.

4 Likes

TL;DR: This would make eio adoption possible for us. I argue we should go further and make this the default behavior.


Thank you for looking into this ! I’ll dig in deeper as soon as I can, but I’m first trying to wrap my head around what Fiber.nest does. From an outside point of view, I suppose it’s a stop point where all sub-fibers are attached instead of bubbling up to the top scheduler, effectively creating a tree of fibers ?

To clarify what I mean by tree, with this (pseudo) example:

Fiber.both 
  (fun () -> Fmt.pr "A")
  (Fiber.both
    (fun () -> Fmt.pr "B")
    (fun () -> Fmt.pr "C"))

The “logical” execution structure of EIO looks like a tree:

└── A
    ├── B
    └── C

But currently under the hood, stack-wise from the OCaml runtime point of view, the are not nested:

├── A
├── B
└── C

We obtain the “logical” behavior because Fiber.both happens to wait for both A and B before returning, but it’s not reflected in the calls nesting from the stack point of view.

My understanding is that the addition of Fiber.nest will catch the Fork effect in some way or another and start the fiber there rather at the root, reflecting the logical nesting in the calls nesting, indeed solving our effect issues.

I must say that if this works as intended, it’s already a much better, officially supported solution for effects composition, which would make using EIO work for us.

I will however add that I really think this should be the default behavior, since I see no case were the other semantic is preferable – although I did not consider performance implication. IOW I feel like it would be good practice to “Always immediately pair any forking point (Fiber.both, Fiber.fork, …) with a Fiber.nest”, at which point it’s just better to have that behavior built-in. I would probably, for Routine, have our own module that shadows these calls to immediately call Fiber.nest above or below and forbid the use of the naked ones.

Additionally, I think it should be the default behavior in the name of composability. One person could legitimately write a log library that provides the logger and logs through an effect, and another person could legitimately write a piece of code that run two externally-provided piece of code through Fiber.both. Without the Fiber.nest, combining these two perfectly legitimate pieces of code will produce an invalid program, hence my impression that "One should always follow a Fiber.both with a Fiber.nest lest everything may collapse when combined with another piece of code, which implies I think that it should be the default and only possible behavior.

I do realize this may be a breaking change, but a good one in my opinion, and we might as well want this while eio is still young and not yet widespread. In my very own vision, the current behavior could even be called a bug, in which case that wouldn’t even qualify as a breaking change.

3 Likes

There are two trees: the branching OCaml call stack with handlers and the Switch cancellation tree. Both are represented implicitly by flat datastructures in the runtime. With Fiber.both they are the same, but interesting behaviors can be achieved when they are not. Along which tree should effects propagate? Right now the prototype sits awkwardly in between and picks the worst of both when they differ. I believe there’s also a bug with cancellation because Fiber.nest introduced some new failure points that don’t account for it…

open Eio

type _ Effect.t += Name : string Effect.t
let with_name (name : string) fn =
  Effect.Deep.(try_with Fiber.nest fn {
    effc = fun (type a) (eff : a Effect.t) ->
      match eff with
      | Name -> Some (fun (k : (a, _) continuation) -> continue k name)
      | _ -> None
  })

let () =
  Eio_main.run @@ fun env ->
  Switch.run @@ fun sw ->

  let stop, set_stop = Promise.create () in
  let get_aaa, set_aaa = Promise.create () in

  Fiber.fork ~sw (fun () ->
    with_name "AAA" @@ fun () ->
    Switch.run @@ fun aaa ->
    Promise.resolve set_aaa aaa ;
    Promise.await stop);

  with_name "BBB" @@ fun () ->
  Fiber.fork ~sw:(Promise.await get_aaa) (fun () ->
    Format.printf "Who am I? %s@." (Effect.perform Name);
    Time.sleep env#clock 0.001;
    Format.printf "Who am I? %s@." (Effect.perform Name);
    Promise.resolve set_stop ())

This is all very hard to test: user-defined effect handlers may break implicit rules. For both trees, we naturally expect that leaves will terminate before their parent. Custom effects enable terminating a parent before its children, so now we have to choose what to do with its orphans.

type _ Effect.t += Suspend : unit Effect.t
let with_suspend fn =
  Effect.Deep.(match_with Fiber.nest fn {
    retc = (fun () () -> ());
    exnc = (fun e () -> raise e);
    effc = fun (type a) (eff : a Effect.t) ->
      match eff with
      | Suspend -> Some (fun (k : (a, _) continuation) () -> continue k () ())
      | _ -> None
  })

let () =
  Eio_main.run @@ fun _env ->
  let result =
    Switch.run @@ fun _parent ->
    Format.printf "parent started@.";
    let result =
      with_suspend @@ fun () ->
      Switch.run @@ fun _child ->
      Format.printf "child started@.";
      Effect.perform Suspend;
      Format.printf "child terminates@."
    in
    Format.printf "parent terminates@.";
    result
  in
  result ()
(*
parent started
child started
parent terminates
child terminates
*)

Regarding performances, Fiber.nest is relatively cheap but not free. It does nothing of interest if it’s not surrounded by a user-defined effect handler, so it is pure overhead to have it everywhere. This feature is best discussed on the Eio issue tracker, but you may have to provide benchmarks and analysis of the breaking change on existing Eio libraries. Actually, we should work on tweaking the semantics to smooth any differences, I don’t see a breaking change being introduced on the request of a non-user of the library.

The motivations need to be stronger. The composition of effect handlers feels intuitive only when one of the handlers is a trivial Some (fun k -> continue k ...): You should must use Fiber-Local Storage (FLS) for such environment passing (including logging), as FLS provide clean, guaranteed, semantics and better performances. A custom handler + Fiber.nest will cause issues on edge cases that could have been avoided with FLS (is it really composable if it sometimes break?).

I believe that Fiber.nest is only useful if the effect handlers are not resuming continuations straight away (= interoperability with other schedulers). What composition means here is dependent on the handlers and may require additional work to behave correctly, e.g. to ensure Eio and Miou yield to each others. Effect handlers are a sharp knife: they enable you to cut and reorganize your spaghetti call stack, but if you do it too much you end up with risotto and sure that’s still Italian cuisine but good luck eating the grains in just the right order to appease the cook.

3 Likes

It seems that all the examples we have for using this just resume the continuation immediately. In that case, as @art-w notes, fiber-local storage makes much more sense and works already.

So let’s separate out the things that already work from those that don’t. For example:

I’ll assume that the log reporter the application wants to use itself uses Eio (e.g. to send log messages to a remote server without blocking the rest of the application). Otherwise, you can just install the handler outside of the Eio loop and eveything works already.

If the logging library is willing to take a dependency on eio.core then it can implement logging simply as:

let log_msg m = Fiber.get logger m

and the application can use Fiber.with_binding logger my_logger ... to configure the reporter.

But if the logging library doesn’t want an eio.core dependency, it can still do it via an effect:

let log_msg m = perform Get_logger m

The application can install a top-level effect handler (outside of the Eio main loop) that returns a logging function that does use Fiber.get. That still allows configuring different loggers for different sub-trees of fibers.

So I think logging is quite easy (e.g. Logs is often used with Eio already, without either depending on the other, though it uses a global rather than an effect).

The interesting case is where the handler doesn’t immediately resume the fiber, but does some kind of scheduling of its own.

As you note, it is possible to give a meaning to this by nesting schedulers, so that Fiber.both runs the two fibers in a new scheduler with its own event loop, so that when one fiber performs an effect the whole sub-scheduler is suspended until that fiber is resumed.

But I’d guess that this isn’t what you’d want in most cases, and is likely to lead to deadlocks. Something similar can be a problem when using Lwt with Eio, if you accidentally perform a blocking Eio operation directly from a Lwt thread (all Lwt threads are suspended until the Eio function finishes). In fact, I had to add a debug mode to lwt_eio that catches all effects and reports an error when this happens, as it’s quite hard to debug otherwise!

1 Like

This discussion now revolves more around “Do we really need to support this, there are other way to achieve X”, so I’ll try to argue why I think we do. To reiterate, I think it’s perfectly reasonable to disagree and deem that Eio won’t support this since there are possible workarounds, in which case it’s up to me to decide whether I’m willing to give up my beloved effects or look for another solution.

Why I (still) think we need this

In no particular order:

I’ll assume that the log reporter the application wants to use itself uses Eio […] then it can implement logging [with Fiber.get].

I don’t want my logger to depend on eio; it should work in plain OCaml without any scheduler. Then I can provide an eio backend (à la logs-lwt, logs-eio etc) that handles the non-blocking io, but this shouldn’t leak in the core API.

But if the logging library doesn’t want an eio.core dependency, it can still do it via a […] top-level effect handler (outside of the Eio main loop).

The thing is that I don’t want my effect handler to be forced above the Eio main loop. One very concrete example is adding context (tags) to the log messages below a certain point in the stack, for instance the unique id of the query being handled by an HTTP server, to help with heavy logs interleaving, or maybe the user performing the call once it’s determined. This can happen at any level in the stack.

I know that fiber local storage can address this, but this goes againts “not depending on Eio”, and reverts to “Eio does not handle this but provides workarounds”. This, IMO, violates composability principles since it’s perfectly reasonable to write a logging piece of software that work this way without having any knowledge of Eio, and it then won’t work as intended when combined with Eio.

Logs is often used with Eio already, without either depending on the other, though it uses a global rather than an effect

True, and I really dislike that mutable global state and would rather keep everything pure. It is done that way because it would be unreasonable to expect the logger to be passed everywhere, so resorting to a global is to me a needed evil. But I feel like effects are here to free us of this dilemma, enabling us to both keep it pure/fonctional and avoid passing the logger everywhere. Eio taking this back from me makes me sad.

All in all, my feeling is that this works fine and is reasonable outside of Eio, so if possible it should keep working inside Eio. Otherwise we’re playing cat & mouse over how to do without and me coming back with other examples of why I need this.

Implementation

Now this is where my feature request may crumble even if we agree it’s desirable, because of implementation constraint. I have not fiddled with Eio enough yet to give bold statements about how it could work, please excuse me if some of the upcoming are not feasible or naive.

As you note, it is possible to give a meaning to this by nesting schedulers, so that Fiber.both runs the two fibers in a new scheduler with its own event loop, so that when one fiber performs an effect the whole sub-scheduler is suspended until that fiber is resumed.

That is the POC I wrote because it was the simplest implementation, but I think we can preserve the current scheduling ? All that matters for this to work is that fibers are started with the correct stack, but one could still schedule them with the current round robin at the root ?

I’m also instinctively under the impression that the call stack tree and the switch cancellation tree should really be the same, but maybe I lack vision there. What would be an example of interesting behavior when they differ ? Maybe understanding that will improve my perception of the issue.

Noteworthy, I have only considered effects that return immediately. If someone is playing the game of suspending execution, I think he must be aware of the consequences, especially if there is already a scheduler at play. Suspending any fiber has its consequences even outside of Eio, for instance holding a mutex indefinitely, and for these reason I would also argue that throwing out a fiber without resuming it is ill-defined.

I don’t want my logger to depend on eio

This is essentially the motivation behind the Picos project. See my recent announcement here on discuss.

The idea is to “standardize” a (relatively) low level interface between effects based schedulers and concurrent abstractions. This then allows concurrent abstractions to be “implemented in Picos” such that they can then work with any “Picos compatible” scheduler.

With Picos the “scheduler” becomes, due to standardization, a relatively uninteresting piece of the puzzle. If you are familiar with pthreads, for example, then you probably understand that, while there are multiple implementations of pthreads, then practically nobody writes their own pthreads implementation to do concurrent programming. That is what I would also expect to happen with Picos. I would expect there to be a number of extremely carefully crafted schedulers, some of them already provided as samples with Picos, and some others yet to be written. And then I’d expect (other) people to write all kinds of concurrent programming models (actors, structured concurrency, …), communication and synchronization mechanisms (mutexes and condition variables, message queues, …), and other abstractions needing concurrency support (IO systems, …). Note that the Picos project already demonstrates all of these, see the announcement.

All of these elements of concurrent programming models (schedulers and other abstractions) can then be more or less interchangeable and interoperable.

it should work in plain OCaml without any scheduler

This was actually how I also wanted Picos to work. The initial prototype I built had a mechanism that allowed it to provide default implementations that worked without any scheduler (and even on OCaml 4 — and Picos still supports OCaml 4). My motivation for this was that I wanted libraries using Picos, e.g. Kcas, to just work out of the box in a REPL without requiring one to pick a scheduler and run everything inside a scheduler. I felt that this would be important to avoid a barrier of entry for people to explore these kinds of concurrent programming libraries.

However, the feedback from scheduler authors was that they wanted the Picos core to be minimal and that default implementations were undesirable. So, the default implementations were removed. The current Picos core implementation was even recently changed such that it is built from a single .ml file.

FWIW, while I feel the pain, and have recently seen others experience that pain, I’m leaning towards thinking that removing the defaults was the right thing to do for the long term. That is because I believe that in the future nobody should be writing concurrent code in OCaml without a scheduler.

effects composition […] it is possible to give a meaning to this by nesting schedulers […] That is the POC I wrote because it was the simplest implementation, but I think we can preserve the current scheduling […]

I don’t really see how this could be made to work properly.

Honestly, I believe I can see the motivation, and I agree it would be nice if it could be made to work. However…

Frankly, the reason I don’t see this would work is that you are trying to solve a toy version of the problem. The effect handlers in your use case examples are of the trivial kind that simply immediately continue from tail position. How are you going to deal with the general case?

A couple of aspects of the general case:

  • Effect handlers can capture the continuation, store it somewhere for later use, and even perform actions after they have continued the continuation (i.e wrap around effects). Under what general conditions do effect handlers like this compose in a useful and meaningful way?

  • Schedulers (which are also just effect handlers) might run things on multiple domains or systhreads. Do you intend to “tunnel” effects from one domain to another in the general case? IOW, if you install a handler and then you use a scheduler to fork a fiber to run potentially on a different domain (perhaps this is done inside a library you are using), then how do you plan to transmit effects to the handler you installed (on another domain/systhread)? Under what conditions does this compose and perform (in terms of performance) in a useful and meaningful way?

So, honestly, I do not currently see how you could make this “effect composition” that you are after to just automatically work in a really useful and meaningful compositional way except in the trivial cases (non capturing, non wrap around handlers, no parallelism, strict nesting, …) and those trivial cases can easily be covered through e.g. fiber-local storage (FLS).

Also, while effects aren’t exactly slow, they are also not exactly fast. In fact, they are relatively speaking about an order of magnitude slower than what I’d expect runtime level support for FLS would be able to achieve. This is in fact a practical concern, because effects are slow enough that certain things, such as obtaining the identity of the current fiber, which is something required e.g. for checked mutexes, have a major impact on performance. I recently spoke about this in an OCaml runtime developers meeting: Support for FLS in the OCaml runtime .

7 Likes

I agree with Vesa, this seems infeasible in practice in parallel
schedulers (e.g. moonpool which uses picos and will happily move a new
fiber to a whole different thread if it wants to).

But even in general, I think this feature is kind of non sensical. Just
like, when you start a thread, it doesn’t inherit the current exception
handlers, new fibers shouldn’t inherit exception or effect handlers or
other parts of the forker’s stack.

Using FLS/TLS/globals for logging is the simple, clean, fast solution in
my book (for FLS I hope picos gets widely adopted so we can all rely on
its specific implementation as a standard).

2 Likes

As mentioned in my last post, it’s true that I have only considered effects that immediately resume so far (or at least that resume unconditionally without introducing interdependencies). Having these would already be a great. Regarding effects with more complex resume conditions, it’s clearly a dangerous game and you might introduce deadlocks, but at some point GIGO, you get what you asked for.

I was really puzzled about why this would be “nonsensical”, but I think the quiproquo might be this : I am not expecting any forked fiber to magically inherit exception or effects handler, as indeed I don’t even see how to properly specify this. I am only thinking of structured concurrency. If some scheduling API call runs a fiber independently in the background, or in a worker pool, etc, in other words detached from the current flow, indeed expecting any handler to be preserved is foolish. But when the scheduler structures the execution flows, it looks pretty well defined to me and very desirable. I think it’s not even exclusive to effects, anything relying on the execution stacks exhibits the same semantics.

Consider:

(* No effects *)
Sql.with_transaction @@ fun transaction ->
  sql_stuff_1 transaction;
  sql_stuff_2 transaction

I notice that stuff 1 and 2 are independent and can be run in parallel. Being a good developer and using Eio, I parallelize it :

Sql.with_transaction @@ fun transaction ->
  Eio.Fiber.both
    (fun () -> sql_stuff_1 transaction)
    (fun () -> sql_stuff_2 transaction)

Surely, this is well defined and legitimate? One is not going to argue that one of the fibers could be detached or outlive its parent, and use a defunct SQL transaction, I think. Even in the case of exceptions, the greatness of structured concurrency guarantees that both fibers will be finished or canceled before we exit with_transaction.

But this only works because of Fiber.both; if one completely detach an execution thread, à la Lwt.dont_wait, nothing is guaranteed. I’m not sure there’s such a feature in Eio, but imagining Eio.detach exists:

Sql.with_transaction @@ fun transaction ->
  Eio.detach (fun () -> sql_stuff_1 transaction);
  sql_stuff_2 transaction

Clearly, this will not work, as stuff_1 captured the transaction and might use it after it’s been committed / rolled back. I don’t think anyone would expect these to magically work.

In short, it’s really the structured nature of Fiber.both, Fiber.all, … that ensure this works.

What I strive is for this to be true for effects too. Imagine that Sql.with_transaction is implemented via effects (not a good idea and a clear overuse of them, but bare with me for the sake of the example).

(* Same with effects *)
Sql.with_transaction @@ fun () ->
  Eio.Fiber.both
    (fun () -> sql_stuff_1 ())
    (fun () -> sql_stuff_2 ())

I think it’s very easy to make the parallel with the effect-less version, and that the same argument applies : I can’t see why one would argue that one of the fibers may outlive the with_transaction, and consequently this seems very well define semantically to me. Likewise, I don’t suppose Fiber.both will run the subfiber in a different domain without telling me (otherwise I have much more pressing problems :sweat_smile: ), so we don’t have the “separate thread” issue. Starting a fiber in a different domain is, AFAIK, an explicit instruction, and one we cannot expect to preserve effects.

Regarding not resuming the continuation immediately, you’re “just” going to stale Fiber.both until you resume. If you create a deadlock doing so, it’s on you, you’re playing a dangerous game scheduling things behind the scheduler’s back. I also have trouble buying this point since one of the two fibers (the second, interestingly) is run directly from the current stack, and in that one you do have all the effect handlers installed, so in practice you call already perfecly do that.

Again, maybe I missed a crucial step that makes it technically impossible even in the very specific cases I’m talking about, but I’m failing to convince myself of this so far.

In short, to address @polytypic point :

the reason I don’t see this would work is that you are trying to solve a toy version of the problem

I think you’re correct, I’m only trying to have a very well defined subset of this to work, but it’s no toy to me, it’s the part I’m interested in. Maybe the issue is that I badly defined the scope of what I’m trying to achieve.

Or put more cheekily, well maybe but it’s MY toy and I like it :slight_smile:

3 Likes

This is coming up again and again, here’s my attempt to summarize the current state of discourse.

@mefyl showed good motivation for the feature: we have two logically concurrent tasks. Both of them might want to use async IO (as provided by Eio), and both of them might want to use other effects.

Currently, Eio has a global scheduler, and threads are to be thought of like system threads that might even run on another core, therefore they can’t inherit the context. But sometimes what we want is like a local while loop that tries to run one thread until it blocks, then run the other thread until it blocks and repeat. In this case, both threads sharing the evaluation context (and with that outer handlers) is no problem. Effects let us easily do this in direct style reusing the same interface.

If I understand @art-w correctly, Eio needs to have some support for cooperating with such local schedulers, but it does work.

2 Likes

I think it’s more than that, you also rely on the fact that the child
fibers run on the current thread. One can have structured concurrency
that spawns multiple threads/domains (and is thus incompatible with what
you want, afaict). The structured concurrency property is only going to
buy you invariants about the lifetime of fibers, nothing about whether
they can share effect/exn handlers.

Are there schedulers that silently switch fibers to other threads? In my perception this is purely opt-in, as most code is not thread safe and shouldn’t be since 20+ years ago coroutines freed us of having to use parallelism where concurrency is needed. If it’s opt-in, then it’s not an issue, since it makes it very clear that the flow is going to be detached and lose all stack context.

In the case of scheduler that may swap any fiber around threads silently, then one must indeed be aware that handlers will be lost. I don’t use such scheduler, so this does not lessen my desire for the feature :slight_smile:

1 Like

As far as I can tell, at least moonpool and miou will schedule fibers on
other threads by default.

As there is some (IIUC limited) form of isomorphism between algebraic effects and monad transformers, and as it is possible to make composeable effect-handlers, I think it would be a wise choice to be very explicit about why your specific library’s handler is not composeable. I agree that the default should be to allow composition. This initial point in the evolution of the effects-ecosystem is important for how things turn out later.

1 Like

I don’t think this paper is relevant, modularity as they describe holds trivially in any language with built-in effect handlers. It’s just about forwarding an effect unhandled by a handler to the next handler etc.

The real issue boils down to this: when you do Eio.both (f,g), at some point effects Suspend f and Suspend g are performed. When you have functions as effect payloads, you have zero guarantees in which context they will run.

There is another way that guarantees that the functions will run in the caller context:
both (f,g) could defined as using Unix-style fork concurrency, if (perform Fork) then f() else g(). The Fork effect has no payload and returns a bool. The functions literally run in the caller context, just after some operation returns. Here the Fork handler uses the continuation twice, which OCaml doesn’t really support.

I’ve only briefly skimmed this paper, but it seems focused on the simple Haskell
style transformers (StateT, etc.). Does Haskell have transformers that
represent asynchronous computations/fibers/threads? All I can find is
IO-level non-transformer libraries.

Generally speaking, how do you expect fibers and other effects to
compose? If I have a state-like handler (an effect to get the value, an effect to
set the value), and I fork 10 fibers from within it, potentially on
other domains; is the state handler now supposed to be thread-safe? are
we ok with race conditions (fiber1 gets; fiber2 gets; fiber2 sets;
fiber1 sets, but based on an obsolete value)?

It’d be nice to be composable and all, but personally I’m not writing
Haskell-style code, I use imperative stuff and side effects for many
things Haskell users would use a monad for. Effects are a killer feature
for concurrency because that’s the foremost place they enable things
that used to be really hard or unergonomic.

I feel like the conversation has started going circles.

AFAICT there is an implementation that makes this work in the case myself and some people are interested in, and I provided it in the opening post. The proposed solution is to split the execution flow at the Fiber.both level instead of letting the fiber bubble to the top. It seems to me that it works and is well defined, and I don’t think this has been disproved in this thread. There has been other reasonable rebuttals, some underlining the fact it wouldn’t work with multiple domains to which I answered that I clearly don’t intend it to and don’t think it should.

I can understand considering that the anticipated performance loss (although I’d like to measure it), more complex design, harder debugging, … isn’t worth it because using effects like I want to is not a good idea; I’ll disagree, but I understand that position.

But I feel like the messages providing an actionable solution and explaining in detail why I think it’s very well defined are being overlooked, in good faith I’m sure, but it brings the discussion to a dead end for me. I’m more than happy to explain myself again if I’m not clearly explaining my train of thought.

To explain my stance, I think it makes sense to describe my intuition about all this related to OCaml as a language.

My initial introduction (a long time ago) to effects in OCaml that made me hyped for them, was Leo Whites talk about typed effects, where I saw how this could bring more FP and more type-safety to the language. Existing effectful functions could suddenly get effect-types, and purity could be enforced in certain places. I also liked what I heard about the partial isomorphism with monad transformers.

My problem now with seeing that compositionality is not a given, and we are unsure about if/when typed effects come at all - is that now I get a feeling that we are moving the language+ecosystem further away from “get what you see” semantics of FP. Related: this is also why I’m critical of modular implicits, as I know how that has been to work with in Scala.

I see the described problem that the effect-based concurrency libraries can have concerning compositionality of handlers, and pragmatism has its advantages sometimes - but as there could be more pure and composeable ways of using effects, that could potentially be useful in OCaml, I feel it looks like a code-smell when:

  • libraries using effects don’t make it explicit how they are not composeable with other effect-handlers and why
  • libraries begin to suggest that other libraries depend on them to exist within them

Ideals I would continue to strive for always, that is already strong within the OCaml community:

  • separation of libraries
  • minimal dependencies
  • typesafety
  • compositionality
  • referential transparency

I like the idea of picos and hope it will gain adoption in all the new concurrency libraries so we can at least have have separation of libraries and minimal dependencies.

4 Likes

Yes, with the right local handler for Suspend and Yield what you want will work. I was pushing back on vague appeals to composability of handlers which no one can define and trying to point out that the signature allows for a wide range of behaviors, you have to use the right handler for the job.