Algebraic Effects?

I picked up Haskell fairly recently, as a "better imperative programming language" to implement highly concurrent code to survey DNSSEC and DANE adoption on the Internet. The results are great, I got a DNS library, network and TLS stack that provide effortless concurrency, and a decent interface to Postgres in the form of the Hasql package and performance is excellent. But I'm still a novice in functional programming, with much to learn. So it is only this week that I've started to read about Algebraic effects, and I curious how the Haskell community views these nowadays. If this is a toxic topic raised by newbies who should just Google past discussions instead, feel free to say so... Does the below thread still sum up the situation: https://www.reddit.com/r/haskell/comments/3nkv2a/why_dont_we_use_effect_hand... I see Haskell now also has an Eff monad. Is it widely used? Efficient? Are there other Haskell libraries that build on it as a foundation? One potential advantage that comes to mind with Effects is that the exceptions raised by a computation can enter its signature and it becomes less likely that a library will leak unexpected exception types from its dependencies to its callers if the expected exceptions are explicit in the signatures and checked by the type system. For example, a while back the Haskell Network.DNS library leaked exceptions from a parser library that was an internal implementation detail, and my code had rare crashes on malformed DNS packets, since I did not expect or handle that exception. -- Viktor.

You can certainly create a new type signature for things that can fail with error or undefined, but keep in mind that the *real* logical bottom, viz. infinite recursion, is still there. I know that Idris and ATS both have some mechanism for checking for non-termination (and in the case of ATS, it is dealt with as an algebraic effect I believe), but GHC would not truly be able to eliminate bottoms without writing an extension yourself. In the case of the bug you mentioned I'd guess it's just API stability/the Haskell ecosystem. I believe error and undefined are in the Haskell2010 report so I doubt they're going to stop causing pain anytime soon :) On 09/17/2018 08:15 PM, Viktor Dukhovni wrote:
I picked up Haskell fairly recently, as a "better imperative programming language" to implement highly concurrent code to survey DNSSEC and DANE adoption on the Internet. The results are great, I got a DNS library, network and TLS stack that provide effortless concurrency, and a decent interface to Postgres in the form of the Hasql package and performance is excellent.
But I'm still a novice in functional programming, with much to learn. So it is only this week that I've started to read about Algebraic effects, and I curious how the Haskell community views these nowadays.
If this is a toxic topic raised by newbies who should just Google past discussions instead, feel free to say so...
Does the below thread still sum up the situation:
https://www.reddit.com/r/haskell/comments/3nkv2a/why_dont_we_use_effect_hand...
I see Haskell now also has an Eff monad. Is it widely used? Efficient? Are there other Haskell libraries that build on it as a foundation?
One potential advantage that comes to mind with Effects is that the exceptions raised by a computation can enter its signature and it becomes less likely that a library will leak unexpected exception types from its dependencies to its callers if the expected exceptions are explicit in the signatures and checked by the type system.
For example, a while back the Haskell Network.DNS library leaked exceptions from a parser library that was an internal implementation detail, and my code had rare crashes on malformed DNS packets, since I did not expect or handle that exception.
-- *Vanessa McHale* Functional Compiler Engineer | Chicago, IL Website: www.iohk.io http://iohk.io Twitter: @vamchale PGP Key ID: 4209B7B5 Input Output http://iohk.io Twitter https://twitter.com/InputOutputHK Github https://github.com/input-output-hk LinkedIn https://www.linkedin.com/company/input-output-global This e-mail and any file transmitted with it are confidential and intended solely for the use of the recipient(s) to whom it is addressed. Dissemination, distribution, and/or copying of the transmission by anyone other than the intended recipient(s) is prohibited. If you have received this transmission in error please notify IOHK immediately and delete it from your system. E-mail transmissions cannot be guaranteed to be secure or error free. We do not accept liability for any loss, damage, or error arising from this transmission

