Am I wrong about Effects? I see them as a step back

I recently discovered about effects in Ocaml 5, and a lot of people seems to be excited about it.
I feel like I am missing something, because to me they look like a step back in terms of program maintenance and correctness.
One of the reasons that attracted me to FP in general (Haskell, Ocaml, Elm, etc) was the rich type system and the ability to encode effects in it. Nothing is hidden anymore, no unexpected runtimes exceptions that appear out of the blue because you didn’t account about one of the gazillion possible edge cases.
To me Result and monads are a feature. I read the already famous article about coloring functions, and while I agree on the disadvantages, it completely fails to propose a better alternative that is safe and correct as those it complains about.

Effects look a lot like try-catch, where every function could, or could not, throw an exception, there is no way for you to know by reading the function signature, and there is nothing forcing you to handle such scenario, so the common thing is that most exceptions are not handled, leading to unexpected behaviours.
Effects seems to add some extra trouble to this situation, where exceptions and effects are mixed, and you never know what you are getting? Reminds me a lot to JS Promise rejecting for know cases and also errors, so you never know which of those are you getting (a proper response from the API that the library has decided randomly to throw? or a real error that happens to came from an unhandled situation). Java is another well know case of abused exceptions.

By the things I have read, it also seems that effects can be handled in any place, making certain parts of the code that seems to be detached to be actually coupled because the communicate through effects. Feels like a fancy way of implementing event emitters, which sounds good in theory until you have to understand how a codebase works, and how your changes may impact other areas of the application.

Obviously, the people behind OCaml are much smarter than me, and if they invested 5 or more years into getting this feature right, there must be something that I am missing, or some feature that I am not aware of, and because I failed at finding this bits myself reading articles about this online, I am just asking here.

How can effects be better than monadic flows where everything is visible in the type system and there is no way to forget to handle any case?

8 Likes

You are right so long as you’re talking about the current effect system. If all we ever have is the current effect system, it must be restricted to concurrency and nothing else. Otherwise we’ll end up making OCaml some of the least safe functional code around.

However, the plan is to integrate typed effects at some point, and this will solve every issue you mention.

9 Likes

I saw some mentions about typed effects, but I failed to find any concrete examples or blog posts about it. Do you have a link?

The effects bibliography can keep you busy for a few weeks. The approach taken on the scala side is enticing to me, it looks like statically checked exceptions done right.

2 Likes

I am personally very much looking forward to getting a chance to use the current effects.

Types are powerful but they can also make it tempting to let go of unit and runtime tests but those are precisely designed to catch situations like an unpredicted exception.

Adding everything to the type system can, on the contrary, be pretty heavy and not conducive to good code, because things like lack of readability, modularity or extensibility.

Not sure about the above statement – Indeed types may lull you into a false sense of safety. But this is hardly a reason to avoid them. It is akin to saying “Avoiding seatbelts is good because wearing seatbelts may make the driver more confident and encourage rash driving.”

As it has been pointed out earlier, untyped effects are transitional. In the future, the effects will become typed. That will be a good thing. The delta is already quite big for OCaml 5.0 - multicore GC & untyped effects. Once the system settles and becomes rock solid in OCaml 5.x, typed effects will be easier to introduce from a development point of view.

3 Likes

It’s not an either/or: effects allow all kinds of cool inversion of control tricks that you may use in your implementation without ever exposing them to the user. As I understand it, the idea is not to replace monadic APIs wholesale with (untyped) effects because of the reasons you mention.

See GitHub - ocaml-multicore/eio: Effects-based direct-style IO for multicore OCaml for an example which uses effects internally with an API that does not mention them.

In fact, the current (5.0) recommendation is to use them precisely like that: purely on the implementation side, without exposing them to the user. It was precisely to discourage exposing untyped effects at the API level that the dedicated syntax for them was not included in 5.0.

Cheers,
Nicolas

5 Likes

One reason to avoid effects, even in internal implementations, is that it limits portability of the code to the OCaml 5 runtime:

  • Currently the javascript targets don’t support them. js_of_ocaml may support them at some point (probably at some unknown performance cost to be paid by all code, not just effect-using code), but Bucklescript and al. that try to produce readable Javascript may never support them at all.
  • Domain parallelism can be emulated to run sequentially on OCaml 4 (see domain-shims), but effect operations cannot easily be emulated on OCaml 4.

