cleff-0.3.2.0: Fast and concise extensible effects
Copyright(c) 2021 Xy Ren
LicenseBSD3
Maintainerxy.r@outlook.com
Stabilityexperimental
Portabilitynon-portable (GHC only)
Safe HaskellTrustworthy
LanguageHaskell2010

Cleff

Description

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 reading 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 and State 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.

In terms of structuring your application, this library helps 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 enforce what effects are involved in each function, and avoid accidentally introduced behaviors.
  • Effect decoupling: You can swap between the implementations of the effects in your application easily, so you can refactor and test your applications with less clutter.
Synopsis

Using effects

data Eff es a Source #

The extensible effects monad. The monad Eff es is capable of performing any effect in the effect stack es, which is a type-level list that holds all effects available.

The best practice is to always use a polymorphic type variable for the effect stack es, and then use the type operators (:>) and (:>>) in constraints to indicate what effects are available in the stack. For example,

(Reader String :> es, State Bool :> es) => Eff es Integer

means you can perform operations of the Reader String effect and the State Bool effect in a computation returning an Integer. The reason why you should always use a polymorphic effect stack as opposed to a concrete list of effects are that

  • it can contain other effects that are used by computations other than the current one, and
  • it does not require you to run the effects in any particular order.

Instances

Instances details
IOE :> es => MonadBase IO (Eff es) Source #

Compatibility instance; use MonadIO if possible.

Instance details

Defined in Cleff.Internal.Base

Methods

liftBase :: IO α -> Eff es α #

IOE :> es => MonadBaseControl IO (Eff es) Source #

Compatibility instance; use MonadUnliftIO if possible.

Instance details

Defined in Cleff.Internal.Base

Associated Types

type StM (Eff es) a #

Methods

liftBaseWith :: (RunInBase (Eff es) IO -> IO a) -> Eff es a #

restoreM :: StM (Eff es) a -> Eff es a #