On Sep 17, 2018, at 10:57 PM, Vanessa McHale
wrote: You can certainly create a new type signature for things that can fail with error or undefined, but keep in mind that the *real* logical bottom, viz. infinite recursion, is still there. I know that Idris and ATS both have some mechanism for checking for non-termination (and in the case of ATS, it is dealt with as an algebraic effect I believe), but GHC would not truly be able to eliminate bottoms without writing an extension yourself.
Given the novelty (to me) of Algebraic Effects, my question was intended to be broader than just whether they could help expose exception signatures. Are they likely to play a larger role in Haskell? Are they sufficiently simpler to reason about or use than monads to warrant thinking in terms of Effects instead in some/many cases?
In the case of the bug you mentioned I'd guess it's just API stability/the Haskell ecosystem. I believe error and undefined are in the Haskell2010 report so I doubt they're going to stop causing pain anytime soon :)
Yes, of course, but I would still like to see libraries convert exceptions in underlying dependencies to something that might make sense to the caller of the library. Thus, (with no prejudice against the Network.DNS library, it just happens a core library in my project) I'd have expected the DNS library to return a some DNS-specific exception (malformed packet, ...) rather than an error from Attoparsec. And indeed this has been addressed. So that was just one possible advantage, but it seems the real win is supposed to be the ability to construct and compose lots of seemingly different primitives out of Effects (generators, concurrency, exceptions, state, ...). And so I am curious whether Haskell is likely some day to adopt and use Effects in some essential way, or whether they will remain a feature of peripheral libraries. Effects appear to be marketed as simpler to learn/use and to offer greater modularity than monads and monad transformers. Do they deliver on these promises, especially in larger projects? -- Viktor.

I think this is a good question. It is one that I investigated in detail about a year ago. Here is a brief summary of my findings: - Haskell programmers want to compose effects, but they usually express effects with monads (e.g. Reader, State, Except), and monads don’t, in general, compose. Therefore, monad transformers were born. However, monad transformers have a new problem, which is an inability to parameterize a function over the exact set of effects in an overall computation. Therefore, mtl style was born. - In recent years, extensible effects libraries have proposed a compelling, less ad-hoc approach to effect composition than mtl style, but mtl style remains by far the most dominant approach to effect composition in Haskell libraries. - In Haskell, extensible effects libraries are historically based on either free monads[1] or “freer” monads[2]. The latter approach is newer, provides a nicer API (though that is admittedly subjective), and is faster due to some clever implementation tricks. However, even freer-based EE libraries are significantly slower than mtl style because the way effect handlers are implemented as ordinary functions defeats the inliner in ways mtl style does not. That said, this cost is in (>>=), which I find is often (usually?) insignificant compared to other costs, so while mtl spanks EE in microbenchmarks, I did not find a meaningful performance difference between mtl style and freer-based EE in real-world applications. - In my personal experience (with an admittedly very small sample size), novice Haskellers find defining new effects with the freer-simple EE library monumentally easier than with mtl style, the latter of which requires a deep understanding of monad transformers, mtl “lifting instances”, and things like newtype deriving or default signatures. (More on freer-simple later.) - The ecosystem of EE libraries is a mess. There are extensible-effects, freer, freer-effects, freer-simple, and others. As far as I can tell, extensible-effects is based on free monads, and freer and freer-effects are both unmaintained. My recommendation: if the performance of using EE is acceptable in your application AND you are willing to pay the cost of less ecosystem support (which in practice means needing to write adapters to mtl style libraries and having access to less documentation), I would strongly recommend the freer-simple extensible effect library. MASSIVE DISCLAIMER: I am the author and maintainer of freer-simple! However, I have a few reasons to believe I am not wholly biased: 1. I developed freer-simple only after using mtl style in production applications for nearly two years and thoroughly investigating the EE landscape. 2. I actually compared and contrasted, in practice, the difference in understanding between teaching mtl style, other EE libraries, and freer-simple to Haskell novices. 3. I have a number of satisfied customers.[3][4] The distinguishing features of freer-simple are better documentation and a dramatically different (and hopefully easier to understand) API for defining new effects compared to other extensible effects libraries. For details, see the freer-simple module documentation on Hackage here: https://hackage.haskell.org/package/freer-simple/docs/Control-Monad-Freer.ht... If you have any further questions, I’m happy to answer them, but this email is long enough already! Hopefully it isn’t too overwhelming. Alexis [1]: http://okmij.org/ftp/Haskell/extensible/exteff.pdf [2]: http://okmij.org/ftp/Haskell/extensible/more.pdf [3]: https://twitter.com/rob_rix/status/1034860773808459777 [4]: https://twitter.com/importantshock/status/1035989288708657153
On Sep 17, 2018, at 20:15, Viktor Dukhovni
wrote: I picked up Haskell fairly recently, as a "better imperative programming language" to implement highly concurrent code to survey DNSSEC and DANE adoption on the Internet. The results are great, I got a DNS library, network and TLS stack that provide effortless concurrency, and a decent interface to Postgres in the form of the Hasql package and performance is excellent.
But I'm still a novice in functional programming, with much to learn. So it is only this week that I've started to read about Algebraic effects, and I curious how the Haskell community views these nowadays.
If this is a toxic topic raised by newbies who should just Google past discussions instead, feel free to say so...
Does the below thread still sum up the situation:
https://www.reddit.com/r/haskell/comments/3nkv2a/why_dont_we_use_effect_hand...
I see Haskell now also has an Eff monad. Is it widely used? Efficient? Are there other Haskell libraries that build on it as a foundation?
One potential advantage that comes to mind with Effects is that the exceptions raised by a computation can enter its signature and it becomes less likely that a library will leak unexpected exception types from its dependencies to its callers if the expected exceptions are explicit in the signatures and checked by the type system.
For example, a while back the Haskell Network.DNS library leaked exceptions from a parser library that was an internal implementation detail, and my code had rare crashes on malformed DNS packets, since I did not expect or handle that exception.
-- Viktor.

Have distributive laws [1] ever been used for monad composition in Haskell? After all, two monads with a distributive law compose. Till [1] https://ncatlab.org/nlab/show/distributive+law Am 18.09.2018 um 08:06 schrieb Alexis King:
I think this is a good question. It is one that I investigated in detail about a year ago. Here is a brief summary of my findings:
- Haskell programmers want to compose effects, but they usually express effects with monads (e.g. Reader, State, Except), and monads don’t, in general, compose. Therefore, monad transformers were born. However, monad transformers have a new problem, which is an inability to parameterize a function over the exact set of effects in an overall computation. Therefore, mtl style was born.
- In recent years, extensible effects libraries have proposed a compelling, less ad-hoc approach to effect composition than mtl style, but mtl style remains by far the most dominant approach to effect composition in Haskell libraries.
- In Haskell, extensible effects libraries are historically based on either free monads[1] or “freer” monads[2]. The latter approach is newer, provides a nicer API (though that is admittedly subjective), and is faster due to some clever implementation tricks. However, even freer-based EE libraries are significantly slower than mtl style because the way effect handlers are implemented as ordinary functions defeats the inliner in ways mtl style does not.
That said, this cost is in (>>=), which I find is often (usually?) insignificant compared to other costs, so while mtl spanks EE in microbenchmarks, I did not find a meaningful performance difference between mtl style and freer-based EE in real-world applications.
- In my personal experience (with an admittedly very small sample size), novice Haskellers find defining new effects with the freer-simple EE library monumentally easier than with mtl style, the latter of which requires a deep understanding of monad transformers, mtl “lifting instances”, and things like newtype deriving or default signatures. (More on freer-simple later.)
- The ecosystem of EE libraries is a mess. There are extensible-effects, freer, freer-effects, freer-simple, and others. As far as I can tell, extensible-effects is based on free monads, and freer and freer-effects are both unmaintained.
My recommendation: if the performance of using EE is acceptable in your application AND you are willing to pay the cost of less ecosystem support (which in practice means needing to write adapters to mtl style libraries and having access to less documentation), I would strongly recommend the freer-simple extensible effect library. MASSIVE DISCLAIMER: I am the author and maintainer of freer-simple! However, I have a few reasons to believe I am not wholly biased:
1. I developed freer-simple only after using mtl style in production applications for nearly two years and thoroughly investigating the EE landscape.
2. I actually compared and contrasted, in practice, the difference in understanding between teaching mtl style, other EE libraries, and freer-simple to Haskell novices.
3. I have a number of satisfied customers.[3][4]
The distinguishing features of freer-simple are better documentation and a dramatically different (and hopefully easier to understand) API for defining new effects compared to other extensible effects libraries. For details, see the freer-simple module documentation on Hackage here:
https://hackage.haskell.org/package/freer-simple/docs/Control-Monad-Freer.ht...
If you have any further questions, I’m happy to answer them, but this email is long enough already! Hopefully it isn’t too overwhelming.
Alexis
[1]: http://okmij.org/ftp/Haskell/extensible/exteff.pdf [2]: http://okmij.org/ftp/Haskell/extensible/more.pdf [3]: https://twitter.com/rob_rix/status/1034860773808459777 [4]: https://twitter.com/importantshock/status/1035989288708657153
On Sep 17, 2018, at 20:15, Viktor Dukhovni
wrote: I picked up Haskell fairly recently, as a "better imperative programming language" to implement highly concurrent code to survey DNSSEC and DANE adoption on the Internet. The results are great, I got a DNS library, network and TLS stack that provide effortless concurrency, and a decent interface to Postgres in the form of the Hasql package and performance is excellent.
But I'm still a novice in functional programming, with much to learn. So it is only this week that I've started to read about Algebraic effects, and I curious how the Haskell community views these nowadays.
If this is a toxic topic raised by newbies who should just Google past discussions instead, feel free to say so...
Does the below thread still sum up the situation:
https://www.reddit.com/r/haskell/comments/3nkv2a/why_dont_we_use_effect_hand...
I see Haskell now also has an Eff monad. Is it widely used? Efficient? Are there other Haskell libraries that build on it as a foundation?
One potential advantage that comes to mind with Effects is that the exceptions raised by a computation can enter its signature and it becomes less likely that a library will leak unexpected exception types from its dependencies to its callers if the expected exceptions are explicit in the signatures and checked by the type system.
For example, a while back the Haskell Network.DNS library leaked exceptions from a parser library that was an internal implementation detail, and my code had rare crashes on malformed DNS packets, since I did not expect or handle that exception.
-- Viktor.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

