freer-simple is a fantastic library and I will definitely use it again. I found some gaps in the documentation that I aim to address here.

Recently I needed to glue some terraform, nixops and ssh commands together so as soon as I realised that bash was quickly going to become unweildly I set about writing a small Haskell program. I had recently worked on a cli app that used a Free monad and found there was quite a lot of boiler plate for little benefit so I decided to use this app to find out about the current state of Freer monads in Haskell.

Eff and the Freer Monad

The Hackage documentation of freer-simple provides some sample code and links to the papers that laid out the groundwork for this library so I’m not going to attempt to explain what the Freer monad is, rather I’m going to explain why its useful and give an example of how you can use it.

With the Freer monad, all monadic code resides within one Monad called Eff. Rather than the ‘stack’ of monads that monad transformers provide, you place a list of constraints on Eff which represents the capabilities it has. You then define handlers (or interpreters) for each of these capabilities and run Eff through those interpreters. Finally you run the monad, as you do with any other monad type. Lets look at some examples:

Console.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}

module Console where

import Control.Monad.Freer
( type (~>)
, Eff
, LastMember
, Member
, interpret
, interpretM
, send
)
import Control.Monad.Freer.Writer (Writer, tell)
import Data.Text (Text)
import qualified Data.Text.IO as Text

-- We start by defining our effects algebra called Console
-- In this case we only have 1 action, PutTextLn
data Console r where
PutTextLn :: Text -> Console ()

-- This is the only boilerplate we really need, a function that hides the way
-- we use effects by 'sending' a Console value
putTextLn :: Member Console effs => Text -> Eff effs ()
putTextLn = send . PutTextLn

