effectful-core-2.2.1.0: An easy to use, performant extensible effects library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful

Synopsis

Introduction

Haskell is one of the few programming languages that distinguishes between pure functions and functions that might perform side effects. For example, a function

f :: Int -> String

can't perform side effects at all, but a function

f :: Int -> IO String

can perform any side effect. This "all or nothing" approach isn't very satisfactory though, because the vast majority of time we would like to signify that a function can perform some side effects, e.g. only be able to log messages.

This library provides support for expressing exactly that with its Eff monad:

f :: Log :> es => Int -> Eff es String

It implements support for extensible effects with both dynamic and static dispatch. For more information about each type consult the documentation in Effectful.Dispatch.Dynamic and Effectful.Dispatch.Static.

The library provides:

  • The Eff monad that tracks effects at the type level. This is going to be the main monad of your application.
  • A set of predefined, basic effects such as Error, Reader, State and Writer.
  • Utilities for defining new effects and interpreting them, possibly in terms of already existing ones.

While basic effects can be used out of the box, in general it's recommended to create your own that serve a more specific purpose.

Integration with existing libraries

Integration with most of existing libraries and frameworks can be done quite easily. The main difference in how that looks like depends on the way a library operates in a monadic context.

There are three main groups a library might fall into. It either operates:

1) In a monad of your application transformed by a library specific monad transformer.

2) In its own, concrete monad, which is usually IO or a couple of monad transformers on top of IO.

3) In a polymorphic monad, which is constrained by a type class that implements core operations of a library.

Each case needs a slightly different approach to integrate with the Eff monad.

Transformed monads

These are libraries that provide a custom transformer for the main monad of your application and their operations make use of it for their operations. Examples include InputT from the haskeline package or ConduitT from the conduit package.

These libraries can trivially be used with the Eff monad since it provides typical instances that these libraries require the underlying monad to have, such as MonadMask or MonadUnliftIO.

In case the Eff monad doesn't provide a specific instance out of the box, it can be supplied via an effect. As an example see how the instance of MonadResource for Eff is implemented in the resourcet-effectful package.

Concrete monads

IO

If a library operates in IO, there are a couple of ways to integrate it.

The easiest way is to use its functions selectively in the Eff monad with the help of liftIO or withEffToIO / withRunInIO. However, this is not particularly robust, since it vastly broadens the scope in which the IOE effect is needed (not to mention that explicit lifting is annoying).

A somewhat better approach is to create a dummy static effect with lightweight wrappers of the library functions. As an example have a look at the Effectful.Concurrent.Async module from the effectful package that wraps the API of the async package. Unfortunately, this requires the amount of work proportional to the size of the library and might not be the best option, especially if you only need to make use of a tiny portion of the API.

Even better (though sometimes hard to do in practice) way is to consider, what do you need the library for and then create a custom effect with high level operations that the library in question will help us implement. The advantage of this approach is that we're hiding implementation details from the so-called "business logic" of our application and make it possible to easily swap them in different environments or during future refactoring.

Other

Some libraries operate in a transformer stack over IO or have its own concrete monad that's a newtype over IO, e.g. Handler from the servant-server package.

In such case it's best to mirror the monad in question by the Eff monad with appropriate effects (as most popular monad transformers have subtle issues), use it as soon as possible, then at the end feed the final state to the monad of the library so it proceeds as if nothing unusual happened.

As an example, consider the following monad:

>>> import qualified Control.Monad.State as T
>>> import qualified Control.Monad.Except as T
>>> data HandlerState
>>> data HandlerError
>>> :{
  newtype Handler a = Handler (T.ExceptT HandlerError (T.StateT HandlerState IO) a)
    deriving ( Applicative, Functor, Monad, MonadIO
             , T.MonadState HandlerState, T.MonadError HandlerError
             )
:}

This is how you can execute Eff actions in the Handler monad:

