Why use an effect system?

Maybe it was already asked before but what are benefits of Bluefin compared to using plain IO functions?

Why should I use

foo
  :: (e1 :> es, e2 :> es) 
  => Handle1 e1 -> Handle2 e2 -> Eff es Foo

instead of a plain

foo :: Handle1 -> Handle2 -> IO Foo
5 Likes

The benefit is that you can remove from the set of effects. If you have

foo :: IORef Int -> IORef Bool -> IO Foo

then you are stuck in IO forever. With Bluefin, if you have

foo ::
  (e1 :> es, e2 :> es) =>
  State Int e1 ->
  State Bool e2 ->
  Eff es Foo

then you can handle the States, removing them from scope, and even end up with a pure value.

result :: Foo
result = runPureEff $
  evalState 0 $ \sInt -> do
    evalState True $ \sBool -> do
      foo sInt sBool

Same can be done with runST:

foo :: STRef s Int -> STRef s Bool -> ST s Foo
result :: Foo
result = runST $ do
  sInt <- newSTRef 0
  sBool <- newSTRef True
  foo sInt sBool

Plain IO also “removes effects” pretty fine:

do
  r <- withH1 $ \ h1 -> do
    x <- withH2 $ \ h2 -> foo h1 h2
    -- 'h2' is "removed" at this point
    bar h1 x
  -- 'h1' is "removed" at this point

It doesn’t prevent us from putting a handle in a function result, but this can be overcome with a helper like:

data Foo s a = Foo { unFoo :: a }
withFoo :: a -> (forall s . Foo s a -> IO b) -> IO b
withFoo x f = f (Foo x)
-- now the 'foo' below won't compile
-- "because type variable ‘s’ would escape its scope"
foo :: IO Int
foo = unFoo <$> withFoo 1 pure

Both ST and IO code looks simpler and have simpler types while allowing to block “effects” from escaping if required.

Is there a need in removing effects from set?

If we need to produce a pure value using the impure algorithm, runST allows us to do it. In impure code we might like a DB connection or a file handle not to escape, but is it worth the additional complexity everywhere? People don’t usually store connections in function results.

Are there other benefits of using Bluefin over plain IO or ST?

1 Like

I think your question is more “why use effects in the first place?”. It’s a valid question, because Bleufin (or effectful for that matter) is something new to learn, and a little more administrative effort. What does one gain? Quite a few things!

Most importantly for me it’s that an effect system pushes me to think about “What are the different ways my program interacts with the world?”. Separating those different ways into different effects is a wonderful exercise.

A second big benefit is that IO doesn’t tell you much. Could be writing files, network requests, database things. With an effect system, every function will tell you what side effects it has with much more granularity. That helps me understand much better what a function actually does.

Effects have a nature of seperating the “what” from the “how”. That means you can have different implementations for the same effect. This typically works really well to set up mocking for tests. E.g. Replace the Database functionality with pretending you updated something and returning a constant value.

4 Likes

Correct, but Bluefin does more than ST. One way to see Bluefin is as a "generalized ST". It’s generalized because it also treats exceptions and IO, neither of which ST treats. Regarding the former, you can write

bar ::
  (e1 :> es, e2 :> es) =>
  State Int e1 ->
  Exception Bool e2 ->
  Eff es Foo

result :: Foo
result = runPureEff $
  evalState 0 $ \sInt -> do
    handle (\case True -> defFoo1; False -> defFoo2) $
      \exBool -> do
        bar sInt exBool

removing the Exception from scope, as well as the State, and ending up with a pure value. Regarding IO, it cannot be removed from scope, but its absence (i.e. the absence of an IOE e -> argument) shows that a function does not do IO.

That pattern is syntactically convenient, and common in the Haskell world (for example, withFile), but it doesn’t actually guarantee removing effects from scope, as you point out.

Unfortunately that’s not sufficient. Consider the following attempt at scoping a resource:

withResource ::
  (forall s. Resource s -> IO r) ->
  IO r

useResource :: Resource s -> IO Result

Then I can write

bad :: IO (IO Result)
bad = withResource $ \resource ->
  pure (useResource resource))

and get access to the resource outside of the scope of withResource. That’s bad! (@Leary explained this to me in an earlier thread on the topic).

ST does allow to block effects from escaping, but it is not really simpler: it’s just doing less. You can write almost the example same code in Bluefin as you would in ST, if all you wanted to do was to manipulate state.

IO does not allow to block effects from escaping, as demonstrated above.

I feel that need, as do some others. Maybe you and different others do not. That’s fair enough. But assuming you do want to remove effects, and you do want value-level effects handles, then I don’t think you’ll find a simpler API than Bluefin’s. (One way this might change is if Haskell got a type level set type. Then we could simplify the types, for example doing away with the e1 :> es constraint.)

