Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library implements an extensible effects system, where sets of monadic actions ("effects") are encoded as
datatypes, tracked at the type level and can have multiple different implementations. This means you can swap out
implementations of certain monadic actions in mock tests or in different environments. The notion of "effect" is
general here: it can be an IO
-performing side effect, or just obtaining the value of a static global environment.
In particular, this library consists of
- The
Eff
monad, which is the core of an extensible effects system. All effects are performed within it and it will be the "main" monad of your application. This monad tracks effects at the type level. - A set of predefined general effects, like
Reader
andState
that can be used out of the box. - Combinators for defining new effects and interpreting them on your own. These effects can be translated in terms
of other already existing effects, or into operations in the
IO
monad.
So, this library allows you to do two things:
- Effect management: The
Eff
monad tracks what effects are used explicitly at the type level, therefore you are able to be certain about what effects are involved in each function. - Effect decoupling: You can decouple the implementation of the effects from your application and swap them easily.
Synopsis
- data Eff es a
- type (:>) = Elem
- type family xs :>> es :: Constraint where ...
- type Effect = (Type -> Type) -> Type -> Type
- data IOE :: Effect
- runPure :: Eff '[] a -> a
- runIOE :: Eff '[IOE] ~> IO
- send :: e :> es => e (Eff es) ~> Eff es
- makeEffect :: Name -> Q [Dec]
- makeEffect_ :: Name -> Q [Dec]
- raise :: forall e es. Eff es ~> Eff (e ': es)
- raiseN :: forall es' es. KnownList es' => Eff es ~> Eff (es' ++ es)
- inject :: forall es' es. Subset es' es => Eff es' ~> Eff es
- subsume :: forall e es. e :> es => Eff (e ': es) ~> Eff es
- subsumeN :: forall es' es. Subset es' es => Eff (es' ++ es) ~> Eff es
- class KnownList (es :: [k])
- class KnownList es => Subset (es :: [k]) (es' :: [k])
- type Handler e es = forall esSend. Handling e es esSend => e (Eff esSend) ~> Eff es
- interpret :: forall e es. Handler e es -> Eff (e ': es) ~> Eff es
- reinterpret :: forall e' e es. Handler e (e' ': es) -> Eff (e ': es) ~> Eff (e' ': es)
- reinterpret2 :: forall e' e'' e es. Handler e (e' ': (e'' ': es)) -> Eff (e ': es) ~> Eff (e' ': (e'' ': es))
- reinterpret3 :: forall e' e'' e''' e es. Handler e (e' ': (e'' ': (e''' ': es))) -> Eff (e ': es) ~> Eff (e' ': (e'' ': (e''' ': es)))
- reinterpretN :: forall es' e es. KnownList es' => Handler e (es' ++ es) -> Eff (e ': es) ~> Eff (es' ++ es)
- interpose :: forall e es. e :> es => Handler e es -> Eff es ~> Eff es
- impose :: forall e' e es. e :> es => Handler e (e' ': es) -> Eff es ~> Eff (e' ': es)
- imposeN :: forall es' e es. (KnownList es', e :> es) => Handler e (es' ++ es) -> Eff es ~> Eff (es' ++ es)
- type HandlerIO e es = forall esSend. Handling e es esSend => e (Eff esSend) ~> IO
- interpretIO :: IOE :> es => HandlerIO e es -> Eff (e ': es) ~> Eff es
- type Translator e e' = forall esSend. e (Eff esSend) ~> e' (Eff esSend)
- transform :: forall e' e es. e' :> es => Translator e e' -> Eff (e ': es) ~> Eff es
- translate :: forall e' e es. Translator e e' -> Eff (e ': es) ~> Eff (e' ': es)
- class Handling e es esSend | e -> es esSend, es -> e esSend, esSend -> e es
- toEff :: Handling e es esSend => Eff esSend ~> Eff es
- toEffWith :: Handling e es esSend => Handler e es -> Eff esSend ~> Eff es
- withFromEff :: Handling e es esSend => ((Eff es ~> Eff esSend) -> Eff esSend a) -> Eff es a
- withToIO :: (Handling e es esSend, IOE :> es) => ((Eff esSend ~> IO) -> IO a) -> Eff es a
- fromIO :: (Handling e es esSend, IOE :> es) => IO ~> Eff esSend
- type (~>) f g = forall a. f a -> g a
- type family xs ++ ys where ...
- class Monad m => MonadIO (m :: Type -> Type) where
- class MonadIO m => MonadUnliftIO (m :: Type -> Type) where
- withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b
Using effects
The extensible effect monad. A monad
is capable of performing any effect in the effect stack Eff
eses
,
which is a type-level list that holds all effects available. However, most of the times, for flexibility, es
should be a polymorphic type variable, and you should use the (:>)
and (:>>)
operators in constraints to
indicate what effects are in the stack. For example,
Reader
String
:>
es,State
Bool
:>
es =>Eff
esInteger
allows you to perform operations of the
effect and the Reader
String
effect in a computation returning an State
Bool
Integer
.
Instances
IOE :> es => MonadBase IO (Eff es) Source # | Compatibility instance; use |
Defined in Cleff.Internal.Base | |
IOE :> es => MonadBaseControl IO (Eff es) Source # | Compatibility instance; use |
Monad (Eff es) Source # | |
Functor (Eff es) Source # | |
MonadFix (Eff es) Source # | |
Defined in Cleff.Internal.Monad | |
Fail :> es => MonadFail (Eff es) Source # | |
Defined in Cleff.Fail | |
Applicative (Eff es) Source # | |
IOE :> es => MonadIO (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
IOE :> es => MonadThrow (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
IOE :> es => MonadCatch (Eff es) Source # | |
IOE :> es => MonadMask (Eff es) Source # | |
IOE :> es => PrimMonad (Eff es) Source # | |
IOE :> es => MonadUnliftIO (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
Semigroup a => Semigroup (Eff es a) Source # | |
Monoid a => Monoid (Eff es a) Source # | |
type PrimState (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
type StM (Eff es) a Source # | |
Defined in Cleff.Internal.Base |
type family xs :>> es :: Constraint where ... infix 0 Source #
The effect for lifting and unlifting the IO
monad, allowing you to use MonadIO
, MonadUnliftIO
, PrimMonad
,
MonadCatch
, MonadThrow
and MonadMask
functionalities. This is the "final" effect that most effects eventually
are interpreted into. For example, you can do:
log ::IOE
:> es =>Eff
es () log =liftIO
(putStrLn
"Test logging")
It is not recommended to use this effect in application code, as it is too liberal and allows arbitrary IO. Ideally, this is only used in interpreting more fine-grained effects.
Note that this is not a real effect and cannot be interpreted in any way besides thisIsPureTrustMe
and
runIOE
. It is similar to Polysemy's Final
effect which also cannot be interpreted. This is mainly for
performance concern, but also that there doesn't really exist reasonable interpretations other than the current one,
given the underlying implementation of the Eff
monad.
IOE
can be a real effect though, and you can enable the dynamic-ioe
build flag to have that. However it is only
for reference purposes and should not be used in production code.
Running effects
To run an effect T
, we should use an interpreter of T
, which is a function that has type like this:
runT ::Eff
(T ': es) a ->Eff
es a
Such an interpreter provides an implementation of T
and eliminates T
from the effect stack. All builtin effects
in cleff
have interpreters coming together with them.
By applying interpreters to an Eff
computation, you can eventually obtain an end computation, where there are no
more effects present on the effect stack. There are two kinds of end computations:
runPure :: Eff '[] a -> a Source #
Unwrap a pure Eff
computation into a pure value, given that all effects are interpreted.
Defining effects
An effect should be defined as a GADT and have the kind Effect
. Each operation in the effect is a constructor of
the effect type. For example, an effect supporting reading/writing files can be as following:
data Filesystem ::Effect
where ReadFile ::FilePath
-> Filesystem mString
WriteFile ::FilePath
->String
-> Filesystem m ()
Operations constructed with these constructors can be performed via the send
function. You can also use the
Template Haskell function makeEffect
to automatically generate definitions of functions that perform the effects.
For example,
makeEffect
''Filesystem
generates the following definitions:
readFile :: Filesystem:>
es =>FilePath
->Eff
esString
readFile x =send
(ReadFile x) writeFile :: Filesystem:>
es =>FilePath
->String
->Eff
es () writeFile x y =send
(WriteFile x y)
send :: e :> es => e (Eff es) ~> Eff es Source #
Perform an effect operation, i.e. a value of an effect type e ::
. This requires Effect
e
to be in the
effect stack.
makeEffect :: Name -> Q [Dec] Source #
For a datatype T
representing an effect,
generates functions defintions for performing the
operations of makeEffect
TT
via send
. The naming rule is changing the first uppercase letter in the constructor name to
lowercase or removing the :
symbol in the case of operator constructors. Also, this function will preserve any
fixity declarations defined on the constructors.
Because of the limitations of Template Haskell, all constructors of T
should be polymorphic in the monad type,
if they are to be used by makeEffect
. For example, this is not OK:
data Limited ::Effect
where Noop :: Limited (Eff
es) ()
because the monad type
is not a fully polymorphic type variable.Eff
es
This function is also "weaker" than polysemy
's makeSem
, because this function cannot properly handle some
cases involving complex higher order effects. Those cases are rare, though. See the tests for more details.
makeEffect_ :: Name -> Q [Dec] Source #
Like makeEffect
, but doesn't generate type signatures. This is useful when you want to attach Haddock
documentation to the function signature, e.g.:
data Identity ::Effect
where Noop :: Identity m ()makeEffect_
''Identity -- | Perform nothing at all. noop :: Identity:>
es =>Eff
es ()
Be careful that the function signatures must be added after the makeEffect_
call.
Trivial effects handling
raise :: forall e es. Eff es ~> Eff (e ': es) Source #
Lift a computation into a bigger effect stack with one more effect. For a more general version see raiseN
.
raiseN :: forall es' es. KnownList es' => Eff es ~> Eff (es' ++ es) Source #
Lift a computation into a bigger effect stack with arbitrarily more effects. This function requires
TypeApplications
.
inject :: forall es' es. Subset es' es => Eff es' ~> Eff es Source #
Lift a computation with a fixed, known effect stack into some superset of the stack.
subsume :: forall e es. e :> es => Eff (e ': es) ~> Eff es Source #
Eliminate a duplicate effect from the top of the effect stack. For a more general version see subsumeN
.
subsumeN :: forall es' es. Subset es' es => Eff (es' ++ es) ~> Eff es Source #
Eliminate several duplicate effects from the top of the effect stack. This function requires TypeApplications
.
class KnownList (es :: [k]) Source #
The list es
list is concrete, i.e. is of the form '[a1, a2, ..., an]
, i.e. is not a type variable.
Interpreting effects
An effect can be understood as the "grammar" (or syntax) of a small language; however we also need to define the "meaning" (or semantics) of the language. In other words, we need to specify the implementation of effects.
In an extensible effects system, this is achieved by writing effect handlers, which are functions that transforms operations of one effect into other "more primitive" effects. These handlers can then be used to make interpreters with library functions that we'll now see.
This is very easy to do. For example, for the Filesystem
effect
data Filesystem ::Effect
where ReadFile ::FilePath
-> Filesystem mString
WriteFile ::FilePath
->String
-> Filesystem m ()
We can easily handle it in terms of IO
operations via interpretIO
, by pattern matching on the effect
constructors:
runFilesystemIO ::IOE
:>
es =>Eff
(Filesystem ': es) a ->Eff
es a runFilesystemIO =interpretIO
\case ReadFile path ->readFile
path WriteFile path contents ->writeFile
path contents
Alternatively, we can also construct an in-memory filesystem in terms of the State
effect via
the reinterpret
function.
runFilesystemPure ::Fail
:>
es =>Map
FilePath
String
->Eff
(Filesystem ': es) a ->Eff
es a runFilesystemPure fs =fmap
fst
.
runState
fs.
reinterpret
\case ReadFile path ->gets
(lookup
path) >>= \caseNothing
->fail
("File not found: " ++show
path)Just
contents ->pure
contents WriteFile path contents ->modify
(insert
path contents)
These interpreters can then be applied to computations with the Filesystem
effect to give different implementations
to the effect.
type Handler e es = forall esSend. Handling e es esSend => e (Eff esSend) ~> Eff es Source #
The type of an effect handler, which is a function that transforms an effect e
from an arbitrary effect stack
into computations in the effect stack es
.
interpret :: forall e es. Handler e es -> Eff (e ': es) ~> Eff es Source #
Interpret an effect e
in terms of effects in the effect stack es
with an effect handler.
reinterpret :: forall e' e es. Handler e (e' ': es) -> Eff (e ': es) ~> Eff (e' ': es) Source #
Like interpret
, but adds a new effect e'
that can be used in the handler.
reinterpret2 :: forall e' e'' e es. Handler e (e' ': (e'' ': es)) -> Eff (e ': es) ~> Eff (e' ': (e'' ': es)) Source #
Like reinterpret
, but adds two new effects.
reinterpret3 :: forall e' e'' e''' e es. Handler e (e' ': (e'' ': (e''' ': es))) -> Eff (e ': es) ~> Eff (e' ': (e'' ': (e''' ': es))) Source #
Like reinterpret
, but adds three new effects.
reinterpretN :: forall es' e es. KnownList es' => Handler e (es' ++ es) -> Eff (e ': es) ~> Eff (es' ++ es) Source #
Like reinterpret
, but adds arbitrarily many new effects. This function requires TypeApplications
.
interpose :: forall e es. e :> es => Handler e es -> Eff es ~> Eff es Source #
Respond to an effect while being able to leave it unhandled (i.e. you can resend the effects in the handler).
impose :: forall e' e es. e :> es => Handler e (e' ': es) -> Eff es ~> Eff (e' ': es) Source #
Like interpose
, but allows to introduce one new effect to use in the handler.
imposeN :: forall es' e es. (KnownList es', e :> es) => Handler e (es' ++ es) -> Eff es ~> Eff (es' ++ es) Source #
Like impose
, but allows introducing arbitrarily many effects. This requires TypeApplications
.
Interpreting in terms of IO
type HandlerIO e es = forall esSend. Handling e es esSend => e (Eff esSend) ~> IO Source #
The type of an IO
effect handler, which is a function that transforms an effect e
into IO
computations.
This is used for interpretIO
.
Translating effects
type Translator e e' = forall esSend. e (Eff esSend) ~> e' (Eff esSend) Source #
The type of a simple transformation function from effect e
to e'
.
transform :: forall e' e es. e' :> es => Translator e e' -> Eff (e ': es) ~> Eff es Source #
Interpret an effect in terms of another effect in the stack via a simple Translator
.
translate :: forall e' e es. Translator e e' -> Eff (e ': es) ~> Eff (e' ': es) Source #
Like transform
, but instead of using an effect in stack, add a new one to the top of it.
Combinators for interpreting higher order effects
Higher order effects are effects whose operations take other effect computations as arguments. For example, the
Error
effect is a higher order effect, because its CatchError
operation takes an effect
computation that may throw errors and also an error handler that returns an effect computation:
data Error e :: Effect
where
ThrowError :: e -> Error e m a
CatchError :: m a -> (e -> m a) -> Error e m a
More literally, an high order effect makes use of the monad type paramenter m
, while a first order effect, like
State
, does not.
It is harder to write interpreters for higher order effects, because we need to transform computations from arbitrary effect stacks into a specific stack that the effect is currently interpreted into. In other words, they need to thread other effects through themselves. This is why Cleff also provides convenient combinators for doing so.
In a Handler
, you can temporarily "unlift" a computation from an arbitrary effect stack into the current stack via
toEff
, explicitly change the current effect interpretation in the computation via toEffWith
, or directly express
the effect in terms of IO
via withToIO
.
class Handling e es esSend | e -> es esSend, es -> e esSend, esSend -> e es Source #
The typeclass that indicates a handler scope, handling effect e
sent from the effect stack esSend
in the
effect stack es
.
You should not define instances for this typeclass whatsoever.
toEffWith :: Handling e es esSend => Handler e es -> Eff esSend ~> Eff es Source #
Run a computation in the current effect stack, but handles the current effect inside the computation differently
by providing a new Handler
. This is useful for interpreting effects with local contexts, like Local
:
runReader :: r ->Eff
(Reader
r ': es)~>
Eff
es runReader x =interpret
(handle x) where handle :: r ->Handler
(Reader
r) es handle r = \caseAsk
->pure
rLocal
f m ->toEffWith
(handle $ f r) m
withFromEff :: Handling e es esSend => ((Eff es ~> Eff esSend) -> Eff esSend a) -> Eff es a Source #
Interpreting IO
-related higher order effects
Miscellaneous
type (~>) f g = forall a. f a -> g a infixr 0 Source #
The type of natural transformations from functor f
to g
.
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
class MonadIO m => MonadUnliftIO (m :: Type -> Type) where #
Monads which allow their actions to be run in IO
.
While MonadIO
allows an IO
action to be lifted into another
monad, this class captures the opposite concept: allowing you to
capture the monadic context. Note that, in order to meet the laws
given below, the intuition is that a monad must have no monadic
state, but may have monadic context. This essentially limits
MonadUnliftIO
to ReaderT
and IdentityT
transformers on top of
IO
.
Laws. For any value u
returned by askUnliftIO
, it must meet the
monad transformer laws as reformulated for MonadUnliftIO
:
unliftIO u . return = return
unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f
Instances of MonadUnliftIO
must also satisfy the idempotency law:
askUnliftIO >>= \u -> (liftIO . unliftIO u) m = m
This law showcases two properties. First, askUnliftIO
doesn't change
the monadic context, and second, liftIO . unliftIO u
is equivalent to
id
IF called in the same monadic context as askUnliftIO
.
Since: unliftio-core-0.1.0.0
withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b #
Convenience function for capturing the monadic context and running an IO
action with a runner function. The runner function is used to run a monadic
action m
in IO
.
Since: unliftio-core-0.1.0.0
Instances
MonadUnliftIO IO | |
Defined in Control.Monad.IO.Unlift | |
IOE :> es => MonadUnliftIO (Eff es) Source # | |
Defined in Cleff.Internal.Base | |
MonadUnliftIO m => MonadUnliftIO (ReaderT r m) | |
Defined in Control.Monad.IO.Unlift | |
MonadUnliftIO m => MonadUnliftIO (IdentityT m) | |
Defined in Control.Monad.IO.Unlift |