The only monads with distributive laws are in Data.Distributive, and
they're all isomorphic to (->) e for some e. So that's effectively
ReaderT.
On Tue, Sep 18, 2018 at 5:06 AM, Till Mossakowski
Have distributive laws [1] ever been used for monad composition in Haskell? After all, two monads with a distributive law compose.
Till
[1] https://ncatlab.org/nlab/show/distributive+law
Am 18.09.2018 um 08:06 schrieb Alexis King:
I think this is a good question. It is one that I investigated in detail about a year ago. Here is a brief summary of my findings:
- Haskell programmers want to compose effects, but they usually express effects with monads (e.g. Reader, State, Except), and monads don’t, in general, compose. Therefore, monad transformers were born. However, monad transformers have a new problem, which is an inability to parameterize a function over the exact set of effects in an overall computation. Therefore, mtl style was born.
- In recent years, extensible effects libraries have proposed a compelling, less ad-hoc approach to effect composition than mtl style, but mtl style remains by far the most dominant approach to effect composition in Haskell libraries.
- In Haskell, extensible effects libraries are historically based on either free monads[1] or “freer” monads[2]. The latter approach is newer, provides a nicer API (though that is admittedly subjective), and is faster due to some clever implementation tricks. However, even freer-based EE libraries are significantly slower than mtl style because the way effect handlers are implemented as ordinary functions defeats the inliner in ways mtl style does not.
That said, this cost is in (>>=), which I find is often (usually?) insignificant compared to other costs, so while mtl spanks EE in microbenchmarks, I did not find a meaningful performance difference between mtl style and freer-based EE in real-world applications.
- In my personal experience (with an admittedly very small sample size), novice Haskellers find defining new effects with the freer-simple EE library monumentally easier than with mtl style, the latter of which requires a deep understanding of monad transformers, mtl “lifting instances”, and things like newtype deriving or default signatures. (More on freer-simple later.)
- The ecosystem of EE libraries is a mess. There are extensible-effects, freer, freer-effects, freer-simple, and others. As far as I can tell, extensible-effects is based on free monads, and freer and freer-effects are both unmaintained.
My recommendation: if the performance of using EE is acceptable in your application AND you are willing to pay the cost of less ecosystem support (which in practice means needing to write adapters to mtl style libraries and having access to less documentation), I would strongly recommend the freer-simple extensible effect library. MASSIVE DISCLAIMER: I am the author and maintainer of freer-simple! However, I have a few reasons to believe I am not wholly biased:
1. I developed freer-simple only after using mtl style in production applications for nearly two years and thoroughly investigating the EE landscape.
2. I actually compared and contrasted, in practice, the difference in understanding between teaching mtl style, other EE libraries, and freer-simple to Haskell novices.
3. I have a number of satisfied customers.[3][4]
The distinguishing features of freer-simple are better documentation and a dramatically different (and hopefully easier to understand) API for defining new effects compared to other extensible effects libraries. For details, see the freer-simple module documentation on Hackage here:
https://hackage.haskell.org/package/freer-simple/docs/Control-Monad-Freer.ht...
If you have any further questions, I’m happy to answer them, but this email is long enough already! Hopefully it isn’t too overwhelming.
Alexis
[1]: http://okmij.org/ftp/Haskell/extensible/exteff.pdf [2]: http://okmij.org/ftp/Haskell/extensible/more.pdf [3]: https://twitter.com/rob_rix/status/1034860773808459777 [4]: https://twitter.com/importantshock/status/1035989288708657153
On Sep 17, 2018, at 20:15, Viktor Dukhovni
wrote: I picked up Haskell fairly recently, as a "better imperative programming language" to implement highly concurrent code to survey DNSSEC and DANE adoption on the Internet. The results are great, I got a DNS library, network and TLS stack that provide effortless concurrency, and a decent interface to Postgres in the form of the Hasql package and performance is excellent.
But I'm still a novice in functional programming, with much to learn. So it is only this week that I've started to read about Algebraic effects, and I curious how the Haskell community views these nowadays.
If this is a toxic topic raised by newbies who should just Google past discussions instead, feel free to say so...
Does the below thread still sum up the situation:
https://www.reddit.com/r/haskell/comments/3nkv2a/why_dont_we_use_effect_hand...
I see Haskell now also has an Eff monad. Is it widely used? Efficient? Are there other Haskell libraries that build on it as a foundation?
One potential advantage that comes to mind with Effects is that the exceptions raised by a computation can enter its signature and it becomes less likely that a library will leak unexpected exception types from its dependencies to its callers if the expected exceptions are explicit in the signatures and checked by the type system.
For example, a while back the Haskell Network.DNS library leaked exceptions from a parser library that was an internal implementation detail, and my code had rare crashes on malformed DNS packets, since I did not expect or handle that exception.
-- Viktor.
Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Sep 18, 2018, at 2:06 AM, Alexis King
wrote: - The ecosystem of EE libraries is a mess.
Yes, it is rather unclear to me whether exploring any of these is is worth the effort, if so which, or how to use them given sometimes scant documentation.
There are extensible-effects, freer, freer-effects, freer-simple, and others. As far as I can tell, extensible-effects is based on free monads, and freer and freer-effects are both unmaintained.
I took a quick look at: https://hackage.haskell.org/package/extensible-0.4.10. The author claims good performance: https://www.schoolofhaskell.com/user/fumieval/extensible/the-world-s-fastest... I've not tried any benchmarks or yet any non-trivial code using this library. The documentation is rather minimal, but I got the below to compile and run: {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} module Main where import Control.Monad.Reader (ask) import Control.Monad.State (get, put) import Control.Monad.Writer (tell) import Control.Monad.IO.Class (liftIO) import Data.Monoid (Sum(..)) import Data.Extensible import Data.Extensible.Effect.Default type IOeff = "IO" :> IO type KitchenSink a = Eff '[ReaderDef Int, StateDef Int, WriterDef (Sum Int), IOeff] a type JustIO a = Eff '[IOeff] a type Result a = ((a, Int), Sum Int) handler :: KitchenSink a -> JustIO (Result a) handler = runWriterDef . flip runStateDef 3 . flip runReaderDef 5 main :: IO () main = do x <- retractEff $ handler $ do liftIO $ putStrLn "running" s <- get r <- ask tell (Sum s) tell (Sum $ s + 1) put $! s + r return $ "magic" print x it outputs: running (("magic",8),Sum {getSum = 7}) With this library, at least when building effects out of mtl transformers, the order of the effects in the Eff type declaration has to match in reverse order the composition of the "runFooDef" functions. That is, the types: Eff '[ReaderDef r, StateDef s] and Eff '[StateDef s, ReaderDef r] are not the same. Perhaps this is a feature?
My recommendation: if the performance of using EE is acceptable in your application AND you are willing to pay the cost of less ecosystem support (which in practice means needing to write adapters to mtl style libraries and having access to less documentation), I would strongly recommend the freer-simple extensible effect library. MASSIVE DISCLAIMER: I am the author and maintainer of freer-simple! However, I have a few reasons to believe I am not wholly biased:
Thanks. I'll take a look. Any comments on similarities to or differences from the "extensible" package above?
The distinguishing features of freer-simple are better documentation
Barring major downsides, that's a compelling difference.
and a dramatically different (and hopefully easier to understand) API for defining new effects compared to other extensible effects libraries. For details, see the freer-simple module documentation on Hackage here:
https://hackage.haskell.org/package/freer-simple/docs/Control-Monad-Freer.ht...
If you have any further questions, I’m happy to answer them, but this email is long enough already! Hopefully it isn’t too overwhelming.
Much appreciated. Still trying to figure out whether to look into this further. My project runs a concurrent computation for many hours, allocating and freeing terabytes of memory over its lifetime: 5,019,533,368,664 bytes allocated in the heap 162,945,132,824 bytes copied during GC 73,229,680 bytes maximum residency (3421 sample(s)) 4,150,592 bytes maximum slop 356 MB total memory in use (83 MB lost due to fragmentation) One concern for me is whether using Effects is likely to cause more allocations and work for the GC, or is the memory pressure about the same? -- Viktor.

