Why use an effect system?

Now why was it so simple to find the bug in that example? Because you only had one effect system to deal with.

So expand your example to a large application that has to use multiple effect systems (in libraries) that only interact with each other via IO a, and imagine trying to find a bug in that labyrinth!

1 Like

I don’t understand how the wired components cannot know about the DI library unless there’s some form of adapter that connects them. But if an adapter is required then you can have exactly the same story with an effect system: no need to them to know about each other, you provide an adapter that connects them.

Or am I missing something? If so, could you give an example? I don’t understand DI well.

It’s tricky, because I think different people actually seem to mean different things by “effect system”. For example, Bluefin is basically the handle pattern with extra type safety, so it’s simultaneously the simplest and most basic approach, coupled with the most “modern”/“advanced”. Some people seem to think effect systems must be “algebraic” (I don’t understand what that means).

FWIW it was clear to me.

Much of the “effects systems” seem to be more “mtl replacements” which entail wrangling typeclasses, I’m not sure it’s the same as the “effects” Moggi described/what IO accomplishes. As far as I can tell much of the difficulty is using typeclasses to witness while juggling stacks of states.

I’m not convinced there’s an elegant solution.

1 Like

Thank you for pointing out this nice registry library. It’s pretty cool how it can automatically wire functions using their types. Unlike effect systems, this one is removing boilerplate. And if we add an argument to a function and it’s already in the registry, there’s no change to the calling code at all.

And it’s simple and monomorphic. Just replace one record-of-functions with another. Not sure it would be possible to mock the effects of current effect systems with such an ease:

-- instead of a simple 
newA :: IO A -- where we can just use the "effect" A
-- effect systems have different types before 
-- and after the effect instantiation
runA :: Eff (A : es) r -> Eff es r
-- or 
runA :: (forall e . A e -> Eff (e :& es) r) -> Eff es r
-- even if we specify the common monad for all components,
-- threading mocked/unmocked effects will require
-- some inhumane type acrobatics, or having the same
-- "escaping"
newA :: Eff es A

Can you give some examples (links to tutorials/documentation) on how these type-directed DI frameworks look in modern OOP languages?

I guess that is true, if Haskell had better type-level programming you could simply have a dictionary with a list of functions on the type-level, that would effectively be superior handle pattern. Alas, not today.

But the compiler cannot guarantee that getCar only does a database read at runtime. So the source of some pernicious bug still could be in getCar.

If ReadDB is a static effect whose interpreter only does database reads, then yes, the compiler does make that guarantee. One may say: “but what if the interpreter does some unsafePerformIO so it hides the fact that is also launches missiles?”. Well, that’s a fair objection – in practical terms the guarantee is not ironclad – but the objection also applies to Haskell as a whole: we have no truly ironclad guarantee that 1 + 1 doesn’t launch missiles either.

2 Likes

If ReadDB is a static effect whose interpreter only does database reads,

That interpreter is written by some library programmer, so it may not do what it says on the tin. Is it not a different level of guarantee to say a function that takes a [String] and returns a [String]?

Ultimately you’re looking for software verification techniques, security audits of the source code and other things like this. Type systems are only a small portion of static analysis, and we shouldn’t aim to guarantee every memory read at the type-level.

9 Likes

It’s not a different level of guarantee. The function [String] -> [String] would also written by some library programmer and could be this one:

import System.IO.Unsafe

myReverse :: [String] -> [String]
myReverse ss =
  case
    unsafePerformIO (putStrLn "The missiles have been launched. Oh dear.")
    of () -> reverse ss

-- ghci> myReverse ["A", "B", "C"]
-- The missiles have been launched. Oh dear.
-- ["C","B","A"]
1 Like