-- We will define an IO interpreter that will output the Text to stdout (I'll explain `~>` soon)
interpretIO ::
(LastMember IO effs, Member IO effs) => Eff (Console ': effs) ~> Eff effs
interpretIO =
interpretM
(\case
PutTextLn msg -> Text.putStrLn msg)

-- We will define an alternative interpreter that adds the Text to a Writer
interpretPure :: Member (Writer Text) effs => Eff (Console ': effs) ~> Eff effs
interpretPure =
interpret
(\case
PutTextLn msg -> tell msg)

Main.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where

import Console (Console, putTextLn)
import qualified Console
import Control.Monad.Freer (Member, Eff, run, runM)
import Control.Monad.Freer.Writer (runWriter)
import Data.Text (Text, unpack)

-- In our example program we just want to put some Text in the console
myProgram :: Member Console effs => Text -> Eff effs ()
myProgram = putTextLn

main :: IO ()
main = do
-- first we can run a pure version which will give us some Text back
let (_, pureMsg) = run . runWriter . Console.interpretPure $ myProgram "hello"

-- lets print this text
putStrLn . unpack $ pureMsg

-- now we can run the IO version which will print directly to stdout
runM . Console.interpretIO $ myProgram "goodbye"

This first example is pretty similar to what is shown in the free-simple documentation however it is different in that I have explicitly defined interpretIO and interpretPure.

Natural Transformations

My lack of understanding of the natural transformation operator ~> and type quantifiers meant it took me some time to work out how to deal with the types. The important thing about ~> is that it hides the second type parameter of Eff. It turns out that in some situations, if we don’t use ~> we need to explicitly quantify this (LastMember IO effs, Member IO effs) => Text -> forall a. Eff (File ': effs) a -> Eff effs a (this also requires enabling the RankNTypes extension). See here

The simplest thing to do is just to use ~> in your interpreter’s type signatures. I had a basic understanding of natural transformations however I had never managed to quite equate them to programming. I found that using Eff and writing interpreters help me gain an intuition for what is going on.

Composing Effects

Now that we know how to properly define effect algebras and interpreters, lets compose 2 different effects. First we’ll create a new effect, File:

File.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}

module File where

import Control.Monad.Freer
( type (~>)
, Eff
, LastMember
, Member
, interpret
, interpretM
, send
)
import Control.Monad.Freer.Writer (Writer, tell)
import Data.Text (Text, pack)
import qualified Data.Text.IO as Text

data File r where
ReadFile :: FilePath -> File Text

readFile :: Member File effs => FilePath -> Eff effs Text
readFile = send . ReadFile

interpretIO ::
(LastMember IO effs, Member IO effs) => Eff (File ': effs) ~> Eff effs
interpretIO =
interpretM
(\case
ReadFile path -> Text.readFile path)

interpretPure :: Member (Writer Text) effs => Eff (File ': effs) ~> Eff effs
interpretPure =
interpret
(\case
ReadFile path -> do
tell $ "try to read file " <> pack path
pure "")

Now lets change our program so that it reads a file and outputs its contents to the console.

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}

module Main where

import Console (Console, putTextLn)
import qualified Console
import Control.Monad.Freer (Eff, Members, run, runM)
import Control.Monad.Freer.Writer (runWriter)
import Data.Text (Text, unpack)
import File (File)
import qualified File

myProgram :: Members '[ Console, File] effs => Eff effs ()
myProgram = do
contents <- File.readFile "myfile.txt"
putTextLn contents

main :: IO ()
main = do
let (_, pureMsg) =
run . runWriter . Console.interpretPure . File.interpretPure $ myProgram
putStrLn . unpack $ pureMsg
runM . Console.interpretIO . File.interpretIO $ myProgram

There are 2 big advantages here:

  1. It is easy to compose code that uses different effects, no more lift or defining loads of mtl-style instances. Instead we use normal function composition to compose interpreters.
  2. You can easily define different interpreters. For example one thing that was really nice in my program was that it was very easy to add a --dry-run flag to my program, if a user adds this flag I simply use pure interpreters for effects and build up a writer monad of what the code would have done if you had run it without the flag.

One thing to note is that interpreters don’t need to be totally pure or monadic, in my --dry-run case I composed IO interpreters with pure ones.

Summary

I wanted some interaction with the console so I built a Console effect algebra. I can use that effect in code that runs in the Eff monad as long as I add a constraint to say that I’m using that effect. I end up with code that runs in an Eff with a (type-level) list of constraints, for example [ Reader Env, Console, File].

I then put this code through various interpreters, each of which removes a constraint. Eventually I am left with an empty list or, if we wish to end up inside some monad, a list with one element.

  • An empty list represents a pure computation so I can then run it to get rid of Eff and return a pure value.
  • A list with one element represents a monadic computation, in my case this final effect was IO. I can then runM this computation to give me a monadic value, in my case IO a.

When you first use this library it can seem a bit complicated and it took me a while to get the hang of it but once you do, it’s quite simple and clean. In my opinion, a vast improvement over mtl-style code.

What are the downsides?

  1. The big downside that would stop freer monads becoming ubiquitous is performance, in certain situations they can be up to 30x slower than a monad transformer. Although there are no fundamental limits on how much this could be improved, it would probably require compiler integration and very clever optimazation so it’s highly likely that monad transformers will be faster for the foreseeable future.
  2. Although the example in the documentation seemed simple and understandable, once I started writing my own effects I found that the documentation was lacking information about how to compose different interpreters.
  3. I’m still unsure about when and where I should define custom effects. Define too many and you end up with an unwieldy constraints list as well as a big final interpretation function. Define too few and you are unable to get the level of control over interpretation that you may wish.

I will definitely use freer-simple again, I felt it made my code much better than it would have been without it. As for performance, in most applications it is likely that Eff won’t be a bottleneck and if it is you can quite easily fall back to monad transformers in specific parts of your code.

Is this the same as Eff in Purescript?

If you’ve ever used Eff purescript then the Eff monad from freer-simple looks very similar on the surface. It uses type-level lists of constraints in place of row types but the lists are unordered so the effect is the same. It’s not quite as pretty as purescript but it’s close.

However the Eff in purescript is basically just tagged IO, whereas the Eff in freer-simple is a Freer monad, this means it defines an algebra of effects and you separately define interpreters to handle those effects.