Yes, but only as long as you didn’t want to use exceptions as well as state.

I think it’s worth it. You may not. It’s probably a matter of preference.

Well, not really, but that’s a bit like asking “is there any other benefit of pure functional programming, besides all functions returning the same result for the same input?”. In both cases the simple foundation provides something very sturdy to build reliable software on top of!

4 Likes

Thank you for pointing out the problem with the (forall ... -> IO a) workaround.

I agree that if not allowing handles to escape is important then Bluefin is probably the most compact way to implement the “generalized ST monad”.

I think it’s worth it. You may not. It’s probably a matter of preference.

It’s not just a matter of preference, but also the amount of work involved. The issue I see is that I have to wrap all the code in Eff monad (a very intrusive change) for the benefit of not allowing a database connection handle to escape. This is quite a hefty price to pay for a problem I have never personally faced.

ST is usually very local. It’s still a pure function outside. The effect system infects all the code, makes interaction with other libraries less convenient, requires digging into how it works with exceptions, state, and concurrency.

effectful allows not to pass arguments (which I consider a bad practice), so it removes the boilerplate in some places at the cost of adding it in others. A debatable benefit but still a benenfit.

Bluefin adds boilerplate but doesn’t remove much, so its benefit of not being able to store handles and being able to remove them should be really important to justify its use.

I had an experience with a legacy transformers-ridden codebase and I haven’t seen any places where effects were removed. It’s mostly runTheGood $ runTheBad $ runTheUgly $ .. at the top function and that’s it.

My use of ST is at most few pages long functions implementing imperative algorithms. Not much place for exceptions there. And ST is usually for performance. I’d like to have a full control there without additional layers.

Sorry for the big wet blanket reply. I do think that "generalized ST" is a good idea. But I’m not sure yet if it outweighs the simplicity of pure IO or ST.

5 Likes

It’s a trade-off between the amount of work involved and the amount of benefit gained. 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?

This discussion reminds me of Python fans who say “I don’t need pure functional programming. Most of the bugs I write are not type errors.” I believe them, but then when I try to write Python I get runtime errors like NoneType object is not callable.

Perhaps it’s because I try to write in functional style in Python. But that’s the point! The benefit of strongly typed pure functional programming is not so that your programs are strongly typed and pure. The benefit is that it gives you freedom to confidently write in a style you simply can’t risk in a non-typed setting, because there’s too much chance of making a mistake.

I would say the same holds for Bluefin. It’s not just “database handles can’t leak, but I’ve never had that problem in practice”, it’s that everything is well scoped and that gives you an awful lot of freedom to confidently write in a style you wouldn’t have dared try before. For example, you can fearlessly mix streams, consumers and scoped jumps (for implemented break and continue). So it’s not just avoiding a database handle leaking from a top-level running (which is pointless anyway), it’s the freedom to mix 1000 effects without difficulty and unlock a programming style that you couldn’t use before.

3 Likes

Be it IO ... or Eff ..., people have no choice other than to use the monadic interface. So what is the difference between:

  • 128 extra exceptions for IO ...
  • 128 extra “external” effects for Eff ...

…?

Effect systems are local in the exact same way as ST is. If you run the final handler, then you’re left with a pure value (some effect systems also allow embedding arbitrary IO, in which case they do end up with an IO value in the end, but that is often optional).

One big difference is that you can define what all the effects mean in pure Haskell code, instead of having to rely on black box IO primitives.

3 Likes

o_0 How exactly does one define what an “external” effect means using pure (effect-free) Haskell code?

What do you actually mean with “external” effect? I thought you just meant effects in general.

1 Like

“External”, as in “externally visible” :

because I/O exceptions can only be legitimately caught in the monadic type IO a.

It’s possible that I’m misunderstanding what you’re saying, but in the same way that IORef can be wrapped as STRef s, providing an interface to mutable state that is guaranteed to be externally pure, IO exceptions can be wrapped, providing an interface that is guaranteed to be externally pure. This is what effectful's Error effect is. Bluefin copied that and calls it Exception.

The archetypal examples of externally-visible effects are:

  • the modifying of a top-level reference’s contents.

  • the various forms of I/O (using files, networks, devices, etc).

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 hope things are different with Bluefin. But

For example, you can fearlessly mix streams , consumers and scoped jumps (for implemented break and continue)

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)

1 Like

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 :slight_smile: ), each with its own idiosyncrasies and most of them much worse than what we have in base.

1 Like

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.

6 Likes

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.

1 Like

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.

3 Likes