I don’t think that trade-off can be resolved by anything other than preference due to the variety of factors involved. Do you think it can?
Some things are measurable. It’s possible to count the number of IO functions in a codebase and estimate the number of lines to be changed. That would be an effort. Then we can count the effects removed. Then there’s indeed preference – the multiplier we need to outweigh the effort. It may be harder to justify preference in front of a concrete value-to-effort ratio.
This discussion reminds me of Python fans who say “I don’t need pure functional programming.
I could be experiencing a Blub paradox. And I hoped that I had one when I started working with a monad-transformers ridden codebase. But in the end it turned out to be just a pure overengineering: rigid, tightly coupled, hard to use and hard to extend (MonadBaseControl is simply impossible for some use cases).
I can do the same in IO, or, much better, not do that and write a simple, purely functional code instead. I didn’t choose Haskell to go back to the imperative mess:
streams – yield looks nice for Python, but we already have lazy lists. In IO we can use writeChan if we like, or call a user supplied callback-function.
consumers – await is not always nice even in JavaScript. Again, we can pattern match on a lazy list, use readChan, the standard blocking readLine or await from the async package.
scoped jumps – I’m sorry, but this is definitely not the code I’d like to see in Haskell.
it’s the freedom to mix 1000 effects without difficulty and unlock a programming style that you couldn’t use before.
The fact that I can mix effects doesn’t mean I should. It’s important to have an orthogonal modular codebase. Mixing evertything means a mess and a big maintenance pain.
Bluefin looks favourably comparing to other effect systems because it makes this mixing obvious – you see that you pass too many arguments to this function and need to do something with this. But I’m not sure I’d like to change all IO (and many pure functions) to Eff. The Blub paradox is still strong with me.
Interesting, is it possible to do some parts of Bluefin in pure ST? If instead of a custom Eff monad we can have an ST (with all the standard ST functions), but with an early return, or state variables that don’t escape the sub-region. I suspect with some hacks it should be possible to make
foo :: (e :> es) => Exception Bar s -> ST es Foo
and then we can play with it locally without converting everything to Eff (though I don’t use ST often and prefer pure functions whenever possible)
Effect systems are usually used for I/O related effects and the final handler is usually in main and returns (). So they’re not that local in their standard usage.
And using an effect system when writing a pure code is questionable. Why use monadic code when we can use pure functions instead?
I would disagree. IO primitives are not a black box – the library code is available, a lot of the basics are covered in research papers and books. Haskell’s I/O and concurrency design is top-notch. And most Haskell developers know how stock I/O and concurrency works.
On the other hand, we have some experimental effects system where we do have to look into pretty convoluted code to understand how it works. And we can have several such systems (they are like JavaScript frameworks nowadays ), each with its own idiosyncrasies and most of them much worse than what we have in base.
I may have misunderstood you. It sounds like you might be talking about the effort involved in converting an existing codebase to Bluefin. I was talking about using Bluefin at all.
I would say the benefit of developing a new project in Bluefin is greater than the benefit of converting an existing project to Bluefin. After all, for a new project Bluefin will help you develop it in a way where you have less risk of bugs. For an existing project one might expect many of the bugs have already been eliminated by other means. (I would say the same of the benefit of converting an existing project to a pure functional language, versus starting a new projecting in a pure functional language.)
Yes, effectful (and hence Bluefin) were developed for good reasons, including significant weaknesses in the MTL approach.
You can’t mix them with effects, and they risk leaking space.
I suppose so!
Right, that’s exactly what Bluefin’s Stream is: a well-scoped callback-function.
Bluefin’s await has no relation to Javascript’s. It’s analogous to that of pipes or conduit.
Which? I can’t find it.
Really? Do you like to see the Maybe or MaybeT monads? They’re isomorphic to Bluefin’s scoped jumps.
Well, I agree, and Bluefin provides you with tools to address this issue: you can freely mix effects within components, but handle the internal effects at component boundaries and expose a very precise, simple API, that leaks no details about the implementation.
Yes, actually, I think it should be possible to do that. It seems a bit dubious but it could probably be made to work.
Personally I prefer programming imperatively, with well-scoped effects, than programming “pure functionally”. For example, consider these fold combinators:
foldr
fold/foldl'
foldM
mapAccumL/mapAccumR
mapAccumLM/mapAccumRM
any/all
They are all just for/for_ with different choices of effects in scope. If you squint a bit you can do mapMaybe and concatMap in roughly the same way. Why program “functionally” with two handfuls of primitives when for/for_ do the same job?
Are you thinking of anything in Bluefin? If so please let me know what it is and I’ll try to simplify.
At some point some IO primitives will need to show something to the screen. I don’t think the code that my GPU uses to move pixels around in its VRAM is available. In general, IO primitives are tightly coupled to many layers of abstraction. In contrast, operations in effect systems are decoupled from any particular implementation.
You could model a screen in a completely pure way using a state effect with the type [[Pixel]] or something like that. It wont be fast, but you will be able to wrap your mind about the complete implementation.
But at some point somewhere in the program, there will still need to be an I/O action which actually displays [[Pixel]] values - there’s no (safe) escape from the I/O “black boxes” in Haskell. However, there is another option for those who prefer a more denotative approach to effects, at least for I/O:
The dialogue library also has a runDialogue :: Dialogue -> IO () function which you’ll need to use if you want to actually run your dialogues, so it is no different from effect systems in this regard.
As both IO ... and Eff ... rely on the monadic interface, is there any other difference between providing:
128 extra exceptions for IO ...
128 extra “external” effects for Eff ...
…?
(and yes: these days, the monadic interface isn’t alone, with the functor, applicative, arrow, comonadic etc interfaces also now available; but I/O in Haskell is still abstract and monadic.)
Good to know that mtl/transformers are not considered a way to go now (though I have nothing against local uses). It took me quite some time to explain the same to fellow team members. Some of them are now converted to a “church of pure functions” and enjoy the simple code without artificial obstacles.
I don’t want to mix them with effects (though I can do it with unsafeInterleaveIO). And yes, lazy values can leak space (though with a bit of experience and a couple of bang patterns it doesn’t happen much), but they make Haskell very expressive, powerful, fast and modular.
For sure. It’s a pretty bad coding style (GOTO) and I don’t want to have any monads here:
-- simple recursive monadic function will work
let loop = do
n' <- get n
modify total (+ n')
unless (n' == 0) $ do
modify n (subtract 1)
loop
loop
-- could be shortened using 'fix'
fix $ \ loop -> do
n' <- get n
modify total (+ n')
unless (n' == 0) $ do
modify n (subtract 1)
loop
-- but the best in this case would be to have a pure function
let count 0 total = total
count n total = count (n-1) (total+n)
count 5 0
It might work. Unlike the implicit arguments passing approach, superfluous handles really need to be passed in Bluefin. So it’s not like “yes, we use global variables everywhere, but we track them really well”. But the examples I’ve seen so far look like sophisticated solutions to problems that were solved much simpler a long time ago.
That left me open-mouthed for a while. So why did you choose Haskell then?
With another two handfuls of primitives?
You might be surprised, but all functions you listed are in fact implemented using two primitives: traverse and foldMap (or sequenceA and foldr, depends on Traversable and Foldable instances).
And I much better prefer to just use any pred [a, b, c] than
withEarlyExit $ \ exit -> do
forM_ [a,b,c] $ \ x -> when (pred x) (exit True)
pure False
And if I don’t have any I can just write it:
any pred = or . map pred
-- or maybe
any pred = not . null . filter pred
-- or
any pred = foldr ((||) . pred) False
All of them are much simpler, shorter and faster.
I didn’t mean Bluefin in particular. I mean that IO is well designed, universally supported and that IO experience is transferable from one project to another. Effects systems are all different and have a lot of quirks you have to learn. I especially don’t like how they work with concurrency, a sensitive topic where I don’t want to have any superfluous layers.
By “another two handfuls of primitives” do you mean effects? Well, there are only three primitive effects in Bluefin: State, Exception and IOE. I think it’s much easier to understand what for with just a State in scope does than what mapAccumL does.
It doesn’t surprise me. In fact I just explained exactly the same thing! What surprises me is that people want two handfuls of fold combinators when for and for_ generalize all of them.
That looks great, but what if pred or the sequence of elements are effecful? That is not an uncommon occurence.
Well, of course one can write these combinators for Bluefin so that you can write any pred = or . map pred in Bluefin too.
But Bluefin and effectfulare just IO, so there’s nothing to learn if you already understand IO. (effectful is actually IO plus a little bit, but really a tiny little bit – and Bluefin’s Effreally just is IO.)
Naturally, if you prefer to program without an effect system you prefer it. I can’t argue with that!
I was talking about the effects systems I see in Haskell. They try to abstract HaskellIO which is a much better abstraction than these effects systems. Haskell IO is open source and this source is usually of a much better quality than that of effect systems.
(a former game developer there) True, there are reference renderers that slowly draw to a 2D array of pixels. But I wouldn’t call this this 2D array an “effect”. It’s a data structure (and a lot of things that lead to have some nice looking bytes in that data structure).
It looks like many standard engineering things – data structures, algorithms, abstract interfaces, data flows, control flows, modules, libraries, components, systems, services, maybe even teams – are all “effects” now. Much like an object in OOP – no one know what it is.
For type safety and composability. IO-based effect systems are as type safe as programming with pure functions (i.e. not using any monad) whilst being more composable, hence I prefer them.
I think the motivation for effect systems is quite simple. If you recognize the utility of distinguishing side-effects at the type-level:
// no side-effects in type signatures
String readFile();
void launchThread(Int);
Int bar(Int,Bool);
void run(); // calls readFile, launchThread, and bar
-- IO to the rescue
readFile :: IO String
launchThread :: Int -> IO ()
bar :: Int -> Bool -> Int
run :: IO ()
Then imo it is easy to see the advantages of distinguishing types of side-effects i.e. increasing granularity:
readFile :: FileReader m => m String
launchThread :: Concurrent m => Int -> m ()
bar :: Int -> Bool -> Int
run :: (Concurrent m, FileReader m) => m ()
Now, where to draw the line is going to be highly personal and likely app-specific. For instance, some apps will care about separating read-only and write-only file-system effects, whereas others will not. And certainly there are downsides to this style of programming (though similar arguments often apply to IO!). But the general idea is a very natural extension of IO.
I don’t see it being a problem. Why would those libraries not expose pure and IO based API in the first place? Or expose both with moe and moe-fused-effects. And even if they did not, with function like readFile :: FileReader m => m String you can always do this.
That’s a different question. The question of where to draw the line is about how fine-grained you want your effects to be. Is the pure/IO distinction enough? Maybe it’s too coarse. Conversely, it’s possible to be too fine.
The dimension of “what effect system do we use and are they compatible”, which I think is what you’re getting at with the list of Scala effect types, is orthogonal.
Ultimately, as @jeukshi and @Kleidukos are saying, you can use IO as the lowest common denominator, just like the C ABI is the lowest common denominator for the FFI. If larry exposes an effectful API you can use its run... functions to get an IO API, and then wrap that in whatever effect system interface you like.
It may be a different question, but it arises from the same problem:
Each of those async frameworks was written by someone who thought all the other frameworks “drew the line” wrongly;
Similarly, each new effect system was also written by someone who thought all the other systems “drew the line” wrongly;
So how many more effects systems will be needed to “draw the line” correctly, with a view to having a standard one for Haskell that can be used by all libraries?
So first you finely slice the effects 1002 ways, according to “where the line should have been drawn in the first place” because “you know best” ;
only to then mash all those effects back together again within an I/O action!
Then why bother with the hassle of an effect system to begin with? Just use IO a directly, exactly because it is the lowest common denominator that all experienced Haskellers know of - at least then, all debates about which $EFFECT_SYSTEM is “best” can be kept out of code reviews…