(Of course some programs are designed to rely on the OCaml 5 runtime, typically they implement a concurrent scheduler. Then losing some portability is par for the course. But many other potential uses of effects are not strictly necessary and could have these unforeseen portability costs, for the authors and also for the users of the library.)

1 Like

I can’t really comment on the effects in particular. My response was directed toward the idea that not having exceptions represented in the type system was making programs less safe.

I think a better metaphor on the same lines as you suggested would be that driving assistance software are good as long as you can remember to keep your eyes on the road.

To make things more explicit, let’s consider the following function:

(* This function returns a positive float *)
let f() =
  let x = Lib.foo () in
  if x >= -1 then
    1. /. float (x + 1)
  else 0.

And imagine that we have an exception monad of sorts so that return types are of the form ('a, 'b) where 'b is the exception type and that we want to positively assert that this function never returns an exception (so 'b would be unit).

First thing first, we can’t have a catchall:

(* This function returns a positive float *)
let f() =
  try
    let x = Lib.foo () in
    if x >= -1 then
      1. /. float (x + 1)
    else 0.
  with _ -> 0.

That would simply negate the benefit of surfacing exceptions in the type.

Next, we’ll be happy to discover that /. can raise a Divide_by_zero exception and to course correct:

(* This function returns a positive float *)
let f() =
  try
    let x = Lib.foo () in
    if x > -1 then
      1. /. float (x + 1)
    else 0.
  with Divide_by_zero -> 
    (* This is already confusing. We might want to raise a assert error
        but we said no exceptions can be coming out of this function! *)
    0.

But, then, it turns out that our Lib dependency also throws exception. In fact, since it is a real-life HTTP call, it raises all sort of exception for network error, business logic error (http response codes) and more. So now we have to add all of them:

(* This function returns a positive float *)
let f() =
  try
    let x = Lib.foo () in
    if x > -1 then
      1. /. float (x + 1)
    else 0.
  with
      | Divide_by_zero
      | Network_timeout
      | Http_error _
      | ... -> (* Might have to do more but let's simply say: *)
                0.

This can quickly impact readability here.

Next, Lib does a next release and adds a new extension. Then, this code will break even though the function’s logic hasn’t changed. This impacts extensivity.

Next, if Lib swaps out their Pcre implementation, the code will break again, pointing to a lack of modularity. Same thing if you’d try to wrap the function inside a functor:

module My_function(Lib: Lib_t) = struct
  (* This function returns a positive float *)
  let f() =
    try
      let x = Lib.foo () in
      if x > -1 then
        1. /. float (x + 1)
      else 0.
    with
        | Divide_by_zero -> 0.
       (* Now, there is no way to know in advance all the exceptions
          potentially raised by Lib.foo *)
end

Meanwhile, the function was actually never satisfying its original expectations and all this type-safety did help to find that out at all:

# 1. /. float (max_int + 1);;
- : float = -2.16840434497100887e-19

In situations like this, a good unit test discipline has a much better impact in making the code safe. You have to look at your function’s code and, defensively, consider all runtime alternatives and corner cases that the code is designed to be executed with and actually run then and see if the outcome is what you’d expect.

To go back to the initial metaphor, GPSes are very powerful tools and have completely changed the way we drive, leading to great increase in safety but, every now and then, their map is out of date and you cannot actually take the left turn it tells you to take or maybe the weather is bad and there are pedestrians crossing so it’s still important to keep your eyes on the road and drive defensively… :slightly_smiling_face:

2 Likes

Indeed, not having exceptions represented in the type system does make programs less safe as you don’t know what exception lurks underneath ! Similarly with untyped effects, there could be some bugs lurking.

With typed effects, we should be able to track effects in the type system. So in the long term effects will not be able to “hide”. They will be visible via the types. [As far as exceptions go I would guess that since exceptions are a kind of effect we should be able to track them also in the future – however I’m not sure about this].

Having types should not be a reason to omit various kinds of tests. When types prove that certain errors cannot exist you can happily omit those kinds of tests. You will still need have tests for other situations which types don’t protect.

Many OCaml projects use types extensively but still have really nice test suites.

In other words, the existence of types always makes you strictly better off. I personally am not lulled by having types. I simply have a smaller space to test.

2 Likes

In other words, the existence of types always makes you strictly better off. I personally am not lulled by having types. I simply have a smaller space to test.

Absolutely!

Glad to see this situation is only temporal, and that people are not encouraged to migrate to it right away. Does anyone have a syntax proposal example? I took a loot at koka, and indeed it looks very nice, but I don’t know how such a system could integrate into ocaml, seems to require a huge refactor to account for effect types in the signatures.

1 Like

There’s some more useful info here.

1 Like

I feel that incredible byproducts of effects are never discussed, and they are awesome. i’ll call two out:

  • reduced module coupling. if some module is intrinsically bound to either a) many modules or b) some heavy module or c) some wonky module, you can abstract those negative properties away with effects. In this fashion, you may erase all references/imports/etc to those modules, then allow your module to focus strictly on its core offering. Your effects consuming module focuses on its functional-core logic, and defers complexity of the outside world to effects designed to deal with the harsh reality of the outside world. Here’s an example.
(* non effects demo *)
module Git = struct
  let is_dir_clean last_sha dir = 
    let files = ref [] in
    Fs.walk ~dir (fun childpath -> files := Fs.open_stream childpath :: files);
    let sha = List.fold digest !files in
    sha = last_sha
end

There’s nothing intrinsically terrible about this module. However, you may observe that we’re coupled to some Fs module, the List module, and …wherever module digest is coming from. Woe is us! What if we wanted to test a remote directory? What if we wanted to swap the hashing impl? Functor police, I hear you, but entertain me.

(*  effects demo *)
module Git = struct
  let is_dir_clean last_sha dir = perform (HashDirectory dir) = last_sha
end

What’s the difference? Now our is_dir_clean is totally decoupled from implementation details. It’s more expressive, it’s more direct. Of course the lines removed are not actually removed, they are just hoisted up the stack somewhere, but that also brings benefit, such as in cases of testing. Even if we had done:

(* non effects demo, p2 *)
module Git = struct
  let is_dir_clean last_sha dir = (Sha.of_dir dir) = last_sha
end

the coupling would still be present, albeit local magnitude of coupling reduced.

They effects syntax and semantics are probably not concise enough right now to make the effects based solution highly pragmatic, but they are close. Many here may suggest “you should have created a parameterized module!” or “Inject that wonky resource! It’s FP, composition is our jam!” This is all fine and good, and probably correct in this tiny demo. However, in some cases composition and functorization also has drawbacks. Parameterization complects module signatures, and forces work directly on consumers, where consumers may not have the the resources available. This scenario happens all of the time. Ultimately, developers find themselves threading resources deep through programs, some way or another. In this case, I needed a directory hasher, bound to a specific Fs type (local/remote) and some hashing algo. I posit that everyone here knows this feeling–“ah shoot, I need X, but X isn’t available here. Let me just refactor my whole (otherwise fine) program to transport resources to where they are needed.” I do this often in mid-to-large sized programs. In some cases, by deferring local complexity by means of effects, one may have a very freeing experience at the cost of some indirection (and likely a tiny bit of performance). The prod/release impl can implement one handler in an isolated space, and the testing impl can implement something simpler in the test harness. One then may ask, “so do I just effect all of the things?”. No, certainly not. However, modules with high integration with other modules may be candidate. I’ve been dwelling on a pattern of exposing libraries that use effects, that conventionally also export a handler fn with sensible defaults. eio somewhat does this now. Consider Eio_main sets up all its needed handlers, then the other modules simply use effects, but the consumer is nonethewiser.

  • direct style programming

OCaml is highly readable, iff the function under study question reads top to bottom. However, it’s extremely common in OCaml to have a “bouncy” function body. E.g.

let foo a =
  let f x = Bar.baz x in
  let get_bars ys = List.map f ys in
  let format_bars b = List.map Bar.fmt in
  get_bars a |> format_bars

I’ve long wanted to write a “code-complexity”-like score for what I call “line bounce”. If follow the control flow of foo, you first read top down, establishing functions, but as you follow your data through the function, you actually jump back up every line, then back down to the return. It’s the polar opposite of fluent programming. In this case, it’s not so bad. But it’s not uncommon for closures to be stacked on closures, auxillary rec functions inlined, callbacks to be passed outside of the local function… :dizzy_face: . I don’t think it’s controversial to suggest that it’s not always the best. Yes, there are strategies to mitigate. effects is one such strategy.

let foo a =
  let bars = perform (GetBars a) in
  perform (FormatBars bars)