I’m not sure this discussion is leading anywhere. But bear in mind that the term “effect system” is IMO overloaded. There are at least 3 features an effect system (could) offer:

  1. Effect tracking: The framework helps tracking what kind of (most-often IO) capabilities a piece of code needs. This is a generalisation of the ReaderT IO/handle pattern with some additional type foo (ST-like use of higher-rank types) so that the types actually ensure that a use of a database connection cannot escape the lexical scope ot its handle.

  2. Effects as interfaces/(Dynamically-dispatched) effect handlers/probably some term I don’t know of that is established in literature: By building on an effect-tracking framework, one may ask

    • Does it really matter that reading from the database needs to be implemented in IO?
    • Isn’t that rather an implementation detail of the database implementation used in production?

    For example, it would be conceivable to handle database requests with a mocking implementation instead. This implementation would not need to run in IO at all.
    “Algebraic effects and handlers” refers to the technique were the particular implementation of a capability can be swapped out dynamically. The effect itself merely becomes an interface, given meaning by at least one concrete implementation, its handler.

  3. (Statically-dispatched) Handlers for common effects: Likewise by building on an effect-tracking framework, one could provide a toolbox of known-useful effects+handler implementations such as for exceptions, state and concurrency. It doesn’t make much sense for these to be implemented as dynamically-dispatched effects, because their implementation is morally pure anyway (no need to mock local state; just use the implementation). Hence these kinds of capabilities are statically dispatched, which means reliable performance.

Effect systems like effectful, bluefin enable all three of these features. In particular, even though their implementation is in terms of IO, the semantics of state, exception etc. are still pure, so it’s OK for their handler implementations to use unsafePerformIO under the hood to enable efficient implementations.