On Sep 18, 2018, at 10:49, Viktor Dukhovni
wrote: I took a quick look at:
https://hackage.haskell.org/package/extensible-0.4.10.
The author claims good performance:
https://www.schoolofhaskell.com/user/fumieval/extensible/the-world-s-fastest...
That’s an interesting post. I am not totally sure why precisely it would be faster than freer/freer-effects/freer-simple, but it’s worth looking into to see if its optimizations can be incorporated into freer-simple. In any case, it seems like it’s “only” faster by a factor of ~2x, while the difference in performance between mtl and extensible is a factor of ~12x, so the difference is not massive. Still, it’s worth investigating.
With this library, at least when building effects out of mtl transformers, the order of the effects in the Eff type declaration has to match in reverse order the composition of the "runFooDef" functions. That is, the types:
Eff '[ReaderDef r, StateDef s] and Eff '[StateDef s, ReaderDef r]
are not the same. Perhaps this is a feature?
Generally, when working with extensible effect frameworks, you do not work with concrete lists of effects, since those two types are indeed different. Instead, you write functions polymorphic over the set of effects, and you include constraints on what must be somewhere in the list. Therefore, you’d express your example like this in freer-simple: Members '[Reader r, State s] effs => Eff effs a This constraint expresses that `Reader r` and `State s` must both exist somewhere in the list of effects `eff`, but it doesn’t matter where they are or what order they’re in. You only pick a concrete set of effects when finally running them. In a sense, this is similar, but not quite equivalent to, the difference between using transformers directly and using mtl typeclasses. Specifically, I mean the difference between these three types: ReaderT r (State s) a StateT s (Reader r) a (MonadReader r m, MonadState s m) => m a The first two specify a concrete transformer stack, which specifies both the order of the transformers and the whole contents of the stack. The mtl classes parameterize over the precise transformer stack, which enables easier composition. However, in a sense, a use of Eff with a concrete list is sort of in between these two types — since each effect can still be handled with an arbitrary effect handler, a concrete list enforces effect order relative to other effects, but it doesn’t enforce which handler must be used to handle each effect. The relationship between those things is largely unimportant when actually using extensible effects, however. Just use the `Member` or `Members` constraints instead of specifying a concrete list, and you’ll be alright.
Thanks. I'll take a look. Any comments on similarities to or differences from the "extensible" package above?
I am not intimately familiar with the extensible package, but it has a much broader scope than simply implementing an extensible effects library: it also implements open records/sums, and a whole bunch of other things (of, in my opinion, questionable usefulness). As for a comparison between exclusively the effects subset of extensible and freer-simple, extensible seems to have a very different API, which labels each effect in an effect stack. Personally, I am skeptical of extensible’s API. It seems to make some tradeoffs with benefits that I can’t imagine are worth the costs. Still, I haven’t used it in practice, so I can’t seriously judge it.
One concern for me is whether using Effects is likely to cause more allocations and work for the GC, or is the memory pressure about the same?
It’s hard to say. My conservative answer is “yes, extensible-effects will allocate more”, since extensible effects systems reify computations as data structures by design, and sadly, GHC isn’t clever enough to eliminate those data structures even when effect handlers are used in such a way that all effects can be statically determined. In contrast, the GHC optimizer is really good at optimizing away the dictionaries inserted by mtl-style typeclasses. That said, I don’t feel like I can really say for sure without being intimately familiar with a given program. The problem with things like extensible-effects is that microbenchmarks are always going to be misleading; the performance characteristics (relative to mtl style, anyway) can vary wildly depending on how they’re used in practice. I think this is an area where you just have to benchmark and see.
On Sep 20, 2018, at 09:29, Lana Black
wrote: extensible-effects is also based on freer monads. One advantage over freer-simple and other libraries is that it includes monad-control instances for most used effects, allowing to mostly painlessly use things like forkIO. The limitations of monad-control apply though.
Thanks for the correction. I peeked at the documentation, and it looks like extensible-effects switched to using freer in November of last year, which sounds about right, since I was looking into extensible effects libraries last July, prior to the switch. I guess I’m a little behind the times. The MonadBaseControl instances are neat, though they seem to be rather limited in that they hardcode particular effect handlers. I don’t know of a way around that restriction, but it does seem potentially misleading to me. In any case, the effort of implementing MonadBaseControl instances is still quite high, and since it still needs to be done for user-defined effects, I’m not sure how useful it would be in practice (as when I use either mtl style or extensible effects, I define a lot of my own effects rather than only using the ones provided by the library). Alexis

On 9/18/18 6:06 AM, Alexis King wrote:
- The ecosystem of EE libraries is a mess. There are extensible-effects, freer, freer-effects, freer-simple, and others. As far as I can tell, extensible-effects is based on free monads, and freer and freer-effects are both unmaintained.
extensible-effects is also based on freer monads. One advantage over freer-simple and other libraries is that it includes monad-control instances for most used effects, allowing to mostly painlessly use things like forkIO. The limitations of monad-control apply though. Huge disclaimer: I'm one of the contributors to extensible-effects.
participants (6)
-
Alexis King
-
Lana Black
-
Till Mossakowski
-
Vanessa McHale
-
Viktor Dukhovni
-
Zemyla