This is admittedly a contrived and weak example, primarily because the “non-effects” version of foo could be easily pipelined with strict top => bottom, left => right semantics. Nonetheless, one can observe that effects is another vehicle to get that t/b, l/r direct fn flow, which yield’s less bounce, with less interim noise. Less noise = more delight!

3 Likes

One thing I worry about a little (if effects and their handlers become more widespread) is the complexity of composing handlers. Of course this might be a little easier to catch bugs with an effect system, but I still think it might be quite complicated for a user.

This is particularly problematic when effects are performed inside other handlers either as part of the implementation of the handler or because the effect runs a user-defined function (e.g. fork in Eio). To take the HashDirectory example:

module Sha = struct
  type _ Effect.t += HashDirectory : Fs.dir Path.t -> string Effect.t

  let hash_dir dir = Effect.perform (HashDirectory dir)

  let local_handler fn =
    (* This doesn't actually do the hash, just performs an effect! *)
    try_with fn () {
      effc = fun (type a) (e : a Effect.t) -> match e with
        | HashDirectory path -> Some (fun (k : (a, _) continuation) -> 
          let first = Path.(path / (List.hd @@ Path.read_dir path)) in
          continue k (Path.load first)
        )
        | _ -> None
    }
end

let () =
  Eio_main.run @@ fun env ->        (* 1 *)
  Sha.local_handler @@ fun () ->    (* 2 *)
  let hash1 = Sha.hash_dir env#cwd in
  let hash2 =
    Switch.run @@ fun sw ->
    Eio.Promise.await_exn @@ Fiber.fork_promise ~sw (fun () -> Sha.hash_dir env#cwd)
  in
  assert (hash1 = hash2)

In this (maybe a little contrived) example there is no ordering of the handlers at 1 and 2 that allows this program to run. In the way it is currently written, the hash_dir inside the fork escapes the scope of the local_handler. If you were to swap the handler around then the effects performed in the implementation of the local_handler (by using Eio functions) would escape the scope of the Eio handler! The programmer has to decide what kind of program they want by ordering the handlers.

I also worry about, but have very little knowledge of, how an effect system would track such a program. Will it know that the function called in fork better not perform a HashDirectory effect because the Eio handler is outside the scope of the local_handler? Is that an easy thing to track? I really have no idea ^^"

But let’s also appreciate the direct-style of it all :)) I think I’m heading towards the camp of limiting my use of effects to only the bare essentials (at the moment, for async IO).

3 Likes

Any sound effect type system will catch the fact that the handler may launch an effect itself and thus will catch the error in your code.

5 Likes

Me too. I think @kayceesrk remarked somewhere that if your effect handler just resumes the continuation immediately, then it probably shouldn’t have been an effect handler (use a function, functor, etc instead).

Most other users of effects seem easy to replace with fiber-local storage (which does work across Fiber.fork). In this case, you could instead do:

module Git = struct
  let is_dir_clean last_sha dir =
    let gen_hash = Fiber.get dir_hasher |> Option.get in
    gen_hash dir = last_sha
end

But I would use a functor here, which would:

  • Avoiding the possible runtime error if the caller didn’t set the hasher.
  • Run faster.
  • Allow using different hashers with different bits of code without one overwriting the other. e.g. a function which compares the hash of a local directory with the hash of a remote one might need two hashers. Though in this example you shouldn’t need different hashers anyway, because Eio.Fs itself will work on both types.
1 Like

js_of_ocaml should receive support for effects pretty soon https://github.com/ocsigen/js_of_ocaml/pull/1340

2 Likes

Thanks for the pointer! On this first iteration it sounds like we can expect a 2x-10x slowdown for js_of_ocaml programs compiled with support for effects. In the current state I would guess that js_of_ocaml will keep an option to not do the CPS transformation, so even people targetting js_of_ocaml will have to keep this in mind. It may be that a global analysis to do selective CPS transformation is workable in practice and makes this problem go away, though.

Note: if a global analysis followed by a selective transform works well, maybe it could also be an option for Melange ? But that sounds like a lot of complex work for a smaller project. Now I wonder if the global analysis could happen on an intermediate representation shared by the two backends, so that people don’t have to reimplement it twice.

(Maybe people will want to experiment with whole-program optimizations for OCaml anyway, there was this dead-code-elimination-by-LTO work by @chambart for example.)

1 Like