For users of one of these libraries, there are advantages to each of the 3 features. The first 2 features improve programming “in the large”, while the last feature is useful “in the small”.

  1. Effect-tracking (1) is very useful for the same reasons that a type system that tracks IO is generally useful. For example it can aid debugging in big applications: When a function’s type says it can access the database but not launch new processes, that is useful information when the problem you are investigating is related to spawning zombie processes, because the function’s implementation must be irrelevant.

    How granular you need to structure your effect domain depends on the use case and your taste. I certainly wouldn’t reach for effect-tracking if my entire program can be defined as main = interact foo (interact). However, I would certainly welcome if GHC’s code base were to be structured using more granular effects, because I have often wondered whether some particular IO-based function in a call stack of 10 is relevant to the problem I’m debugging. Saying “I don’t see the appeal in effect-tracking” likely means that your IO-layer isn’t complex to warrant effect-tracking, and that’s fine. It does not mean that effect systems are useless, IMO.

  2. Effect handlers (2) are useful for mocking production implementations in unit tests. Yes, there are other means to achieve mocking. But effect handlers make it particualrly convenient to define and implement new effects, while retaining acceptable performance. Effect handlers are basically the evolution of dialogue-based APIs that @atravers keeps bringing up, as evidenced by @jaror in Dialogues vs continuations (and algebraic effects) to implement I/O. Whether you pick continuations (the mother of all monads) or implement a monad with continuations to sequence effects is IMO a bit beside the point.

    As others such as @osa1 and @danidiaz have implied, there is a deep connection to dependency injection (DI). The job of a DI framework such as autofac is to construct instances of a class (I’ll stay with C# lingo here because that’s where I know it from). Every class specifies interfaces such as IDatabase it needs access to (commonly via constructor parameters), and the job of the DI framework is to resolve these interfaces to their proper implementation (such as MySqlDatabase) upon constructing the class via reflection. Which interface gets resolved to what implementation is specified at one central location: The registry (hence I suppose the name for the Haskell DI library).
    Defining a handler can be seen as registering an implementation in a DI container, which subsequently resolves every use of that effect with said handler. I think one fundamental difference to DI containers is that handlers have a builtin notion of scope, whereas that counts as an advanced use of DI frameworks. Yet, I would guess that you could probably implement a useful DI framework on top of bluefin or effectful.

  3. An effect toolbox (3) is pretty handy, locally, in the small. For example, it is useful to have efficient exceptions. Additionally, I have the guarantee that the effects in the toolbox work well together; the interaction of state, exceptions and concurrency is just as one would expect. Furthermore, these effects can all eliminated in pure code! Thus, use of the toolbox does not even need to show in any exported type signature.

    Some anecdotal evidence wrt. efficiency and exceptions:

    I recently have reviewed a function that was basically applying escapes to a string, escape :: String -> Either Error String. This function should return Left err when there was an error during escape resolution. It would be prohibitively expensive to implement this function in terms of Either, though, because it means that every call of the recursive worker function would need to implement a Right upon returning. It would be far more efficient to implement this function using unsafePerformIO and throwIO+catch, allocating Right/Left only upon exiting the function. The resulting function was still pure, but I felt bad for the use of unsafePerformIO. Using bluefin in such a scenario would yield just the same implementation, but without needing to justify unsafePerformIO in my code.

Summary

To summarise my understanding, I would pick an effect library such as effectful or bluefin if

  1. I want to implement a function using exceptions, early return and/or state, because such formulations can be clearer than applicative encodings (see also ‘do’ unchained for examples). Then the effect toolbox (3) is useful.
  2. I have (or expect to be having) an IO-heavy code base where I have difficulty to debug the source of faulty behavior of a pervasively used side-effect such as interacting with a database. Then the effect-tracking feature is useful.
  3. I want to unit-test such a complex IO layer, so I need to be able to mock out application domains. One way to achieve this is by decoupling application domains into effects with dynamically specified handlers. In particular, if I use bluefin or effectful for effect-tracking anyway, it should be a pretty cheap transition to use it for mocking and dependency injection as well.
13 Likes

If you only have Tagged.Connection e then you’re probably using a system where someone is providing a safe API. Naturally, you can’t convert it safely to Untagged.Connection, just like you can’t safely convert IO a to a. Of course, one can provide workarounds, such as

unsafeUntag :: Tagged.Connection e -> Untagged.Connection

or

unsafePerformIO :: IO a -> a

Indeed that’s exactly what I do in Bluefin.System.IO to allow converting between a tagged Handle and an untagged Handle (unsafeWithHandle).

No doubt this could be made more ergonomic (for example by providing a Bluefin-standard tagging type, like

data BluefinTag a e = UnsafeMkBluefinTag a

Ultimately, I don’t see this as any more challenging than converting between a and IO a, or between Aeson.Value and SomeOtherLibrary.Json etc., etc… It’s all standard fare.

Yes, I agree. I would say that the only ones that are truly “production ready” are the IO-based ones (e.g. naked IO, ReaderT IO/RIO, effectful, Bluefin). But none of them are experimental. I’m confident that there are no “gotchas” with them that are not already understood.

I agree with that. I think newbies should be allowed to feel comfortable using IO before even trying transformers or mtl. In fact, I’d suggest they skip both of those and graduate to RIO/ReaderT IO, and if and when they need extra safety, then switch to Bluefin or effectful. However, given that most people learn Haskell through university (I believe) they will most likely be exposed to monad transformers first, since there is some long theoretical history behind them.

Well, I also don’t see a future for Haskell without effect systems. We need a lightweight way to get the best of both worlds: predictable performance/resource safety whilst also allowing us to locally run effects in a way that is invisible from the outside. So far that is only provided by Bluefin and effectful.

Bluefin and effectful also have that guarantee for their local effects.

I don’t understand this. It should be trivial, barring simple adaptor functions. Do you have any other examples besides the Tagged/Untagged.Connection above, which, whilst certainly requiring non-zero effect I still consider trivial.

Have you actually tried it? Again, this really should be trivial. If you’re having particular problems with it then please let me know the details and I’m happy to help out.

3 Likes

Then the point is, if we had type IO a = Eff All a that would not be a problem? Less of a problem? But, IMO, this is such a remote solution to a problem that doesn’t exist yet that I honestly just don’t care.

I’d just like to unpack “large applications that has to use multiple effect systems (in libraries)”.

If it is an application, then I’d prefer it to use a zero or one effect system. That is a choice, and nothing is impossible about it.

Multiple effect systems (in libraries) is what I don’t get, though.

  1. You might be using a library, that uses an effect system, and you wouldn’t know, without consulting the source code.
foo :: IO ()
foo = runEff . runSacrificeKitten . runStealCandy . ...
  1. A Library that, for some reason, exposes API with effects.
foo :: (Party :> es) => Eff es ()

You can adapt it

myFoo :: IO ()
myFoo = runEff . runParty foo

or use something else.

  1. A library that is made for a specific effect system and integrates with its ecosystem well.
foo :: (Log :> es, FooE :> es) => Eff es ()

Still adaptable, but might not be worth it. If it is critical for you, and you can’t use anything else, maybe adopt its effect system for your whole app. Or fork it. Or something. But this example is pushing it, there are a handful or something-effectful libs on Hackage, and most of them are wrappers.

  1. A framework, making you write your code in some effect system. Well, it’s a framework, it’s what they do. Use another.

So 1 and 2 are just like using a library today. 3 is in “oh, well” territory and might never materialize as a problem. 4 is a legit use case, and nothing we can do about it.

I’m afraid I’d need an example of what is a concern here.

2 Likes

This thread has become quite a mess! Hopefully my perspective aligns with some others and is clear enough to help resolve some of the cyclic arguments in seeing here rather than increasing the chaos, but let’s be honest, it’s really just that I can’t keep my mouth shut.

In short, the main reason I am not interested in effect systems is that I don’t feel inclined, as some seem to be, to use effects throughout my programs. I make a thin, effectful “crust” around a thick, pure “mantle”, which in turn surrounds a small “core” of primitives that are benignly effectful. There are two places, therefore, where an effect system is potentially useful. The primitive core is not a great candidate because I intend to pretend the effects aren’t there in the first place. The real-world-facing crust is also not a great candidate because I intend for it to be trivial, so there just aren’t any problems I have with IO that are addressed by restricting myself to subsets of its effects.

In my programs, the crust calls into the mantle, and the mantle calls into the core. The mindset of an effect system appears to be that it allows you to dig “tunnels” from the crust into the mantle, allowing the mantle to effectively call into the crust. To me, that’s more of a contamination than a feature. I realize I am probably misrepresenting this perspective, as it is not coming from the need to inject effects into pure code so much as from an apparent need to control otherwise out-of-control effects in a thick or vaguely defined crust. I essentially don’t track them; I only use the IO type constructor as a way of showing that I am not in the pure mantle of my program. But the other perspective is that effects are pragmatic and/or inevitable and therefore should not be considered as so gross; but they are kind of gross, so best to carefully “track” them so that they can be used pervasively without becoming as crazy.

Consistent with my perspective, I don’t see effect systems and transformers as alternatives to each other at all. MTL is perhaps intended to be used this way, but not monad transformers in general. I use transformers to build abstractions, not to visibly combine effects and expose them in the interface.

5 Likes

Yes:


Yes!

If an effect system ever matured to the point of being capable of replacing the current (and infamous!) definition of IO a, based on nothing at all State# RealWorld, then future Haskell educators and programmers would no longer have to “play effect-system roulette” :

…because just like you:

future Haskell educators and programmers would also prefer to have only one effect system to teach and use. So do you care now?


Libraries can depend on other libraries, which can depend on yet more libraries…with each and every library potentially using a different effect system (worst-case scenario):

So again:

That’s a good attitude to have, as the tide of parallelism continues to rise - you’ll have less code to “decontaminate” in a future parallel-by-default Haskell.

I’m sure you didn’t intend it this way, but that could be interpreted as criticism as those who have been participating in this thread. I personally have obtained a lot of insight from this thread and I’m grateful to everyone who has contributed their thoughts.

In any case, I find your contribution very interesting too, thanks! I wonder if you have any examples that you can share. In particular, I don’t understand what “benignly effectful” primitives are.

3 Likes

I absolutely did not mean it as criticism of anybody, so thank you for bringing it up. I think the state of this thread is messy only because people are having difficulty understanding each other’s differing values, not because anyone is doing anything wrong.

I am calling most code that in practice uses unsafePerformIO to hide underlying IO “benign” in the sense that it is almost never intended to have observably impure behavior outside its API boundary. It’s an impure implementation for pure semantics. The prototypical example would be ST, but maybe a more helpful example, since you wouldn’t normally implement ST yourself, would be something like using effects to implement memoization for pure functions.

2 Likes

I’ve seen those “benign effects” mentioned before:

(with Std ML examples of exact real-number integration and search algorithms available in When is a functional program not a functional program?). So if an effect system were to ever mature to the point of being a substitute for IO a:

type IO a = Eff All a

main :: Eff All ()  {- foreign export ... "hs_rts_Main_main" main :: Eff All () -}

foreign ... thisNewEffect :: ... -> Eff All ()

there will probably be a need for:

unsafe...Eff :: Eff es a -> a 

(…or something/s like it).


But Haskell is only one pure functional language, with Single-Assignment C being another (albeit first-order and strict); this being from a research article about that language:

…with the source of that chaos being non-deterministic side effects in I/O. It looks like the proverbial “recipe for disaster”, but the designers of SAC actually use that nondeterminism to achieve a simple form of concurrent programming:

And all this without any of the type-level chaos which seems so prevalent in the current batch of effect systems:

Browse and search packages | Hackage (effect system (deprecated:false))

So If the technique used by SAC’s designers can control and use nondeterminism (the ultimate I/O effect?) in a pure (strict first-order) functional language, perhaps that technique can be reused in Haskell to temper the other effects of I/O, with its abundance of “sequentialising” abstract interfaces - monadic, arrow, comonadic, etc…and could even reduce the need for ugliness like unsafe...Eff :: Eff [...] a -> a .

I’ve never used any effect systems unless mtl counts, but I think I understand the appeal. Of course we try to make stuff pure as much as possible. But for some domains we fail, so we put in IO. And of course we try to make that a simple shell, but for some domains, we fail at that too. Sometimes I fail immediately, and the entire program is a tangle of interleaved IO actions. There may be a better way to organize it, but I’m not smart enough or don’t have enough time to think of it. It depends on the domain, I’ve done one large program which is almost entirely pure, and other large programs which are almost entirely in IO. I didn’t get dumber (I hope!) in between so it must be the domain. Of course I would like to not do IO or do a thin IO layer but regardless of my inclination there are many domains where I’m simply not smart enough for that. If I had only ever worked in the easily-pure domain of the first program, I wouldn’t understand the need for fancy IO categorization.

But maybe the tangle of interleaved IO is not so interleaved when it comes to what kind of IO. Giving up power is usually the key. So I can understand if you have lots of IO then it’s a useful extra tool to be able to slice them by capability. I do the same with pure mtl stuff, it’s fantastic that I can have whole sections which can’t fail (because return value not Either), or such and such state isn’t available (because State not passed in), and I know that from the type signature of the entry point to the system. Why wouldn’t the same be useful for IO exceptions and filesystem and network access? I treat all IO as if it will throw, but that’s basically all down to filesystem which does pervasively as basic design, IORefs won’t do that, and MVars and STM at least not intentionally. It would be neat to know that. I have definitely had production stuff crash because something did filesystem where it didn’t used to, and thus throws an exception from what previously wouldn’t.

I’ve also passed in the record of IO actions to mock out stuff, and it’s ok in the small but I can see it getting messy if it’s all done by hand. I also often use a real filesystem or dummy db or whatever and just like the other ideals it’s great until we fail at it, and now what? At that point I often don’t write tests and see what happens in production, and that’s actually the right choice in many domains, but when it’s not I’d like another option.

Yes I expect there’s a chance you won’t be able to seamlessly use the high level interface of some library because they chose a different effect system and expose that in the API. Library authors can do that. If you’re paying them, ask them to expose a lower level API, or use your system. Chances are greater that they chose an entirely different language and and even if you are paying them they still may not care about your taste in effect systems let alone languages, and you will write a C adaptor. But, I haven’t had any cases where some library used an effect system so I couldn’t use it. I’ve had more cases where it simply didn’t export some internal thing I want (for both haskell and C!), some because good reasons some because oversight. Or its put something into IO gratuitously when it should have been pure and you can’t just unsafePerformIO because it also throws (unexported!) IO exceptions as part of its interface, that’s sort of an incompatible effect system decision right there. So submit a patch upstream, and fork the library anyway because they may be permanently AFK. Anyway it’s just to say it seems like an incompatible grain on the incompatible beach, and far from the biggest.

I also used to not understand the point of streaming libraries “why not just lazy lists.” Lazy lists worked well for the first 15 years or so! But then I moved to a domain where there were little bits of IO scattered throughout the pipeline, and now streaming became a useful way to find a structured spot in between pure functions and lists and callbacks, IORefs, and Chans everywhere.

Anyway that was my thoughts reading (skimming!) the thread. It rephrases some things others have said, and doesn’t contribute to what I see is the more interesting discussion beyond the “why at all”, namely what specific thing would be better or worse in which effect system, and why, because that gets at when do they help or hurt and when to try one.

1 Like