Monad (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Monad

Methods

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

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

return :: a -> Eff es a #

Functor (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Monad

Methods

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

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

MonadFix (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Monad

Methods

mfix :: (a -> Eff es a) -> Eff es a #

Fail :> es => MonadFail (Eff es) Source # 
Instance details

Defined in Cleff.Fail

Methods

fail :: String -> Eff es a #

Applicative (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Monad

Methods

pure :: a -> Eff es a #

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

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

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

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

MonadZip (Eff es) Source #

Compatibility instance for MonadComprehensions.

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

mzip :: Eff es a -> Eff es b -> Eff es (a, b) #

mzipWith :: (a -> b -> c) -> Eff es a -> Eff es b -> Eff es c #

munzip :: Eff es (a, b) -> (Eff es a, Eff es b) #

IOE :> es => MonadIO (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

liftIO :: IO a -> Eff es a #

IOE :> es => MonadThrow (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

throwM :: Exception e => e -> Eff es a #

IOE :> es => MonadCatch (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

catch :: Exception e => Eff es a -> (e -> Eff es a) -> Eff es a #

IOE :> es => MonadMask (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

mask :: ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b #

uninterruptibleMask :: ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b #

generalBracket :: Eff es a -> (a -> ExitCase b -> Eff es c) -> (a -> Eff es b) -> Eff es (b, c) #

IOE :> es => PrimMonad (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Associated Types

type PrimState (Eff es) #

Methods

primitive :: (State# (PrimState (Eff es)) -> (# State# (PrimState (Eff es)), a #)) -> Eff es a #

IOE :> es => MonadUnliftIO (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

withRunInIO :: ((forall a. Eff es a -> IO a) -> IO b) -> Eff es b #

Bounded a => Bounded (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

minBound :: Eff es a #

maxBound :: Eff es a #

Floating a => Floating (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

pi :: Eff es a #

exp :: Eff es a -> Eff es a #

log :: Eff es a -> Eff es a #

sqrt :: Eff es a -> Eff es a #

(**) :: Eff es a -> Eff es a -> Eff es a #

logBase :: Eff es a -> Eff es a -> Eff es a #

sin :: Eff es a -> Eff es a #

cos :: Eff es a -> Eff es a #

tan :: Eff es a -> Eff es a #

asin :: Eff es a -> Eff es a #

acos :: Eff es a -> Eff es a #

atan :: Eff es a -> Eff es a #

sinh :: Eff es a -> Eff es a #

cosh :: Eff es a -> Eff es a #

tanh :: Eff es a -> Eff es a #

asinh :: Eff es a -> Eff es a #

acosh :: Eff es a -> Eff es a #

atanh :: Eff es a -> Eff es a #

log1p :: Eff es a -> Eff es a #

expm1 :: Eff es a -> Eff es a #

log1pexp :: Eff es a -> Eff es a #

log1mexp :: Eff es a -> Eff es a #

Fractional a => Fractional (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

(/) :: Eff es a -> Eff es a -> Eff es a #

recip :: Eff es a -> Eff es a #

fromRational :: Rational -> Eff es a #

Num a => Num (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

(+) :: Eff es a -> Eff es a -> Eff es a #

(-) :: Eff es a -> Eff es a -> Eff es a #

(*) :: Eff es a -> Eff es a -> Eff es a #

negate :: Eff es a -> Eff es a #

abs :: Eff es a -> Eff es a #

signum :: Eff es a -> Eff es a #

fromInteger :: Integer -> Eff es a #

IsString a => IsString (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

fromString :: String -> Eff es a #

Semigroup a => Semigroup (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

(<>) :: Eff es a -> Eff es a -> Eff es a #

sconcat :: NonEmpty (Eff es a) -> Eff es a #

stimes :: Integral b => b -> Eff es a -> Eff es a #

Monoid a => Monoid (Eff es a) Source #

Since: 0.2.1.0

Instance details

Defined in Cleff.Internal.Instances

Methods

mempty :: Eff es a #

mappend :: Eff es a -> Eff es a -> Eff es a #

mconcat :: [Eff es a] -> Eff es a #

type PrimState (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

type PrimState (Eff es) = RealWorld
type StM (Eff es) a Source # 
Instance details

Defined in Cleff.Internal.Base

type StM (Eff es) a = a

class (e :: Effect) :> (es :: [Effect]) infix 0 Source #

e :> es means the effect e is present in the effect stack es, and therefore can be sended in an Eff es computation.

Instances

Instances details
(TypeError (ElemNotFound e) :: Constraint) => e :> ('[] :: [Effect]) Source # 
Instance details

Defined in Cleff.Internal.Rec

Methods

reifyIndex :: Int

e :> es => e :> (e' ': es) Source # 
Instance details

Defined in Cleff.Internal.Rec

Methods

reifyIndex :: Int

e :> (e ': es) Source #

The element closer to the head takes priority.

Instance details

Defined in Cleff.Internal.Rec

Methods

reifyIndex :: Int

type family xs :>> es :: Constraint where ... infix 0 Source #

xs :>> es means the list of effects xs are all present in the effect stack es. This is a convenient type alias for (e1 :> es, ..., en :> es).

Equations

'[] :>> _ = () 
(x ': xs) :>> es = (x :> es, xs :>> es) 

type Effect = (Type -> Type) -> Type -> Type Source #

The type of effects. An effect e m a takes an effect monad type m :: Type -> Type and a result type a :: Type.

data IOE :: Effect Source #

The effect capable of 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 directly in application code, as it is too liberal and allows arbitrary IO, therefore making it harder to do proper effect management. Ideally, this is only used in interpreting more fine-grained effects.

Technical details

Note that this is not a real effect and cannot be interpreted in any way besides thisIsPureTrustMe and runIOE. 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 a 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 out of the box in their respective modules.

By applying interpreters to an Eff computation, you can eventually obtain an end computation, where there are no more effects to be interpreted on the effect stack. There are two kinds of end computations:

  • A pure computation with the type Eff '[] a, which you can obtain the value via runPure; or,
  • An impure computation with type Eff '[IOE] a that can be unwrapped into an IO computation via runIOE.

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

Unwrap a pure Eff computation into a pure value, given that all effects are interpreted.

runIOE :: Eff '[IOE] ~> IO Source #

Unwrap an Eff computation with side effects into an IO computation, given that all effects other than IOE 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 and writing files can be like this:

data Filesystem :: Effect where
  ReadFile :: FilePath -> Filesystem m String
  WriteFile :: FilePath -> String -> Filesystem m ()

Here, ReadFile is an operation that takes a FilePath and returns a String, presumably the content of the file; WriteFile is an operation that takes a FilePath and a String and returns (), meaning it only performs side effects - presumably writing the String to the file specified.

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.

send :: e :> es => e (Eff es) ~> Eff es Source #

Perform an effect operation, i.e. a value of an effect type e :: Effect. This requires e to be in the effect stack.

sendVia :: e :> es' => (Eff es ~> Eff es') -> e (Eff es) ~> Eff es' Source #

Perform an action in another effect stack via a transformation to that stack; in other words, this function "maps" the effect operation from effect stack es to es'. This is a largely generalized version of send; only use this if you are sure about what you're doing.

send = sendVia id

Since: 0.2.0.0

makeEffect :: Name -> Q [Dec] Source #

For a datatype T representing an effect, makeEffect T generates function defintions for performing the operations of T via send. For example,

makeEffect ''Filesystem

generates the following definitions:

readFile      :: Filesystem :> es => FilePath -> Eff es String
readFile  x   =  send (ReadFile x)
writeFile     :: Filesystem :> es => FilePath -> String -> Eff es ()
writeFile x y =  send (WriteFile x y)

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.

Technical details

This function is also "weaker" than polysemy's makeSem, because this function cannot properly handle some cases involving ambiguous types. Those cases are rare, though. See the ThSpec test spec 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 :: [Effect]) Source #

KnownList es means the list es is concrete, i.e. is of the form '[a1, a2, ..., an] instead of a type variable.

Instances

Instances details
KnownList ('[] :: [Effect]) Source # 
Instance details

Defined in Cleff.Internal.Rec

Methods

reifyLen :: Int

KnownList es => KnownList (e ': es) Source # 
Instance details

Defined in Cleff.Internal.Rec

Methods

reifyLen :: Int

class KnownList es => Subset (es :: [Effect]) (es' :: [Effect]) Source #

es is a subset of es', i.e. all elements of es are in es'.

Instances

Instances details
Subset ('[] :: [Effect]) es Source # 
Instance details

Defined in Cleff.Internal.Rec

Methods

reifyIndices :: [Int]

(Subset es es', e :> es') => Subset (e ': es) es' Source # 
Instance details

Defined in Cleff.Internal.Rec

Methods

reifyIndices :: [Int]

Interpreting effects

An effect can be understood as the syntax of a tiny language; however we also need to define the meaning (or semantics) of the language. In other words, we need to specify the implementations 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.

For example, for the Filesystem effect:

data Filesystem :: Effect where
  ReadFile :: FilePath -> Filesystem m String
  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

Specifically, a ReadFile operation is mapped to a real readFile IO computation, and similarly a WriteFile operation is mapped to a writeFile computation.

An effect is a set of abstract operations, and naturally, they can have more than one interpretations. Therefore, here we can also construct an in-memory filesystem that reads from and writes into a State effect, via the reinterpret function that adds another effect to the stack for the effect handler to use:

filesystemToState
  :: Fail :> es
  => Eff (Filesystem : es) a
  -> Eff (State (Map FilePath String) : es) a
filesystemToState = reinterpret \case
  ReadFile path -> gets (lookup path) >>= \case
    Nothing       -> fail ("File not found: " ++ show path)
    Just contents -> pure contents
  WriteFile path contents -> modify (insert path contents)

Here, we used the reinterpret function to introduce a State (Map FilePath String) as the in-memory filesystem, making filesystemToState a reinterpreter that "maps" an effect into another effect. We also added a Fail :> es constraint to our reinterpreter so that we're able to report errors. To make an interpreter out of this is simple, as we just need to interpret the remaining State effect:

runFilesystemPure
  :: Fail :> es
  => Map FilePath String
  -> Eff (Filesystem : es) a
  -> Eff es a
runFilesystemPure fs
  = fmap fst           -- runState returns (Eff es (a, s)), so we need to extract the first component to get (Eff es a)
  . runState fs        -- (State (Map FilePath String) : es) ==> es
  . filesystemToState  -- (Filesystem : es) ==> (State (Map FilePath String) : es)

Both of 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 esSend e es => 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' to the stack 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, but does not eliminate it from the stack. This means you can re-send the operations in the effect handler; it is often useful when you need to "intercept" operations so you can add extra behaviors like logging.

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 esSend e es => 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.

interpretIO :: IOE :> es => HandlerIO e es -> Eff (e ': es) ~> Eff es Source #

Interpret an effect in terms of IO, by transforming an effect into IO computations.

interpretIO f = interpret (liftIO . f)

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.

transform trans = interpret (sendVia toEff . trans)

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.

translate trans = reinterpret (sendVia toEff . trans)

Transforming interpreters

raiseUnder :: forall e' e es. Eff (e ': es) ~> Eff (e ': (e' ': es)) Source #

Like raise, but adds the new effect under the top effect. This is useful for transforming an interpreter e' :> es => Eff (e : es) ~> Eff es into a reinterpreter Eff (e : es) ~> Eff (e' : es):

myInterpreter :: Bar :> es => Eff (Foo : es) ~> Eff es
myInterpreter = ...

myReinterpreter :: Eff (Foo : es) ~> Eff (Bar : es)
myReinterpreter = myInterpreter . raiseUnder

In other words,

reinterpret h == interpret h . raiseUnder

However, note that this function is suited for transforming an existing interpreter into a reinterpreter; if you want to define a reinterpreter from scratch, you should still prefer reinterpret, which is both easier to use and more efficient.

Since: 0.2.0.0

raiseNUnder :: forall es' e es. KnownList es' => Eff (e ': es) ~> Eff (e ': (es' ++ es)) Source #

Like raiseUnder, but allows introducing multiple effects. This function requires TypeApplications.

Since: 0.2.0.0

raiseUnderN :: forall e es' es. KnownList es' => Eff (es' ++ es) ~> Eff (es' ++ (e ': es)) Source #

Like raiseUnder, but allows introducing the effect under multiple effects. This function requires TypeApplications.

Since: 0.2.0.0

raiseNUnderN :: forall es'' es' es. (KnownList es', KnownList es'') => Eff (es' ++ es) ~> Eff (es' ++ (es'' ++ es)) Source #

A generalization of both raiseUnderN and raiseNUnder, allowing introducing multiple effects under multiple effects. This function requires TypeApplications and is subject to serious type ambiguity; you most likely will need to supply all three type variables explicitly.

Since: 0.2.0.0

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 the operations of these effects carry computations from arbitrary effect stacks, and we'll need to convert the to the current effect stack that the effect is being interpreted into. Fortunately, Cleff 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 esSend e es | esSend -> e es Source #

The typeclass that denotes 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.

toEff :: Handling esSend e es => Eff esSend ~> Eff es Source #

Run a computation in the current effect stack; this is useful for interpreting higher-order effects. For example, if you want to interpret a bracketing effects in terms of IO:

data Resource m a where
  Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b

You will not be able to simply write this for the effect:

runBracket :: IOE :> es => Eff (Resource : es) a -> Eff es a
runBracket = interpret \case
  Bracket alloc dealloc use -> UnliftIO.bracket alloc dealloc use

This is because effects are sended from all kinds of stacks that has Resource in it, so effect handlers received the effect as Resource esSend a, where esSend is an arbitrary stack with Resource, instead of Resource es a. This means alloc, dealloc and use are of type Eff esSend a, while bracket can only take and return Eff es a. So we need to use toEff, which converts an Eff esSend a into an Eff es a:

runBracket :: IOE :> es => Eff (Resource : es) a -> Eff es a
runBracket = interpret \case
  Bracket alloc dealloc use -> UnliftIO.bracket
    (toEff alloc)
    (toEff . dealloc)
    (toEff . use)

toEffWith :: forall esSend e es. Handling esSend e es => Handler e es -> Eff esSend ~> Eff es Source #

Run a computation in the current effect stack, just like toEff, but takes a Handler of the current effect being interpreted, so that inside the computation being ran, the effect is interpreted differently. 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 = \case
      Ask       -> pure r
      Local f m -> toEffWith (handle $ f r) m

withFromEff :: Handling esSend e es => ((Eff es ~> Eff esSend) -> Eff esSend a) -> Eff es a Source #

Temporarily gain the ability to lift some Eff es actions into Eff esSend. This is only useful for dealing with effect operations with the monad type in the negative position, which means it's unlikely that you need to use this function in implementing your effects.

Interpreting IO-related higher order effects

withToIO :: (Handling esSend e es, IOE :> es) => ((Eff esSend ~> IO) -> IO a) -> Eff es a Source #

Temporarily gain the ability to unlift an Eff esSend computation into IO. This is analogous to withRunInIO, and is useful in dealing with higher-order effects that involves IO. For example, the Resource effect that supports bracketing:

data Resource m a where
  Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b

can be interpreted into bracket actions in IO, by converting all effect computations into IO computations via withToIO:

runResource :: IOE :> es => Eff (Resource : es) a -> Eff es a
runResource = interpret \case
  Bracket alloc dealloc use -> withToIO $ \toIO ->
    bracket (toIO alloc) (toIO . dealloc) (toIO . use)

fromIO :: (Handling esSend e es, IOE :> es) => IO ~> Eff esSend Source #

Lift an IO computation into Eff esSend. This is analogous to liftIO, and is only useful in dealing with effect operations with the monad type in the negative position, for example masking:

data Mask :: Effect where
  Mask :: ((m ~> m) -> m a) -> Mask m a
                 ^ this "m" is in negative position

See how the restore :: IO a -> IO a from mask is "wrapped" into Eff esSend a -> Eff esSend a:

runMask :: IOE :> es => Eff (Mask : es) a -> Eff es a
runMask = interpret \case
  Mask f -> withToIO $ \toIO -> mask $
    \restore -> f (fromIO . restore . toIO)

Here, toIO from withToIO takes an Eff esSend to IO, where it can be passed into the restore function, and the returned IO computation is recovered into Eff with fromIO.

Miscellaneous

type (~>) f g = forall a. f a -> g a Source #

A natural transformation from f to g. With this, instead of writing

runSomeEffect :: Eff (SomeEffect : es) a -> Eff es a

you can write:

runSomeEffect :: Eff (SomeEffect : es) ~> Eff es

type family xs ++ ys where ... infixr 5 Source #

Type level list concatenation.

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

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:

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

IOE :> es => MonadIO (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

liftIO :: IO a -> Eff es a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, Functor m, MonadIO m) => MonadIO (AccumT w m) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

liftIO :: IO a -> AccumT w m a #

MonadIO m => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (SelectT r m) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

liftIO :: IO a -> SelectT r m a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

MonadIO m => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

liftIO :: IO a -> RWST r w s m a #

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

Methods

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

Instances details
MonadUnliftIO IO 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

IOE :> es => MonadUnliftIO (Eff es) Source # 
Instance details

Defined in Cleff.Internal.Base

Methods

withRunInIO :: ((forall a. Eff es a -> IO a) -> IO b) -> Eff es b #

MonadUnliftIO m => MonadUnliftIO (ReaderT r m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. ReaderT r m a -> IO a) -> IO b) -> ReaderT r m b #

MonadUnliftIO m => MonadUnliftIO (IdentityT m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. IdentityT m a -> IO a) -> IO b) -> IdentityT m b #