>>> import Effectful.Error.Static
>>> import Effectful.State.Static.Local
>>> :{
  effToHandler :: Eff [Error HandlerError, State HandlerState, IOE] a -> Handler a
  effToHandler m = do
    -- Retrieve the current state of the Handler.
    s <- T.get
    -- Run the Eff monad with effects mirroring the capabilities of @Handler@.
    (er, s') <- liftIO . runEff . runState s . runErrorNoCallStack @HandlerError $ m
    -- Update the state of the Handler and throw an error if appropriate.
    T.put s'
    either T.throwError pure er
:}

Polymorphic monads

Libraries working in a polymorphic monad use mtl style effects. Details about their integration with the Eff monad require familiarity with dynamically dispatched effects and thus are available in the Effectful.Dispatch.Dynamic module.

The Eff monad

data Eff (es :: [Effect]) a Source #

The Eff monad provides the implementation of a computation that performs an arbitrary set of effects. In Eff es a, es 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 value of type Bool would have the following type:

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

Abstracting over the list of effects with (:>):

  • Allows the computation to be used in functions that may perform other effects.
  • Allows the effects to be handled in any order.

Instances

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

Instance included for compatibility with existing code, usage of withRunInIO is preferrable.

Instance details

Defined in Effectful.Internal.Monad

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 #

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

Instance included for compatibility with existing code, usage of liftIO is preferrable.

Instance details

Defined in Effectful.Internal.Monad

Methods

liftBase :: IO α -> Eff es α #

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

Defined in Effectful.Internal.Monad

Methods

fail :: String -> Eff es a #

MonadFix (Eff es) Source # 
Instance details

Defined in Effectful.Internal.Monad

Methods

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

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

Defined in Effectful.Internal.Monad

Methods

liftIO :: IO a -> Eff es a #

NonDet :> es => Alternative (Eff es) Source #

@since: 2.2.0.0

Instance details

Defined in Effectful.Internal.Monad

Methods

empty :: Eff es a #

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

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

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

Applicative (Eff es) Source # 
Instance details

Defined in Effectful.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 #

Functor (Eff es) Source # 
Instance details

Defined in Effectful.Internal.Monad

Methods

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

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

Monad (Eff es) Source # 
Instance details

Defined in Effectful.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 #

NonDet :> es => MonadPlus (Eff es) Source #

@since: 2.2.0.0

Instance details

Defined in Effectful.Internal.Monad

Methods

mzero :: Eff es a #

mplus :: Eff es a -> Eff es a -> Eff es a #

MonadCatch (Eff es) Source # 
Instance details

Defined in Effectful.Internal.Monad

Methods

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

MonadMask (Eff es) Source # 
Instance details

Defined in Effectful.Internal.Monad

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) #

MonadThrow (Eff es) Source # 
Instance details

Defined in Effectful.Internal.Monad

Methods

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

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

Defined in Effectful.Internal.Monad

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 #

Use withEffToIO if you want accurate stack traces on errors.

Instance details

Defined in Effectful.Internal.Monad

Methods

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

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

Defined in Effectful.Internal.Monad

Methods

mempty :: Eff es a #

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

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

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

Defined in Effectful.Internal.Monad

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 #

type PrimState (Eff es) Source # 
Instance details

Defined in Effectful.Internal.Monad

type StM (Eff es) a Source # 
Instance details

Defined in Effectful.Internal.Monad

type StM (Eff es) a = a

Effect constraints

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

The kind of effects.

data Dispatch Source #

A type of dispatch. For more information consult the documentation in Effectful.Dispatch.Dynamic and Effectful.Dispatch.Static.

Constructors

Dynamic 
Static SideEffects 

type family DispatchOf (e :: Effect) :: Dispatch Source #

Dispatch types of effects.

Instances

Instances details
type DispatchOf Fail Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf IOE Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf NonDet Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf Prim Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf (Error e) Source # 
Instance details

Defined in Effectful.Error.Dynamic

type DispatchOf (Error e) Source # 
Instance details

Defined in Effectful.Error.Static

type DispatchOf (Reader r) Source # 
Instance details

Defined in Effectful.Reader.Dynamic

type DispatchOf (Reader r) Source # 
Instance details

Defined in Effectful.Reader.Static

type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Dynamic

