Effectful: how to prevent big Effect runner functions?

Since the past couple of months, I’ve been playing around with effectful. What I like in particular, is this video, which advocates for creating some hierarchy of effects. I find it very satisfying to build a bunch of effects, and then express my program in terms of these effects. I also like that effects are easy to refactor and restructure.

What I’m not too comfortable about, though, is this:

source

main :: IO ()
main = do
  exitCode <-
    runEff $
      runCliIO $
        runFilesIO $
          runInterruptible $
            Env.runEnvironment $
              runLoggingIO
                run

  exitWith exitCode

Another example, source:

{-# LANGUAGE PartialTypeSignatures #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}

runEffects :: Eff _listOfAllEffects a -> IO a
runEffects =
  runEff
    . Logger.logStdout
    . Config.runGetConfig
    . Environment.runEnvironment
    . Concurrent.runConcurrent
    . Error.runFailOnError @CommandError
    . Error.runFailOnError @Secrets.SecretError
    . Command.runCommand
    . Sqlite.runSqliteIO
    . Secrets.runSecrets
    . runMountDrive
    . RSync.runRSync
    . MostRecentBackup.runMostRecentBackupStateSqlite
    . ExternalDiskBackup.runExternalDiskBackup
    . Time.runCurrentTime
    . PeriodicBackup.runPeriodicBackup

The more effects a program has, the bigger this Eff [biglist] a -> IO a becomes. This seems to be because you have to run the effects of the entire hierarchy, and not just the ones at the top.

From an architectural point of view, what would be the best strategy?

  • Hide effects by using the reinterpret function, with the downside that mocking becomes harder
  • Accept the big list of effects in a single big handler, and deal with it by e.g. using the type hole in the example above, or writing a type alias for the effects list.
  • Avoid having/using many effects in the first place.
  • Split up the Eff someList a -> IO a by making/combining interpreters that interpret multiple effects at once
  • Stop using effects in favour of X (not really what I’m aiming to discuss here)

In defense of the big effects list, I do like that it provides a nice summary of how my program interacts with the world. From the second snippet above, one can tell immediately that my program does stuff with SQLite, backups, rsync, running commands, etc. That’s a nice summary, and a simple “go to definition” will lead to the answer of “how”.

Why are you not comfortable? :slight_smile:

This big list of effects is constructed only at the program entry, later your functions are using polymorphic list with specific :> constraints, right?

You can also use inject to hide some of the low level effects that are not supposed to be used by the application code.

2 Likes

That’s true, and I don’t use hard lists anywhere else in the program. I guess the discomfort comes from the idea that low level details bubble up all the way to the main function. More directly, it’s kind of annoying to maintain that list. The order of the list has to be the same as the order of the runners in the definition. It’s not the biggest deal, but it’s somewhat unergonomic.

My biggest question is whether I’m on the right path by doing it this way. I thought this big list was perhaps an indication of me not doing things the way they should. If this way of doing things is actually fine, then I guess the open question is on how to make that list a little more ergonomic. The partial type is one easy way, but I wonder if there are cleaner.

Ah, do you mean that they would still be in the implemntation for runEffects, but no longer available for the caller, like this?

alternativeRunEffects
  :: Eff
      [ Secrets.Secrets
      -- , Error Secrets.SecretError -- Hidden by inject!
      -- , Error CommandError -- Hidden by inject!
      , Concurrent.Concurrent
      , Environment.Environment
      , Config.GetConfig
      , Logger.Logger
      -- , IOE -- Hidden by inject!
      ]
      a
  -> IO a
alternativeRunEffects =
  runEff
    . Logger.logStdout
    . Config.runGetConfig
    . Environment.runEnvironment
    . Concurrent.runConcurrent
    . Error.runFailOnError @CommandError
    . Error.runFailOnError @Secrets.SecretError
    . Secrets.runSecrets
    . inject

-- No error, because IOE is there
foo :: IO ()
foo = runEffects $ liftIO $ putStrLn "foo"

-- Error! No handler for IOE
alternativeFoo :: IO ()
alternativeFoo = alternativeRunEffects $ liftIO $ putStrLn "foo"

That could be interesting, it also makes it easier to maintain the list, because I can just change the order of items in the type list, without having it match the order of function calls. Does this have an effect on runtime, or is this just a compile time trick?

1 Like

It’s perfectly ok to have a place near main where we “known all the types” and tie a bunch of loosely coupled components together. Sometimes this place is called the composition root.

A typical feature of dependency injection frameworks is to work as the “composition root” and handle the wiring themselves, often in a type-directed way.

2 Likes

Thanks, that makes sense!

Thanks @arybczak for your reply as well. This has been very helpful!

With the inject tip, I changed the runEffects function to hide the IOE. With that, i immediately got an error about a function in application code using IOE, neat!

1 Like

It has a small one-time runtime cost of rearranging the internal array of references to effects.

1 Like

But this is the same for any effect system, right? It would be the same for concrete transformers, MTL-style, even for ReaderT IO!

1 Like

True, but I’ve noticed that with transformers/mtl, people don’t tend to create a whole pyramid of monads, usually they stick to the state/reader monads, and monads defined by specific libraries. Even with some free monad solutions I’ve seen, people stick to only creating a couple big ones. The reason, I think, is because combining them is a pain.

With effectful (and probably also with polysemy/eff/similar libraries) this goes quite the other way. It’s very little effort to make an effect, and even less effort to combine a bunch of effects. That’s why I have so many in my rather simple backup program. The consequence is that I’m no longer just running state/reader/conduit, but a much bigger pile with things like ExternalDiskBackup.

Seeing the replies to this topic, and the reference to the concept of composition root, made me realise that this is not a downside, or bad smell, but actually an important part of the design of an effects system. Having that composition in one central place has a ton of benefits. That truly answers my question. Thanks!

By the way @arybczak, amazing work on the effectful library, I’m very enthusiastic about it.

5 Likes

I’m actually trying out effectful myself. This is my first time using an effects system (I decided to give it a go instead of just having IO everywhere) and it was pleasantly easy to get started.

I’ve been pretty reluctant to try out an effects system since I’ve been pretty confused by all the learning content; it all just seemed so unwieldy and unnecessary. But somehow I guess I finally found some Intuition for them and effectful has been great so far. The compilation errors have been easy to understand and I haven’t been stuck trying to fix anything for more than a few minutes.
Nice work, thanks for making this! @arybczak

4 Likes