freer-simple-1.2.1.2: A friendly effect system for Haskell.
Copyright(c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King
LicenseBSD3
MaintainerAlexis King <lexi.lambda@gmail.com>
Stabilityexperimental
PortabilityGHC specific language extensions.
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Freer

Description

This library is an implementation of an extensible effect system for Haskell, a general-purpose way of tracking effects at the type level and handling them in different ways. The concept of an “effect” is very general: it encompasses the things most people consider side-effects, like generating random values, interacting with the file system, and mutating state, but it also includes things like access to an immutable global environment and exception handling.

Traditional Haskell tracks and composes effects using monad transformers, which involves modeling each effects using what is conceptually a separate monad. In contrast, freer-simple provides exactly one monad, Eff, parameterized by a type-level list of effects. For example, a computation that produces an Integer by consuming a String from the global environment and acting upon a single mutable cell containing a Bool would have the following type:

Eff '[Reader String, State Bool] Integer

For comparison, this is the equivalent stack of monad transformers:

ReaderT String (State Bool) Integer

However, this is slightly misleading: the example with Eff is actually more general than the corresponding example using transformers because the implementations of effects are not concrete. While StateT specifies a specific implementation of a pseudo-mutable cell, State is merely an interface with a set of available operations. Using runState will “run” the State effect much the same way that StateT does, but a hypothetical handler function runStateTVar could implement the state in terms of a STM TVar.

The freer-simple effect library is divided into three parts:

  1. First, freer-simple provides the Eff monad, an implementation of extensible effects that allows effects to be tracked at the type level and interleaved at runtime.
  2. Second, it provides a built-in library of common effects, such as Reader, Writer, State, and Error. These effects can be used with Eff out of the box with an interface that is similar to the equivalent monad transformers.
  3. Third, it provides a set of combinators for implementing your own effects, which can either be implemented entirely independently, in terms of other existing effects, or even in terms of existing monads, making it possible to use freer-simple with existing monad transformer stacks.

One of the core ideas of freer-simple is that most effects that occur in practical applications are really different incarnations of a small set of fundamental effect types. Therefore, while it’s possible to write new effect handlers entirely from scratch, it’s more common that you will wish to define new effects in terms of other effects. freer-simple makes this possible by providing the reinterpret function, which allows translating an effect into another one.

For example, imagine an effect that represents interactions with a file system:

data FileSystem r where
  ReadFile :: FilePath -> FileSystem String
  WriteFile :: FilePath -> String -> FileSystem ()

An implementation that uses the real file system would, of course, be implemented in terms of IO. An alternate implementation, however, might be implemented in-memory in terms of State. With reinterpret, this implementation is trivial:

runInMemoryFileSystem :: [(FilePath, String)] -> Eff (FileSystem ': effs) ~> Eff effs
runInMemoryFileSystem initVfs = evalState initVfs . fsToState where
  fsToState :: Eff (FileSystem ': effs) ~> Eff (State [(FilePath, String)] ': effs)
  fsToState = reinterpret $ case
    ReadFile path -> get >>= \vfs -> case lookup path vfs of
      Just contents -> pure contents
      Nothing -> error ("readFile: no such file " ++ path)
    WriteFile path contents -> modify $ \vfs ->
      (path, contents) : deleteBy ((==) `on` fst) (path, contents) vfs

This handler is easy to write, doesn’t require any knowledge of how State is implemented, is entirely encapsulated, and is composable with all other effect handlers. This idea—making it easy to define new effects in terms of existing ones—is the concept around which freer-simple is based.

Effect Algebras

In freer-simple, effects are defined using effect algebras, which are representations of an effect’s operations as a generalized algebraic datatype, aka GADT. This might sound intimidating, but you really don’t need to know very much at all about how GADTs work to use freer-simple; instead, you can just learn the syntax entirely in terms of what it means for defining effects.

Consider the definition of the FileSystem effect from the above example:

data FileSystem r where
  ReadFile :: FilePath -> FileSystem String
  WriteFile :: FilePath -> String -> FileSystem ()

The first line, data FileSystem r where, defines a new effect. All effects have at least one parameter, normally named r, which represents the result or return type of the operation. For example, take a look at the type of ReadFile:

ReadFile :: FilePath -> FileSystem String

This is very similar to the type of readFile from the standard Prelude, which has type FilePath -> IO String. The only difference is that the name of the effect, in this case FileSystem, replaces the use of the monad, in this case IO.

Also notice that ReadFile and WriteFile begin with capital letters. This is because they are actually data constructors. This means that ReadFile "foo.txt" actually constructs a value of type FileSystem String, and this is useful, since it allows effect handlers like runInMemoryFileSystem to pattern-match on the effect’s constructors and get the values out.

To actually use our FileSystem effect, however, we have to write just a little bit of glue to connect our effect definition to the Eff monad, which we do using the send function. We can write an ordinary function for each of the FileSystem constructors that mechanically calls send:

readFile :: Member FileSystem effs => FilePath -> Eff effs String
readFile path = send (ReadFile path)

writeFile :: Member FileSystem effs => FilePath -> String -> Eff effs ()
writeFile path contents = send (WriteFile path contents)

Notice the use of the Member constraint on these functions. This constraint means that the FileSystem effect can be anywhere within the type-level list represented by the effs variable. If the signature of readFile were more concrete, like this:

readFile :: FilePath -> Eff '[FileSystem] String

…then readFile would only be usable with an Eff computation that only performed FileSystem effects, which isn’t especially useful.

Since writing these functions is entirely mechanical, they can be generated automatically using Template Haskell; see Control.Monad.Freer.TH for more details.

Synopsis

Effect Monad

data Eff effs a Source #

The Eff monad provides the implementation of a computation that performs an arbitrary set of algebraic effects. In Eff effs a, effs is a type-level list that contains all the effects that the computation may perform. For example, a computation that produces an Integer by consuming a String from the global environment and acting upon a single mutable cell containing a Bool would have the following type:

Eff '[Reader String, State Bool] Integer

Normally, a concrete list of effects is not used to parameterize Eff. Instead, the Member or Members constraints are used to express constraints on the list of effects without coupling a computation to a concrete list of effects. For example, the above example would more commonly be expressed with the following type:

Members '[Reader String, State Bool] effs => Eff effs Integer

This abstraction allows the computation to be used in functions that may perform other effects, and it also allows the effects to be handled in any order.

Instances

Instances details
(MonadBase b m, LastMember m effs) => MonadBase b (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

liftBase :: b α -> Eff effs α #

Monad (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

(>>=) :: Eff effs a -> (a -> Eff effs b) -> Eff effs b #

(>>) :: Eff effs a -> Eff effs b -> Eff effs b #

return :: a -> Eff effs a #

Functor (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

fmap :: (a -> b) -> Eff effs a -> Eff effs b #

(<$) :: a -> Eff effs b -> Eff effs a #

Applicative (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

pure :: a -> Eff effs a #

(<*>) :: Eff effs (a -> b) -> Eff effs a -> Eff effs b #

liftA2 :: (a -> b -> c) -> Eff effs a -> Eff effs b -> Eff effs c #

(*>) :: Eff effs a -> Eff effs b -> Eff effs b #

(<*) :: Eff effs a -> Eff effs b -> Eff effs a #

(MonadIO m, LastMember m effs) => MonadIO (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

liftIO :: IO a -> Eff effs a #

Member NonDet effs => Alternative (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

empty :: Eff effs a #

(<|>) :: Eff effs a -> Eff effs a -> Eff effs a #

some :: Eff effs a -> Eff effs [a] #

many :: Eff effs a -> Eff effs [a] #

Member NonDet effs => MonadPlus (Eff effs) Source # 
Instance details

Defined in Control.Monad.Freer.Internal

Methods

mzero :: Eff effs a #

mplus :: Eff effs a -> Eff effs a -> Eff effs a #

Effect Constraints

As mentioned in the documentation for Eff, it’s rare to actually specify a concrete list of effects for an Eff computation, since that has two significant downsides:

  1. It couples the computation to that specific list of effects, so it cannot be used in functions that perform a strict superset of effects.
  2. It forces the effects to be handled in a particular order, which can make handler code brittle when the list of effects is changed.

Fortunately, these restrictions are easily avoided by using effect constraints, such as Member or Members, which decouple a computation from a particular concrete list of effects.

class FindElem eff effs => Member (eff :: Type -> Type) effs Source #

A constraint that requires that a particular effect, eff, is a member of the type-level list effs. This is used to parameterize an Eff computation over an arbitrary list of effects, so long as eff is somewhere in the list.

For example, a computation that only needs access to a cell of mutable state containing an Integer would likely use the following type:

Member (State Integer) effs => Eff effs ()

Minimal complete definition

inj, prj

Instances

Instances details
(FindElem t r, IfNotFound t r r) => Member t r Source # 
Instance details

Defined in Data.OpenUnion.Internal

Methods

inj :: t a -> Union r a Source #

prj :: Union r a -> Maybe (t a) Source #

type family Members effs effs' :: Constraint where ... Source #

A shorthand constraint that represents a combination of multiple Member constraints. That is, the following Members constraint:

Members '[Foo, Bar, Baz] effs

…is equivalent to the following set of Member constraints:

(Member Foo effs, Member Bar effs, Member baz effs)

Note that, since each effect is translated into a separate Member constraint, the order of the effects does not matter.

Equations

Members (eff ': effs) effs' = (Member eff effs', Members effs effs') 
Members '[] effs' = () 

class Member m effs => LastMember m effs | effs -> m Source #

Like Member, LastMember eff effs is a constraint that requires that eff is in the type-level list effs. However, unlike Member, LastMember requires m be the final effect in effs.

Generally, this is not especially useful, since it is preferable for computations to be agnostic to the order of effects, but it is quite useful in combination with sendM or liftBase to embed ordinary monadic effects within an Eff computation.

Instances

Instances details
LastMember m '[m] Source # 
Instance details

Defined in Data.OpenUnion

LastMember m effs => LastMember m (eff ': effs) Source # 
Instance details

Defined in Data.OpenUnion

Sending Arbitrary Effects

send :: Member eff effs => eff a -> Eff effs a Source #

“Sends” an effect, which should be a value defined as part of an effect algebra (see the module documentation for Control.Monad.Freer), to an effectful computation. This is used to connect the definition of an effect to the Eff monad so that it can be used and handled.

sendM :: (Monad m, LastMember m effs) => m a -> Eff effs a Source #

Identical to send, but specialized to the final effect in effs to assist type inference. This is useful for running actions in a monad transformer stack used in conjunction with runM.

Lifting Effect Stacks

raise :: Eff effs a -> Eff (e ': effs) a Source #

Embeds a less-constrained Eff into a more-constrained one. Analogous to MTL's lift.

Handling Effects

Once an effectful computation has been produced, it needs to somehow be executed. This is where effect handlers come in. Each effect can have an arbitrary number of different effect handlers, which can be used to interpret the same effects in different ways. For example, it is often useful to have two effect handlers: one that uses sendM and interpretM to interpret the effect in IO, and another that uses interpret, reinterpret, or translate to interpret the effect in an entirely pure way for the purposes of testing.

This module doesn’t provide any effects or effect handlers (those are in their own modules, like Control.Monad.Freer.Reader and Control.Monad.Freer.Error), but it does provide a set of combinators for constructing new effect handlers. It also provides the run and runM functions for extracting the actual result of an effectful computation once all effects have been handled.

Running the Eff monad

run :: Eff '[] a -> a Source #

Runs a pure Eff computation, since an Eff computation that performs no effects (i.e. has no effects in its type-level list) is guaranteed to be pure. This is usually used as the final step of running an effectful computation, after all other effects have been discharged using effect handlers.

Typically, this function is composed as follows:

someProgram
  & runEff1 eff1Arg
  & runEff2 eff2Arg1 eff2Arg2
  & run

runM :: Monad m => Eff '[m] a -> m a Source #

Like run, runM runs an Eff computation and extracts the result. Unlike run, runM allows a single effect to remain within the type-level list, which must be a monad. The value returned is a computation in that monad, which is useful in conjunction with sendM or liftBase for plugging in traditional transformer stacks.

Building Effect Handlers

Basic effect handlers

interpret :: forall eff effs. (eff ~> Eff effs) -> Eff (eff ': effs) ~> Eff effs Source #

The simplest way to produce an effect handler. Given a natural transformation from some effect eff to some effectful computation with effects effs, produces a natural transformation from Eff (eff ': effs) to Eff effs.

interpose :: forall eff effs. Member eff effs => (eff ~> Eff effs) -> Eff effs ~> Eff effs Source #

Like interpret, but instead of handling the effect, allows responding to the effect while leaving it unhandled.

subsume :: forall eff effs. Member eff effs => Eff (eff ': effs) ~> Eff effs Source #

Interprets an effect in terms of another identical effect. This can be used to eliminate duplicate effects.

Derived effect handlers

reinterpret :: forall f g effs. (f ~> Eff (g ': effs)) -> Eff (f ': effs) ~> Eff (g ': effs) Source #

Like interpret, but instead of removing the interpreted effect f, reencodes it in some new effect g.

reinterpret2 :: forall f g h effs. (f ~> Eff (g ': (h ': effs))) -> Eff (f ': effs) ~> Eff (g ': (h ': effs)) Source #

Like reinterpret, but encodes the f effect in two new effects instead of just one.

reinterpret3 :: forall f g h i effs. (f ~> Eff (g ': (h ': (i ': effs)))) -> Eff (f ': effs) ~> Eff (g ': (h ': (i ': effs))) Source #

Like reinterpret, but encodes the f effect in three new effects instead of just one.

reinterpretN :: forall gs f effs. Weakens gs => (f ~> Eff (gs :++: effs)) -> Eff (f ': effs) ~> Eff (gs :++: effs) Source #

Like interpret, reinterpret, reinterpret2, and reinterpret3, but allows the result to have any number of additional effects instead of simply 0-3. The problem is that this completely breaks type inference, so you will have to explicitly pick gs using TypeApplications. Prefer interpret, reinterpret, reinterpret2, or reinterpret3 where possible.

translate :: forall f g effs. (f ~> g) -> Eff (f ': effs) ~> Eff (g ': effs) Source #

Runs an effect by translating it into another effect. This is effectively a more restricted form of reinterpret, since both produce a natural transformation from Eff (f ': effs) to Eff (g ': effs) for some effects f and g, but translate does not permit using any of the other effects in the implementation of the interpreter.

In practice, this difference in functionality is not particularly useful, and reinterpret easily subsumes all of the functionality of translate, but the way translate restricts the result leads to much better type inference.

translate f = reinterpret (send . f)

Monadic effect handlers

interpretM :: forall eff m effs. (Monad m, LastMember m effs) => (eff ~> m) -> Eff (eff ': effs) ~> Eff effs Source #

Like interpret, this function runs an effect without introducing another one. Like translate, this function runs an effect by translating it into another effect in isolation, without access to the other effects in effs. Unlike either of those functions, however, this runs the effect in a final monad in effs, intended to be run with runM.

interpretM f = interpret (sendM . f)

Advanced effect handlers

interpretWith :: forall eff effs b. (forall v. eff v -> (v -> Eff effs b) -> Eff effs b) -> Eff (eff ': effs) b -> Eff effs b Source #

A highly general way of handling an effect. Like interpret, but explicitly passes the continuation, a function of type v -> Eff effs b, to the handler function. Most handlers invoke this continuation to resume the computation with a particular value as the result, but some handlers may return a value without resumption, effectively aborting the computation to the point where the handler is invoked. This is useful for implementing things like catchError, for example.

interpret f = interpretWith (e -> (f e >>=))

interposeWith :: forall eff effs b. Member eff effs => (forall v. eff v -> (v -> Eff effs b) -> Eff effs b) -> Eff effs b -> Eff effs b Source #

Combines the interposition behavior of interpose with the continuation-passing capabilities of interpretWith.

interpose f = interposeWith (e -> (f e >>=))

Re-exported bindings

type (~>) (f :: k -> Type) (g :: k -> Type) = forall (x :: k). f x -> g x infixr 0 #

A natural transformation from f to g.