type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Static.Local

type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Static.Shared

type DispatchOf (Writer w) Source # 
Instance details

Defined in Effectful.Writer.Dynamic

type DispatchOf (Writer w) Source # 
Instance details

Defined in Effectful.Writer.Static.Local

type DispatchOf (Writer w) Source # 
Instance details

Defined in Effectful.Writer.Static.Shared

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

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

For example, a computation that only needs access to a mutable value of type Integer would have the following type:

State Integer :> es => Eff es ()

Instances

Instances details
(TypeError (('Text "There is no handler for '" :<>: 'ShowType e) :<>: 'Text "' in the context") :: Constraint) => e :> ('[] :: [Effect]) Source # 
Instance details

Defined in Effectful.Internal.Effect

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

Defined in Effectful.Internal.Effect

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

Defined in Effectful.Internal.Effect

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

Deprecated: Usage of (:>>) slows down GHC too much, so it will be removed in 3.0.0.0. See https://github.com/haskell-effectful/effectful/issues/52#issuecomment-1269155485 for more information.

Convenience operator for expressing that a function uses multiple effects in a more concise way than enumerating them all with (:>).

[E1, E2, ..., En] :>> es ≡ (E1 :> es, E2 :> es, ..., En :> es)

Equations

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

Running the Eff monad

Pure computations

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

Run a pure Eff computation.

For running computations with side effects see runEff.

Computations with side effects

runEff :: Eff '[IOE] a -> IO a Source #

Run an Eff computation with side effects.

For running pure computations see runPureEff.

data IOE :: Effect Source #

Run arbitrary IO computations via MonadIO or MonadUnliftIO.

Note: it is not recommended to use this effect in application code as it is too liberal. Ideally, this is only used in handlers of more fine-grained effects.

Instances

Instances details
type DispatchOf IOE Source # 
Instance details

Defined in Effectful.Internal.Monad

newtype StaticRep IOE Source # 
Instance details

Defined in Effectful.Internal.Monad

Unlifting

data UnliftStrategy Source #

The strategy to use when unlifting Eff computations via withEffToIO, withRunInIO or the localUnlift family.

Constructors

SeqUnlift

The fastest strategy and a default setting for IOE. An attempt to call the unlifting function in threads distinct from its creator will result in a runtime error.

ConcUnlift !Persistence !Limit

A strategy that makes it possible for the unlifting function to be called in threads distinct from its creator. See Persistence and Limit settings for more information.

Instances

Instances details
Generic UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep UnliftStrategy :: Type -> Type #

Show UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

Eq UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

Ord UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep UnliftStrategy Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep UnliftStrategy = D1 ('MetaData "UnliftStrategy" "Effectful.Internal.Unlift" "effectful-core-2.2.1.0-7BMyuuCljwxL06bmHiEQCm" 'False) (C1 ('MetaCons "SeqUnlift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConcUnlift" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Persistence) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Limit)))

data Persistence Source #

Persistence setting for the ConcUnlift strategy.

Different functions require different persistence strategies. Examples:

  • Lifting pooledMapConcurrentlyN from the unliftio library requires the Ephemeral strategy as we don't want jobs to share environment changes made by previous jobs run in the same worker thread.
  • Lifting forkIOWithUnmask requires the Persistent strategy, otherwise the unmasking function would start with a fresh environment each time it's called.

Constructors

Ephemeral

Don't persist the environment between calls to the unlifting function in threads distinct from its creator.

Persistent

Persist the environment between calls to the unlifting function within a particular thread.

Instances

Instances details
Generic Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep Persistence :: Type -> Type #

Show Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

Eq Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

Ord Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Persistence Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Persistence = D1 ('MetaData "Persistence" "Effectful.Internal.Unlift" "effectful-core-2.2.1.0-7BMyuuCljwxL06bmHiEQCm" 'False) (C1 ('MetaCons "Ephemeral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Persistent" 'PrefixI 'False) (U1 :: Type -> Type))

data Limit Source #

Limit setting for the ConcUnlift strategy.

Constructors

Limited !Int

Behavior dependent on the Persistence setting.

For Ephemeral, it limits the amount of uses of the unlifting function in threads distinct from its creator to N. The unlifting function will create N copies of the environment when called N times and K+1 copies when called K < N times.

For Persistent, it limits the amount of threads, distinct from the creator of the unlifting function, it can be called in to N. The amount of calls to the unlifting function within a particular threads is unlimited. The unlifting function will create N copies of the environment when called in N threads and K+1 copies when called in K < N threads.

Unlimited

Unlimited use of the unlifting function.

Instances

Instances details
Generic Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep Limit :: Type -> Type #

Methods

from :: Limit -> Rep Limit x #

to :: Rep Limit x -> Limit #

Show Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

Eq Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Methods

(==) :: Limit -> Limit -> Bool #

(/=) :: Limit -> Limit -> Bool #

Ord Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

Methods

compare :: Limit -> Limit -> Ordering #

(<) :: Limit -> Limit -> Bool #

(<=) :: Limit -> Limit -> Bool #

(>) :: Limit -> Limit -> Bool #

(>=) :: Limit -> Limit -> Bool #

max :: Limit -> Limit -> Limit #

min :: Limit -> Limit -> Limit #

type Rep Limit Source # 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Limit = D1 ('MetaData "Limit" "Effectful.Internal.Unlift" "effectful-core-2.2.1.0-7BMyuuCljwxL06bmHiEQCm" 'False) (C1 ('MetaCons "Limited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Unlimited" 'PrefixI 'False) (U1 :: Type -> Type))

withUnliftStrategy :: IOE :> es => UnliftStrategy -> Eff es a -> Eff es a Source #

Locally override the UnliftStrategy with the given value.

withEffToIO Source #

Arguments

:: (HasCallStack, IOE :> es) 
=> ((forall r. Eff es r -> IO r) -> IO a)

Continuation with the unlifting function in scope.

-> Eff es a 

Create an unlifting function with the current UnliftStrategy.

This function is equivalent to withRunInIO, but has a HasCallStack constraint for accurate stack traces in case an insufficiently powerful UnliftStrategy is used and the unlifting function fails.

Lifting

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

Lift an Eff computation into an effect stack with one more effect.

raiseWith Source #

Arguments

:: HasCallStack 
=> UnliftStrategy 
-> ((forall r. Eff (e ': es) r -> Eff es r) -> Eff es a)

Continuation with the unlifting function in scope.

-> Eff (e ': es) a 

Lift an Eff computation into an effect stack with one more effect and create an unlifting function with the given strategy.

Since: 1.2.0.0

subsume :: e :> es => Eff (e ': es) a -> Eff es a Source #

Eliminate a duplicate effect from the top of the effect stack.

inject :: Subset xs es => Eff xs a -> Eff es a Source #

Allow for running an effect stack xs within es as long as xs is a permutation (with possible duplicates) of a subset of es.

Generalizes raise and subsume.

Note: this function should be needed rarely, usually when you have to cross API boundaries and monomorphic effect stacks are involved. Using monomorphic stacks is discouraged (see Eff), but sometimes might be necessary due to external constraints.

class Subset (xs :: [Effect]) (es :: [Effect]) Source #

Provide evidence that xs is a subset of es.

Instances

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

Defined in Effectful.Internal.Effect

Methods

reifyIndices :: [Int] Source #

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

Defined in Effectful.Internal.Effect

Methods

reifyIndices :: [Int] Source #

Re-exports

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. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

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 #

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

Defined in Effectful.Internal.Monad

Methods

liftIO :: IO a -> Eff es a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT 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 #

(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 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT 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 (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r 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 (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s 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 #

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

Defined in Control.Monad.Trans.Writer.CPS

Methods

liftIO :: IO a -> WriterT w 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 #

(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 #

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

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r 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 #

(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 #

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 #

Use withEffToIO if you want accurate stack traces on errors.

Instance details

Defined in Effectful.Internal.Monad

Methods

withRunInIO :: ((forall a. Eff es a -> IO a) -> IO b) -> Eff es 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 #

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 #