My observation is that a lot of commentary on checked exceptions from 2000s and earlier […] do not apply to today’s type systems, scale, and language features.
Then here’s the challenge for you and everyone else who thinks IO a is now bunglesome and needs diluting:
type IO a = Eff All a
…use your preferred system of effects to provide a Haskell declaration for All .
I see a lot of speculation here and people speaking past each-other. Why don’t you all go and build something with an effect system, and come back with actual production insights? The conversation would certainly be more productive.
The second one is tightly coupled to the effect system. It’s impossible to convert to a pure IO action and pass to a non-Eff subsystem … It’s only reusable within Eff framework and unusable outside. Doesn’t look too modular.
This is not true. There is no coupling to the effect system (assuming we’re talking about Bluefin). To see this, note that this function is safe:
tag :: Untagged.Connection -> Tagged.Connection e
so you can define the former write in terms of the latter:
Agreed with this. It would be good to establish one.
I disagree with this. Effect systems as a whole are an extremely well understood area of the Haskell world. They’re so well known, in fact, that their significant weaknesses, and potential approaches to ameliorate them, is extensively covered and recovered ground.
However, until the progression from ReaderT IO to effectful that I covered in my talk there had been no approach developed that resolved all the significant weaknesses. effectful does address all the issues of existing effect systems (with one exception: it doesn’t directly support multi-shot continuations – that’s probably fine!) and we know it doesn’t have any additional weaknesses of its own relative to IObecause it is just IO. Bluefin inherits these properties.
I suppose one could argue: “but the additional interface that effectful and Bluefin put on IO is too complex”. But firstly, IOE :> es => Eff es ais (almost) just IO a, so you’re never far from the lowest common denominator, and secondly, I don’t believe there is a simpler way to carve out effects from IO. Can you think of one? If not then that’s evidence that carving out effects requires a certain level of additional complexity. If you don’t want that complexity then so be it, but that’s not the same as a proof that effectful and Bluefin are experimental or flawed.
I don’t recall anyone saying effect systems were a pre-requisite for writing basic programs. Can you point out such a claim?
Regarding “this is the future of Haskell”, perhaps you’re referring to my slide “Bluefin is the future of Haskell!” at timestamp 40s of my talk. To be clear, that is not advertising. That is simply my belief. The point of the talk was to justify that belief based on properties of Bluefin. To summarise why that is my belief:
To justify effect systems per se: I believe it is useful in practical programs to “make invalid operations unrepresentable”, i.e. use types to tightly delimit what externally-visible effects a function can perform. This must include, at minimum, state, exceptions and I/O, and it must do so in a composable manner.
To justify IO-based effect systems: it is essential for practical programming that an effect system provide resource safety and easy reasoning about behaviour. I don’t believe this is possible outside IO-based effect systems.
To justify Bluefin (i.e. value level effect arguments) versus effectful (i.e. type level effect arguments), I think it’s simpler and more approachable. (I wouldn’t really be surprised or disappointed if effectful won out over Bluefin. It’s a matter of taste and I’m happy to let the market decide. But the Haskell ecosystem really does IO-based effect systems to displace all others, and I think that’s inevitable.)
EDIT:
Do you also feel the same way about ST, which has the same “polymorphic” property?
That’s good news for effectful and Bluefin then, because you can use them in internal components without effecting external APIs, which can either be pure (if the internal components didn’t use IO) or use IO (if they did).
I agree. Bluefin and effectful can do this, no problem.
This is completely false for Bluefin and effectfulbecause they are just IO wrappers: they are minimal and you can always just unwrap to IO.
I agree, but not everything has to be reusable outside the context it is important in. I mentioned codebase, but that is not good enough. I’d draw a distinction between application/library code. Then I’d agree that for library code (API to be precise), Eff is not it. But for application code, you don’t care for unusable outside.
Noisy types, leaks details, hides details, unmodular, Java factory, infects code. I think those could arguably work. I don’t know if it is worth discussing, though. Just wanted to point out that Bluefin is really close to a record of functions, which is what I like about it.
As someone who doesn’t have a strong opinion on this topic I’d say ultimately it depends on the kind of applications that you write and on personal preference.
However I’d like to point out another aspect, that I don’t see mentioned in this discussion, namely that Haskell is not a “batteries-included” language. If you consider a language like PHP, which has built-in support for HTTP, database clients and whatnot, Haskell is on the other end of the spectrum. It’s probably the only (almost) mainstream language without even built-in booleans!
This is both the strength and the curse of Haskell. It’s a strength because it makes it flexible and general-purpose. It helped the language to remain relevant for more than 30 years despite not being super-popular. It’s a curse because more functionality is delegated to the libraries, so for each feature that other languages would provide as built-in, we have a myriad of competing solutions and libraries. The whole ecosystem is more distributed compared to other programming language communities.
So, just like the lack of proper built-in record manipulation encouraged the development of optics (which ultimately became much more than just record selectors), we can say that effect libraries were also born from the lack of certain built-in features (and they probably provide more than what built-in features could have provided, at the cost of additional complexity/boilerplate).
Part of the discussion here seems to be just the latest reiteration of this same issue. The tension between vanilla Haskell being “too simple” and libraries being “too powerful”. Finding the sweet spot is hard. It may even be a wrong idea, and maybe the decision should be taken on a case-by-case basis.
There are many ways to achieve mocking without effect systems:
use original services but with test data
mock services
use functions: mockConnection :: IO Connection where Connection has functions inside (Connection {write :: ...} or Connection :: Service a => a -> Connection which is less convenient to use)
built-in mocking: data Connection = Real Socket | Mock (IORef (Input, Output))
Mocking worked long before effect systems. Ironically, it’s especially easy to mock with first-class functions.
Hm, if I look at base, text, async, network, unix, warp or http-client packages, I usually see pure functions or IO. What parts or ecosystem have these “convenient” runners?
I worked on a moderate sized production project (~150k lines) with effect system, so I do have some experience which I’m sharing here. It wasn’t effectful, but switching to effectful will still keep a lot of problems (though indeed it will improve performance and simplify the implementation of new effects).
It will work if you have Untagged.Connection. What if you only have Tagged.Connection e? And that’s what usually happen (at least in my experience).
That’s why write :: ... IO () is modular – you can use it standalone, or embed into an effect system, and write :: Eff ... is not (unless it uses a modular IO underneath).
I think you confirmed my “most of them are not production ready or have flaws”. Yes, effectful is a pretty good implementation. But there’s already a Bluefin that tries to replace it. A lot of other systems to come.
I think that Bluefin is still in its early stages. I was mostly talking about myriad of other systems.
That’s my general feeling. I see far too many discussions about effect systems, I see newbies asking which system to use. It’s becoming a matter of course to use an effect system, whereas it’s an advanced and experimental thing with no consensus on which one to use.
Yes, I was referring to this. Maybe if it was “the future of Haskell effect systems” I wouldn’t start all this discussion
Yes, for performance considerations and to be able to use exceptions, state and concurrency properly, IO-based system looks inevitable.
Though there are many other use cases (like verification) where interpreting a program might be more convenient.
In a sense, yes. But ST is local and has a very strong guarantee – function that uses runST is still pure, I can easily use its pure results everywhere.
Effect systems are usually for managing IO, and there can be a need to connect systems that use Eff and systems that use IO. Here I can have issues connecting the two.
Hm, much like runST. It may work, but it will lead to a bizzare mixed codebase (one part is IO, another is Eff), and may complicate extracting parts of Eff system to a separate IO libraries.
Many libraries are initially part of the application and are extracted later. It’s a sign of good modularity if the application code can be extracted into a library. So it’s worth aiming for IO. Otherwise the Eff code, which could be a future library, would remain coupled to the application.
Hm, it’s still an abstract Connection data type, that is not noisy and doesn’t leak much details. Though yes, it might hide details as it’s not clean which functions are used.
And it’s great. It makes Haskell a vehicle for innovation, and sometimes we get amazing results.
This is one of the things I don’t like about effect systems – they are often proposed as the one true way to write Haskell.
Production services with test data is QA territory;
Built-in mocking means your declarations and implementations for both the production and the test versions have to live in the same module, whereas they most probably belong to two different executables.
Mocking downstream services is something I’d much rather have the service do itself via a sandbox, so that’s QA again;
Passing records of functions makes you responsible for juggling all that as extra arguments instead of constraints. It’ll definitely work, the question is just how much inline visual clutter the team you’re working in is willing to endure.
Though it’s hard to say just how more convenient effect systems are because there definitely is a problem of sharing overlapping effects between components and I don’t know if anyone has solved it yet.
That part of my reply vaguely gestures at the mentality that produces duplications like this bunch and package after package with no refined constituent pieces, like most web-servers, but as it relates to this discussion specifically I think it’s a non-sequitur. (unless “I think everyone should agree on one effect system” is a point worth discussing)
I think I finally understood this concern. Effect systems (those named in this topic at least) are not about breaking IO into pieces, they are not even about IO at all. They are about built-in/custom effects and restricting functions to specific effects. Of course, there are performance and ergonomics issues too. One of the ergonomic considerations is providing a way to make effects out of the existing code. Which happens to be Haskell code, and a lot of it lives in IO. So those libraries provide an easy way to make effect use IO, to use IO functions.
Just like effectful provides an easy way to integrate mtl code to make effects. Nothing profound about that at all.
The latest entry to Philip Wadler’s list of notable quotes:
Now another era is being foisted upon Haskell, an era where someone might have to generate an I/O action out of a library using fused-effects and provide it to a library using speff. Can anyone seriously argue that this is an improvement?
I don’t get it. Is this a trick question? In effectful the answer is type All = '[IOE]. Why did you ask the question and what’s the consequence now that you have an answer?
Then IO a can be superseded in a future Haskell standard without breaking every Haskell program in existence. (can we assume that there are no more Haskell 1.0-1.2 programs still in use ? :-)
So for example, future Haskellers could use Eff All ... directly in FFI calls:
foreign ... thisNewEffect :: ... -> Eff All ()
(or use a subset of All).
But as I recall…IOE is connected to the current definition of IO a, so you would need to sever that connection somehow to avoid a vacuous cycle between the two.
I will preface this that my understanding through reading this thread is that effect systems seem better for doing things with IO; therefore my pure logging endeavours below might not put them in the best light but I’d like to share what I’ve learned so far.
I’m currently making Snake in Haskell via Brick as a learning opportunity and decided I wanted to learn about effect systems and see what it was like to combine effect systems together with mtl/transformer-style. To understand 1) Can I make a logging system with a known name? and 2) if I can, how does it work alongside Brick?
Brick’s EventM type is a big ReaderT of stuff and I wanted to do logging on the side but without adding to the overall stack of Monad Transformers.
I choose Bluefin as the one to learn and came up with this for my logging solution.
My initial plan was to have the whole Eff es Eventlist as a record in my overall GameplayState type because then later, I can call runPureEff and extract the Eventlist out of it. I couldn’t get this work by adding Eff e Eventlist to the GameplayState type as then it becomes GameplayState e and I struggled to get logInGame function to be happy when called in my eventHandler function (some type stuff, couldn’t figure it out why it wasn’t happy).
So right now I just build the list at the time of usage.
runLogger :: (forall e. Logger g e -> Eff (e :& es) r) -> g -> Eff es EventList
runLogger f gps =
execWriter $ \writ -> do
runReader gps $ \rea -> do
useImplIn f $ Logger (mapHandle writ) (mapHandle rea)
...
handleMovement :: (e1 :> es) => ([a1] -> Either a2 (K.KeyDispatcher KeyEvent m)) -> BrickEvent n e2 -> Logger GameplayState e1 -> Eff es ()
handleMovement disp ev (Logger writ readstate) = do
gameplaystate <- ask readstate
let logaction = getKeyEvent disp altConfig ev
tick = gameplaystate ^. tickNo
addToLog writ tick logaction
...
logInGame :: BrickEvent n e2 -> GameplayState -> EventList
logInGame ev gs = runPureEff $ runLogger (handleMovement gameplayDispatcher ev) $ gs
...
eventHandler :: BrickEvent MenuOptions Tick -> EventM MenuOptions GameplayState ()
eventHandler ev = do
glf <- use gameLog
gps <- get
case gs of
...
Playing _ -> do
zoom gameState $ handleGameplayEvent' ev
gameLog .= (logInGame ev gps <> glf)
tickNo %= (+1)
...
However, for me this solution feels like cheating because at the end of the day, all my Logger es is doing is generating a singleton event to append onto the front of my EventList which is a linked list and I’m just appending them onto the front of the list by calling a function ==> a lot of work for (++) - which really should become a (:) in this current state - and function to pattern match on KeyEvents. Still, a lot has been learned so far.
Ideally, it would be nice to get the Logger e or the Eff e into the GameplayState type but I can’t figure it out right now.
I’m still experimenting around and trying to understand it and I have nowhere near the capability as anyone used to working on this stuff on a regular basis :’) so apologies if I have butchered anything.
The impressions I acquired from the majority of other’s posts on this topic was that:
IO a is now more hindrance than help.
the use of a “piecemeal” monadic type for effects have been hindered by adverse attitudes towards earlier (and allegedly-defective) implementations (with frequent criticism of Java’s checked-exception mechanism) - apparently it can be done correctly in Haskell.
So I proposed this challenge:
type IO a = Eff All a -- what is "All"?
…with a view to a future Haskell standard - if IO a could be defined as a special case of a more general system of effects, doing this would mean moving closer to having one standard system of effects that everyone can improve together, as an alternative to everyone continuing to build their own.
But here’s something else I’ve just realised - by being able to switch between IO a's current definition and that special-case definition right now (for example by reusing some of the alternate Haskell preludes) it would be possible for the authors of effect systems to more-or-less use the entire Haskell ecosystem to test and refine their offerings.
As I have now mentioned a few times already, a more permanent change for the management of effects would be a matter for a future Haskell standard. But it will be one of many matters that the writers of that standard will have to contend with; this being another:
It is difficult to estimate just how much time would be needed for a supercomputer to solve a distribution with 76 detected photons—in large part because it is not exactly feasible to spend 2.5 billion years running a supercomputer to directly check it.
Hence the increasing relevance of this edited comment: