in-other-words-0.2.0.0: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect

Synopsis

Core class

class Monad m => Carrier m Source #

The class of effect carriers, and the underlying mechanism with which effects are implemented.

Each carrier is able to implement a number of derived effects, and primitive effects. Users usually only interact with derived effects, as these determine the effects that users have access to.

The standard interpretation tools are typically powerful enough to let you avoid making instances of this class directly. If you need to make your own instance of Carrier, import Control.Effect.Carrier and consult the wiki.

Minimal complete definition

algPrims, reformulate

Associated Types

type Derivs m :: [Effect] Source #

The derived effects that m carries. Each derived effect is eventually reformulated into terms of the primitive effects Prims m or other effects in Derivs m.

In application code, you gain access to effects by placing membership constraints upon Derivs m. You can use Eff or Effs for this purpose.

Although rarely relevant for users, Derivs m can also contain effects that aren't expressed in terms of other effects, as longs as the handlers for those effects can be lifted generically using lift. Such effects don't need to be part of Prims m, which is exclusively for primitive effects whose handlers need special treatment to be lifted.

For example, first order effects such as State never need to be part of Prims m. Certain higher-order effects - such as Cont - can also be handled such that they never need to be primitive.

Instances

Instances details
Carrier Identity Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs Identity :: [Effect] Source #

type Prims Identity :: [Effect] Source #

(Carrier m, MonadCatch m) => Carrier (ErrorIOToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.ErrorIO

Associated Types

type Derivs (ErrorIOToIOC m) :: [Effect] Source #

type Prims (ErrorIOToIOC m) :: [Effect] Source #

(Carrier m, MonadBaseControlPure IO m) => Carrier (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Associated Types

type Derivs (ConcToIOC m) :: [Effect] Source #

type Prims (ConcToIOC m) :: [Effect] Source #

(Carrier m, Threads (WriterT (Dual [String])) (Prims m)) => Carrier (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Associated Types

type Derivs (TraceListC m) :: [Effect] Source #

type Prims (TraceListC m) :: [Effect] Source #

(Carrier m, Threads ListT (Prims m)) => Carrier (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Associated Types

type Derivs (NonDetC m) :: [Effect] Source #

type Prims (NonDetC m) :: [Effect] Source #

(Carrier m, Threads ListT (Prims m)) => Carrier (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Associated Types

type Derivs (CullCutC m) :: [Effect] Source #

type Prims (CullCutC m) :: [Effect] Source #

(Carrier m, Threads ListT (Prims m)) => Carrier (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Associated Types

type Derivs (LogicC m) :: [Effect] Source #

type Prims (LogicC m) :: [Effect] Source #

(Monad m, Carrier (InterpretSimpleC Fail m)) => Carrier (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type Derivs (InterpretFailSimpleC m) :: [Effect] Source #

type Prims (InterpretFailSimpleC m) :: [Effect] Source #

(Carrier m, Threads (ExceptT String) (Prims m)) => Carrier (FailC m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type Derivs (FailC m) :: [Effect] Source #

type Prims (FailC m) :: [Effect] Source #

(Carrier m, Threads (ExceptT ()) (Prims m)) => Carrier (AltMaybeC m) Source # 
Instance details

Defined in Control.Effect.Alt

Associated Types

type Derivs (AltMaybeC m) :: [Effect] Source #

type Prims (AltMaybeC m) :: [Effect] Source #

(Monad m, Carrier (InterpretSimpleC Alt m)) => Carrier (InterpretAltSimpleC m) Source # 
Instance details

Defined in Control.Effect.Alt

Associated Types

type Derivs (InterpretAltSimpleC m) :: [Effect] Source #

type Prims (InterpretAltSimpleC m) :: [Effect] Source #

Carrier m => Carrier (Ap m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs (Ap m) :: [Effect] Source #

type Prims (Ap m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (Ap m)) (Ap m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (Ap m)) (Prims (Ap m)) (Ap m) z a Source #

algDerivs :: Algebra' (Derivs (Ap m)) (Ap m) a Source #

Carrier m => Carrier (Alt m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs (Alt m) :: [Effect] Source #

type Prims (Alt m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (Alt m)) (Alt m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (Alt m)) (Prims (Alt m)) (Alt m) z a Source #

algDerivs :: Algebra' (Derivs (Alt m)) (Alt m) a Source #

Carrier m => Carrier (IdentityT m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs (IdentityT m) :: [Effect] Source #

type Prims (IdentityT m) :: [Effect] Source #

Carrier m => Carrier (Itself m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs (Itself m) :: [Effect] Source #

type Prims (Itself m) :: [Effect] Source #

Carrier (CompositionBaseT ts m) => Carrier (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Associated Types

type Derivs (CompositionC ts m) :: [Effect] Source #

type Prims (CompositionC ts m) :: [Effect] Source #

Carrier m => Carrier (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Associated Types

type Derivs (Effly m) :: [Effect] Source #

type Prims (Effly m) :: [Effect] Source #

(Threads (ReaderT (ReifiedPrimHandler e m)) (Prims m), ThreadsEff (ReaderT (ReifiedPrimHandler e m)) e, RepresentationalEff e, Carrier m) => Carrier (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (InterpretPrimSimpleC e m) :: [Effect] Source #

type Prims (InterpretPrimSimpleC e m) :: [Effect] Source #

(Threads (ReaderT (ReifiedHandler e m)) (Prims m), RepresentationalEff e, Carrier m) => Carrier (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (InterpretSimpleC e m) :: [Effect] Source #

type Prims (InterpretSimpleC e m) :: [Effect] Source #

Carrier m => Carrier (EmbedC m) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type Derivs (EmbedC m) :: [Effect] Source #

type Prims (EmbedC m) :: [Effect] Source #

Monad m => Carrier (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type Derivs (RunMC m) :: [Effect] Source #

type Prims (RunMC m) :: [Effect] Source #

(Monoid o, Carrier m, Threads (WriterT o) (Prims m)) => Carrier (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (WriterLazyC o m) :: [Effect] Source #

type Prims (WriterLazyC o m) :: [Effect] Source #

(Monoid o, Carrier m, Threads (WriterT o) (Prims m)) => Carrier (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (ListenLazyC o m) :: [Effect] Source #

type Prims (ListenLazyC o m) :: [Effect] Source #

(Monoid o, Carrier m, Threads (WriterT o) (Prims m)) => Carrier (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (TellLazyC o m) :: [Effect] Source #

type Prims (TellLazyC o m) :: [Effect] Source #

(Carrier m, Monoid o, Threads (WriterT o) (Prims m)) => Carrier (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (WriterC o m) :: [Effect] Source #

type Prims (WriterC o m) :: [Effect] Source #

(Carrier m, Monoid o, Threads (WriterT o) (Prims m)) => Carrier (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (ListenC o m) :: [Effect] Source #

type Prims (ListenC o m) :: [Effect] Source #

(Carrier m, Monoid o, Threads (WriterT o) (Prims m)) => Carrier (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Associated Types

type Derivs (TellC o m) :: [Effect] Source #

type Prims (TellC o m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (TellC o m)) (TellC o m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (TellC o m)) (Prims (TellC o m)) (TellC o m) z a Source #

algDerivs :: Algebra' (Derivs (TellC o m)) (TellC o m) a Source #

Carrier m => Carrier (UnliftC m) Source # 
Instance details

Defined in Control.Effect.Internal.Unlift

Associated Types

type Derivs (UnliftC m) :: [Effect] Source #

type Prims (UnliftC m) :: [Effect] Source #

(Carrier m, Threads (StateT s) (Prims m)) => Carrier (StateLazyC s m) Source # 
Instance details

Defined in Control.Effect.Internal.State

Associated Types

type Derivs (StateLazyC s m) :: [Effect] Source #

type Prims (StateLazyC s m) :: [Effect] Source #

(Carrier m, Threads (StateT s) (Prims m)) => Carrier (StateC s m) Source # 
Instance details

Defined in Control.Effect.Internal.State

Associated Types

type Derivs (StateC s m) :: [Effect] Source #

type Prims (StateC s m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (StateC s m)) (StateC s m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (StateC s m)) (Prims (StateC s m)) (StateC s m) z a Source #

algDerivs :: Algebra' (Derivs (StateC s m)) (StateC s m) a Source #

Carrier m => Carrier (HoistC m) Source # 
Instance details

Defined in Control.Effect.Internal.Regional

Associated Types

type Derivs (HoistC m) :: [Effect] Source #

type Prims (HoistC m) :: [Effect] Source #

(Threads (ReaderT i) (Prims m), Carrier m) => Carrier (ReaderC i m) Source # 
Instance details

Defined in Control.Effect.Internal.Reader

Associated Types

type Derivs (ReaderC i m) :: [Effect] Source #

type Prims (ReaderC i m) :: [Effect] Source #

Carrier m => Carrier (HoistOptionC m) Source # 
Instance details

Defined in Control.Effect.Internal.Optional

Associated Types

type Derivs (HoistOptionC m) :: [Effect] Source #

type Prims (HoistOptionC m) :: [Effect] Source #

(IntroConsistent ('[] :: [Effect]) '[UnwrappedEff e] m, EffNewtype e, Carrier m) => Carrier (UnwrapTopC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Associated Types

type Derivs (UnwrapTopC e m) :: [Effect] Source #

type Prims (UnwrapTopC e m) :: [Effect] Source #

(Carrier m, Member (UnwrappedEff e) (Derivs m), EffNewtype e) => Carrier (UnwrapC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Associated Types

type Derivs (UnwrapC e m) :: [Effect] Source #

type Prims (UnwrapC e m) :: [Effect] Source #

(Eff (Embed IO) m, MonadCatch m, Threaders '[ReaderThreads] m p) => Carrier (ErrorToIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (ErrorToIOSimpleC e m) :: [Effect] Source #

type Prims (ErrorToIOSimpleC e m) :: [Effect] Source #

(Carrier m, Threaders '[ReaderThreads] m p) => Carrier (InterpretErrorSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (InterpretErrorSimpleC e m) :: [Effect] Source #

type Prims (InterpretErrorSimpleC e m) :: [Effect] Source #

(Exception e, MonadCatch m, Carrier m) => Carrier (ErrorToIOAsExcC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (ErrorToIOAsExcC e m) :: [Effect] Source #

type Prims (ErrorToIOAsExcC e m) :: [Effect] Source #

(Eff ErrorIO m, Exception e) => Carrier (ErrorToErrorIOAsExcC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (ErrorToErrorIOAsExcC e m) :: [Effect] Source #

type Prims (ErrorToErrorIOAsExcC e m) :: [Effect] Source #

(Carrier m, Threads (ExceptT e) (Prims m)) => Carrier (ErrorC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (ErrorC e m) :: [Effect] Source #

type Prims (ErrorC e m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ErrorC e m)) (ErrorC e m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ErrorC e m)) (Prims (ErrorC e m)) (ErrorC e m) z a Source #

algDerivs :: Algebra' (Derivs (ErrorC e m)) (ErrorC e m) a Source #

(Carrier m, Threads (ExceptT e) (Prims m)) => Carrier (ThrowC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (ThrowC e m) :: [Effect] Source #

type Prims (ThrowC e m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ThrowC e m)) (ThrowC e m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ThrowC e m)) (Prims (ThrowC e m)) (ThrowC e m) z a Source #

algDerivs :: Algebra' (Derivs (ThrowC e m)) (ThrowC e m) a Source #

(Carrier m, Threaders '[ReaderThreads] m p) => Carrier (SafeErrorToErrorIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

(Eff (Embed IO) m, MonadCatch m, Threaders '[ReaderThreads] m p) => Carrier (SafeErrorToIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorToIOSimpleC e m) :: [Effect] Source #

type Prims (SafeErrorToIOSimpleC e m) :: [Effect] Source #

(Carrier m, Threads (ExceptT exc) (Prims m)) => Carrier (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorC exc m) :: [Effect] Source #

type Prims (SafeErrorC exc m) :: [Effect] Source #

Carrier m => Carrier (BaseControlC m) Source # 
Instance details

Defined in Control.Effect.Internal.BaseControl

Associated Types

type Derivs (BaseControlC m) :: [Effect] Source #

type Prims (BaseControlC m) :: [Effect] Source #

(Carrier m, Enum uniq, Threads (StateT uniq) (Prims m)) => Carrier (FreshEnumC uniq m) Source # 
Instance details

Defined in Control.Effect.Fresh

Associated Types

type Derivs (FreshEnumC uniq m) :: [Effect] Source #

type Prims (FreshEnumC uniq m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (FreshEnumC uniq m)) (FreshEnumC uniq m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (FreshEnumC uniq m)) (Prims (FreshEnumC uniq m)) (FreshEnumC uniq m) z a Source #

algDerivs :: Algebra' (Derivs (FreshEnumC uniq m)) (FreshEnumC uniq m) a Source #

(Monoid o, Eff (Embed IO) m, MonadMask m, Threads (ReaderT (o -> STM ())) (Prims m)) => Carrier (WriterTVarC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (WriterTVarC o m) :: [Effect] Source #

type Prims (WriterTVarC o m) :: [Effect] Source #

(Monoid o, Eff (Embed IO) m, MonadMask m, Threads (ReaderT (o -> STM ())) (Prims m)) => Carrier (ListenTVarC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (ListenTVarC o m) :: [Effect] Source #

type Prims (ListenTVarC o m) :: [Effect] Source #

(Effs '[Bracket, Embed IO] m, Monoid o, Threads (ReaderT (o -> STM ())) (Prims m)) => Carrier (WriterToBracketC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (WriterToBracketC o m) :: [Effect] Source #

type Prims (WriterToBracketC o m) :: [Effect] Source #

(Monoid o, HeadEffs '[Pass (Endo o), Listen (Endo o), Tell (Endo o)] m) => Carrier (WriterIntoEndoWriterC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (WriterIntoEndoWriterC o m) :: [Effect] Source #

type Prims (WriterIntoEndoWriterC o m) :: [Effect] Source #

(Monoid o, HeadEffs '[Listen (Endo o), Tell (Endo o)] m) => Carrier (ListenIntoEndoListenC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (ListenIntoEndoListenC o m) :: [Effect] Source #

type Prims (ListenIntoEndoListenC o m) :: [Effect] Source #

(Carrier m, Threads (WriterT (Endo [o])) (Prims m)) => Carrier (TellListLazyC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (TellListLazyC o m) :: [Effect] Source #

type Prims (TellListLazyC o m) :: [Effect] Source #

(Carrier m, Threads (WriterT (Dual [o])) (Prims m)) => Carrier (TellListC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Associated Types

type Derivs (TellListC o m) :: [Effect] Source #

type Prims (TellListC o m) :: [Effect] Source #

(Carrier m, Threads (FreeT (ContBase (m r) r)) (Prims m)) => Carrier (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Associated Types

type Derivs (ShiftC r m) :: [Effect] Source #

type Prims (ShiftC r m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ShiftC r m)) (ShiftC r m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ShiftC r m)) (Prims (ShiftC r m)) (ShiftC r m) z a Source #

algDerivs :: Algebra' (Derivs (ShiftC r m)) (ShiftC r m) a Source #

(Carrier m, Threads (FreeT (ContBase (m r) r)) (Prims m)) => Carrier (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Associated Types

type Derivs (ContC r m) :: [Effect] Source #

type Prims (ContC r m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ContC r m)) (ContC r m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ContC r m)) (Prims (ContC r m)) (ContC r m) z a Source #

algDerivs :: Algebra' (Derivs (ContC r m)) (ContC r m) a Source #

(Threads (FreeT (FOEff e)) (Prims m), Carrier m) => Carrier (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Associated Types

type Derivs (SteppedC e m) :: [Effect] Source #

type Prims (SteppedC e m) :: [Effect] Source #

(FirstOrder e, Carrier m, Threads (ReaderT (ReifiedFOHandler e m)) (Prims m)) => Carrier (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Associated Types

type Derivs (InterceptRC e m) :: [Effect] Source #

type Prims (InterceptRC e m) :: [Effect] Source #

(Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => Carrier (ListenSteppedC w m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Associated Types

type Derivs (ListenSteppedC w m) :: [Effect] Source #

type Prims (ListenSteppedC w m) :: [Effect] Source #

(FirstOrder e, Carrier m, Member e (Derivs m), Threaders '[SteppedThreads] m p) => Carrier (InterceptContC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Associated Types

type Derivs (InterceptContC e m) :: [Effect] Source #

type Prims (InterceptContC e m) :: [Effect] Source #

Handler h Fail m => Carrier (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Associated Types

type Derivs (InterpretFailC h m) :: [Effect] Source #

type Prims (InterpretFailC h m) :: [Effect] Source #

Handler h Alt m => Carrier (InterpretAltC h m) Source # 
Instance details

Defined in Control.Effect.Alt

Associated Types

type Derivs (InterpretAltC h m) :: [Effect] Source #

type Prims (InterpretAltC h m) :: [Effect] Source #

(Carrier m, Member e (Derivs m)) => Carrier (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs (SubsumeC e m) :: [Effect] Source #

type Prims (SubsumeC e m) :: [Effect] Source #

(Carrier m, KnownList top, KnownList new, IntroConsistent top new m) => Carrier (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type Derivs (IntroC top new m) :: [Effect] Source #

type Prims (IntroC top new m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (IntroC top new m)) (IntroC top new m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (IntroC top new m)) (Prims (IntroC top new m)) (IntroC top new m) z a Source #

algDerivs :: Algebra' (Derivs (IntroC top new m)) (IntroC top new m) a Source #

(Threads (ReaderT (ReifiedHandler e m)) (Prims m), RepresentationalEff e, KnownList new, HeadEffs new m, Carrier m) => Carrier (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (ReinterpretSimpleC e new m) :: [Effect] Source #

type Prims (ReinterpretSimpleC e new m) :: [Effect] Source #

(Carrier m, Handler h e m) => Carrier (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (InterpretC h e m) :: [Effect] Source #

type Prims (InterpretC h e m) :: [Effect] Source #

PrimHandler h e m => Carrier (InterpretPrimC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (InterpretPrimC h e m) :: [Effect] Source #

type Prims (InterpretPrimC h e m) :: [Effect] Source #

(KnownList l, HeadEffs l m) => Carrier (UnionC l m) Source # 
Instance details

Defined in Control.Effect.Union

Associated Types

type Derivs (UnionC l m) :: [Effect] Source #

type Prims (UnionC l m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (UnionC l m)) (UnionC l m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (UnionC l m)) (Prims (UnionC l m)) (UnionC l m) z a Source #

algDerivs :: Algebra' (Derivs (UnionC l m)) (UnionC l m) a Source #

(Member e' (Derivs m), Coercible e e', Carrier m) => Carrier (WrapC e e' m) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Associated Types

type Derivs (WrapC e e' m) :: [Effect] Source #

type Prims (WrapC e e' m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (WrapC e e' m)) (WrapC e e' m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (WrapC e e' m)) (Prims (WrapC e e' m)) (WrapC e e' m) z a Source #

algDerivs :: Algebra' (Derivs (WrapC e e' m)) (WrapC e e' m) a Source #

(Carrier m, Threads (FreeT (ContBase (m (s, r)) (s, r))) (Prims m)) => Carrier (SelectC s r m) Source # 
Instance details

Defined in Control.Effect.Internal.Select

Associated Types

type Derivs (SelectC s r m) :: [Effect] Source #

type Prims (SelectC s r m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (SelectC s r m)) (SelectC s r m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (SelectC s r m)) (Prims (SelectC s r m)) (SelectC s r m) z a Source #

algDerivs :: Algebra' (Derivs (SelectC s r m)) (SelectC s r m) a Source #

Carrier (t (u m)) => Carrier (ComposeT t u m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Associated Types

type Derivs (ComposeT t u m) :: [Effect] Source #

type Prims (ComposeT t u m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ComposeT t u m)) (ComposeT t u m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ComposeT t u m)) (Prims (ComposeT t u m)) (ComposeT t u m) z a Source #

algDerivs :: Algebra' (Derivs (ComposeT t u m)) (ComposeT t u m) a Source #

(Handler h e m, Carrier m, KnownList new, IntroConsistent ('[] :: [Effect]) new m) => Carrier (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (ReinterpretC h e new m) :: [Effect] Source #

type Prims (ReinterpretC h e new m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ReinterpretC h e new m)) (ReinterpretC h e new m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ReinterpretC h e new m)) (Prims (ReinterpretC h e new m)) (ReinterpretC h e new m) z a Source #

algDerivs :: Algebra' (Derivs (ReinterpretC h e new m)) (ReinterpretC h e new m) a Source #

(KnownList b, Eff (Union b) m) => Carrier (UnionizeC b m) Source # 
Instance details

Defined in Control.Effect.Union

Associated Types

type Derivs (UnionizeC b m) :: [Effect] Source #

type Prims (UnionizeC b m) :: [Effect] Source #

(HeadEff (Union b) m, KnownList b) => Carrier (UnionizeHeadC b m) Source # 
Instance details

Defined in Control.Effect.Union

Associated Types

type Derivs (UnionizeHeadC b m) :: [Effect] Source #

type Prims (UnionizeHeadC b m) :: [Effect] Source #

(Carrier m, MonadCatch m, ReifiesErrorHandler s s' e (ErrorIOToIOC m)) => Carrier (ErrorToIOC' s s' e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (ErrorToIOC' s s' e m) :: [Effect] Source #

type Prims (ErrorToIOC' s s' e m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ErrorToIOC' s s' e m)) (ErrorToIOC' s s' e m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ErrorToIOC' s s' e m)) (Prims (ErrorToIOC' s s' e m)) (ErrorToIOC' s s' e m) z a Source #

algDerivs :: Algebra' (Derivs (ErrorToIOC' s s' e m)) (ErrorToIOC' s s' e m) a Source #

(Carrier m, ReifiesErrorHandler s s' e m) => Carrier (InterpretErrorC' s s' e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Associated Types

type Derivs (InterpretErrorC' s s' e m) :: [Effect] Source #

type Prims (InterpretErrorC' s s' e m) :: [Effect] Source #

(Carrier m, ReifiesErrorHandler s s' exc m) => Carrier (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorToErrorIOC' s s' exc m) :: [Effect] Source #

type Prims (SafeErrorToErrorIOC' s s' exc m) :: [Effect] Source #

(Eff (Embed IO) m, MonadCatch m, ReifiesErrorHandler s s' exc (ErrorIOToIOC m)) => Carrier (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (SafeErrorToIOC' s s' exc m) :: [Effect] Source #

type Prims (SafeErrorToIOC' s s' exc m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (SafeErrorToIOC' s s' exc m)) (SafeErrorToIOC' s s' exc m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (SafeErrorToIOC' s s' exc m)) (Prims (SafeErrorToIOC' s s' exc m)) (SafeErrorToIOC' s s' exc m) z a Source #

algDerivs :: Algebra' (Derivs (SafeErrorToIOC' s s' exc m)) (SafeErrorToIOC' s s' exc m) a Source #

Eff (Exceptional eff exc) m => Carrier (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Associated Types

type Derivs (ExceptionallyC eff exc m) :: [Effect] Source #

type Prims (ExceptionallyC eff exc m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ExceptionallyC eff exc m)) (ExceptionallyC eff exc m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ExceptionallyC eff exc m)) (Prims (ExceptionallyC eff exc m)) (ExceptionallyC eff exc m) z a Source #

algDerivs :: Algebra' (Derivs (ExceptionallyC eff exc m)) (ExceptionallyC eff exc m) a Source #

(Reifies sHandler (HandlerCState p m z), Reifies sReform (ReifiedReformulation r p m), Monad z) => Carrier (HandlerC sHandler sReform r p m z) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (HandlerC sHandler sReform r p m z) :: [Effect] Source #

type Prims (HandlerC sHandler sReform r p m z) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (HandlerC sHandler sReform r p m z)) (HandlerC sHandler sReform r p m z) a Source #

reformulate :: Monad z0 => Reformulation' (Derivs (HandlerC sHandler sReform r p m z)) (Prims (HandlerC sHandler sReform r p m z)) (HandlerC sHandler sReform r p m z) z0 a Source #

algDerivs :: Algebra' (Derivs (HandlerC sHandler sReform r p m z)) (HandlerC sHandler sReform r p m z) a Source #

Carrier m => Carrier (GainBaseControlC b z m) Source # 
Instance details

Defined in Control.Effect.BaseControl

Associated Types

type Derivs (GainBaseControlC b z m) :: [Effect] Source #

type Prims (GainBaseControlC b z m) :: [Effect] Source #

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

The kind of effects.

Helpful for defining new effects:

data InOut i o :: Effect where
  Input  :: InOut i o m i
  Output :: o -> InOut i o m ()

class (forall m n x. Coercible m n => Coercible (e m x) (e n x)) => RepresentationalEff (e :: Effect) Source #

RepresentationalEff is the constraint every effect is expected to satisfy: namely, that any effect e m a is representational in m, which -- in practice -- means that no constraints are ever placed upon m within the definion of e, and that m isn't present in the return type of any action of e.

You don't need to make instances of RepresentationalEff; the compiler will automatically infer if your effect satisfies it.

RepresentationalEff is not a very serious requirement, and even effects that don't satisfy it can typically be rewritten into equally powerful variants that do.

If you ever encounter that an effect you've written doesn't satisfy RepresentationalEff, please consult the wiki.

Instances

Instances details
(forall (m :: Type -> Type) (n :: Type -> Type) x. Coercible m n => Coercible (e m x) (e n x)) => RepresentationalEff e Source # 
Instance details

Defined in Control.Effect.Internal.Union

Effect membership

type Eff e m = Effs '[e] m Source #

(Morally) a type synonym for (Member e (Derivs m), Carrier m). This and Effs are the typical methods to gain access to effects.

Unlike Member, Eff gives Bundle special treatment. As a side-effect, Eff will get stuck if e is a type variable.

If you need access to some completely polymorphic effect e, use (Member e (Derivs m), Carrier m) instead of Eff e m.

type Effs es m = (EffMembers es (Derivs m), Carrier m) Source #

A variant of Eff that takes a list of effects, and expands them into multiple Member constraints on Derivs m. This and Eff are the typical methods to gain access to effects.

Like Eff, Effs gives Bundle special treatment. As a side-effect, Effs will get stuck if any element of the list is a type variable.

If you need access to some completetely polymorphic effect e, use a separate Member e (Derivs m) constraint.

data Bundle :: [Effect] -> Effect Source #

A pseudo-effect given special treatment by Eff and Effs.

An Eff/s constraint on Bundle '[eff1, eff2, ... , effn] will expand it into membership constraints for eff1 through effn. For example:

Error e = Bundle '[Throw e, Catch e]

so

Eff (Error e) m = (Carrier m, Member (Throw e) (Derivs m), Member (Catch e) (Derivs m))

Bundle should never be used in any other contexts but within Eff and Effs, as it isn't an actual effect.

Not to be confused with Union, which is a proper effect that combines multiple effects into one.

class Member e r Source #

A constraint that e is part of the effect row r.

r is typically Derivs m for some m. Member e (Derivs m) allows you to use actions of e with m.

If e occurs multiple times in r, then the first occurence will be used.

If possible, use Eff/s instead.

Minimal complete definition

membership

Instances

Instances details
(TypeError ((('Text "Unhandled effect: " :<>: 'ShowType e) :$$: 'Text "You need to either add or replace an interpreter in your interpretation stack so that the effect gets handled.") :$$: 'Text "To check what effects are currently handled by your interpretation stack, use `debugEffects' from `Control.Effect.Debug'.") :: Constraint) => Member (e :: k) ('[] :: [k]) Source # 
Instance details

Defined in Control.Effect.Internal.Membership

Methods

membership :: ElemOf e '[] Source #

Member e r => Member (e :: a) (_e ': r :: [a]) Source # 
Instance details

Defined in Control.Effect.Internal.Membership

Methods

membership :: ElemOf e (_e ': r) Source #

Member (e :: a) (e ': r :: [a]) Source # 
Instance details

Defined in Control.Effect.Internal.Membership

Methods

membership :: ElemOf e (e ': r) Source #

Sending actions of effects

send :: (Member e (Derivs m), Carrier m) => e m a -> m a Source #

Perform an action of an effect.

send should be used to create actions of your own effects. For example:

data CheckString :: Effect where
  CheckString :: String -> CheckString m Bool

checkString :: Eff CheckString m => String -> m Bool
checkString str = send (CheckString str)

Running final monad

run :: RunC a -> a Source #

Extract the final result from a computation of which no effects remain to be handled.

runM :: Monad m => RunMC m a -> m a Source #

Extract the final monad m from a computation of which no effects remain to be handled except for Embed m.

Integrating external monads

newtype Embed b (m :: * -> *) a where Source #

An effect for embedding actions of a base monad into the current one.

Constructors

Embed 

Fields

embed :: Eff (Embed b) m => b a -> m a Source #

Effect interpretation

interpretSimple :: forall e m a p. (RepresentationalEff e, Threaders '[ReaderThreads] m p, Carrier m) => EffHandler e m -> InterpretSimpleC e m a -> m a Source #

Interpret an effect in terms of other effects, without needing to define an explicit Handler instance. This is an alternative to interpretViaHandler.

See EffHandler for more information about the handler you pass to this function.

Derivs (InterpretSimpleC e m) = e ': Derivs m
Prims  (InterpretSimpleC e m) = Prims m

This is a significantly slower variant of interpret that doesn't have a higher-ranked type, making it much easier to use partially applied.

Note: this emits the threading constraint ReaderThreads (see Threaders). This makes interpretSimple significantly less attractive to use in application code, as it means propagating that constraint through your application.

Example usage:

data Teletype :: Effect where
  ReadTTY  :: Teletype m String
  WriteTTY :: String -> Teletype m ()

readTTY :: Eff Teletype m => m String
readTTY = send ReadTTY

writeTTY :: Eff Teletype m => String -> m ()
writeTTY = send . WriteTTY

echo :: Eff Teletype m => m ()
echo = readTTY >>= sendTTY

teletypeToIO :: Eff (Embed IO) m => SimpleInterpreterFor Teletype m
teletypeToIO = interpretSimple $ \case
  ReadTTY -> embed getLine
  WriteTTY str -> embed $ putStrLn str

main :: IO ()
main = runM $ teletypeToIO $ echo

type SimpleInterpreterFor e m = forall x p. Threaders '[ReaderThreads] m p => InterpretSimpleC e m x -> m x Source #

A useful type synonym for the type of interpretSimple provided a handler

m is left polymorphic so that you may place Eff/s constraints on it.

interpretViaHandler :: forall h e m a. Handler h e m => InterpretC h e m a -> m a Source #

Interpret an effect in terms of other effects by using an explicit Handler instance.

See Handler for more information.

Unlike interpret, this does not have a higher-rank type, making it easier to use partially applied, and unlike interpretSimple doesn't sacrifice performance.

Derivs (InterpretC h e m) = e ': Derivs m
Prims  (InterpretC h e m) = Prims m

Example usage:

data Teletype :: Effect where
  ReadTTY  :: Teletype m String
  WriteTTY :: String -> Teletype m ()

readTTY :: Eff Teletype m => m String
readTTY = send ReadTTY

writeTTY :: Eff Teletype m => String -> m ()
writeTTY = send . WriteTTY

echo :: Eff Teletype m => m ()
echo = readTTY >>= sendTTY

data TeletypeToIOH

instance Eff (Embed IO) m
      => Handler TeletypeToIOH Teletype m where
  effHandler = \case
    ReadTTY -> embed getLine
    WriteTTY str -> embed $ putStrLn str

type TeletypeToIOC = InterpretC TeletypeToIOH Teletype

teletypeToIO :: Eff (Embed IO) m => TeletypeToIOC m a -> m a
teletypeToIO = interpretViaHandler

main :: IO ()
main = runM $ teletypeToIO $ echo

class (RepresentationalEff e, Carrier m) => Handler (h :: *) e m where Source #

The class of effect handlers for derived effects. Instances of this class can be used together interpretViaHandler in order to interpret effects.

h is the tag for the handler, e is the effect to interpret, and m is the Carrier on which the handler operates.

To define your own interpreter using this method, create a new datatype without any constructors to serve as the tag for the handler, and then define a Handler instance for it. Then, you can use your handler to interpret effects with interpretViaHandler.

Alternatively, you can use interpret or interpretSimple, which lets you avoid the need to define instances of Handler, but come at other costs.

Instances

Instances details
(MonadThrow m, Eff (Optional ((->) SomeException :: Type -> Type)) m) => Handler ErrorIOFinalH ErrorIO m Source # 
Instance details

Defined in Control.Effect.Internal.ErrorIO

(Eff ErrorIO m, Exception e) => Handler ErrorToErrorIOAsExcH (Throw e) m Source # 
Instance details

Defined in Control.Effect.Internal.Error

(Eff ErrorIO m, Exception e) => Handler ErrorToErrorIOAsExcH (Catch e) m Source # 
Instance details

Defined in Control.Effect.Internal.Error

Eff (ListenPrim w) m => Handler ListenSteppedH (Listen w) m Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

(FirstOrder e, Member e (Derivs m), Eff (Unravel (InterceptB e)) m) => Handler InterceptH (InterceptCont e) m Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

(FirstOrder e, Eff (Unravel (InterceptB e)) m) => Handler InterceptH (Intercept e) m Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

(Member eff (Derivs m), Eff (Catch exc) m) => Handler ExceptionalH (Exceptional eff exc) m Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

effHandler :: EffHandler (Exceptional eff exc) m Source #

(RepresentationalEff e, Carrier m, Reifies s (ReifiedHandler e m)) => Handler (ViaReifiedH s) e m Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Eff (Shift (s, r)) m => Handler (SelectH r) (Select s) m Source # 
Instance details

Defined in Control.Effect.Internal.Select

interpret :: forall e m a. (RepresentationalEff e, Carrier m) => EffHandler e m -> InterpretReifiedC e m a -> m a Source #

Interpret an effect in terms of other effects, without needing to define an explicit Handler instance. This is an alternative to interpretViaHandler, and is more performant than interpretSimple.

See EffHandler for more information about the handler you pass to this function.

Derivs (InterpretReifiedC e m) = e ': Derivs m
Prims  (InterpretReifiedC e m) = Prims m

This has a higher-rank type, as it makes use of InterpretReifiedC. This makes interpret very difficult to use partially applied. In particular, it can't be composed using .. You must use paranthesis or $.

Consider using interpretSimple instead if performance is secondary.

Example usage:

data Teletype :: Effect where
  ReadTTY  :: Teletype m String
  WriteTTY :: String -> Teletype m ()

readTTY :: Eff Teletype m => m String
readTTY = send ReadTTY

writeTTY :: Eff Teletype m => String -> m ()
writeTTY = send . WriteTTY

echo :: Eff Teletype m => m ()
echo = readTTY >>= sendTTY

teletypeToIO :: Eff (Embed IO) m => InterpreterFor Teletype m
teletypeToIO = interpret $ \case
  ReadTTY -> embed getLine
  WriteTTY str -> embed $ putStrLn str

main :: IO ()
main = runM $ teletypeToIO $ echo

type InterpreterFor e m = forall x. InterpretReifiedC e m x -> m x Source #

A useful type synonym for the type of interpret provided a handler

m is left polymorphic so that you may place Eff/s constraints on it.

type EffHandler e m = forall z x. (Carrier z, Derivs z ~ Derivs m, Prims z ~ Prims m, MonadBase m z) => e (Effly z) x -> Effly z x Source #

The type of effect handlers for a derived effect e with current carrier m.

Don't let the type overwhelm you; in most cases, you can treat this as e m x -> m x.

Any EffHandler is required to work with any carrier monad z that lifts m, and has the same derived and primitive effects as m does. The only constraints that are propagated to z are membership constraints: MonadIO m doesn't imply MonadIO z, but Eff (Embed IO) m does imply Eff (Embed IO) z.

In addition, since z lifts m, you can lift values of m to z through liftBase. This is most useful when using interpret or interpretSimple, as it allows you to bring monadic values of m from outside of the handler (like arguments to the interpreter) into the handler.

The z provided to the handler has Effly wrapped around it, so the handler may make use of the various instances of Effly. For example, you have access to MonadFix inside the handler if you have Eff Fix m.

Any effect to be handled needs to be representational in the monad parameter. See RepresentationalEff for more information.

Effect reinterpretation

reinterpretSimple :: forall e new m a p. (RepresentationalEff e, KnownList new, HeadEffs new m, Threaders '[ReaderThreads] m p) => EffHandler e m -> ReinterpretSimpleC e new m a -> m a Source #

Reinterpret an effect in terms of newly introduced effects.

This combines interpretSimple and introUnder in order to introduce the effects new under e, which you then may make use of inside the handler for e.

Derivs (ReinterpretSimpleC e new m) = e ': StripPrefix new (Derivs m)
Prims  (ReinterpretSimpleC e new m) = Prims m

This is a significantly slower variant of reinterpret that doesn't have a higher-ranked type, making it much easier to use partially applied.

reinterpretViaHandler :: forall h e new m a. (Handler h e m, KnownList new, HeadEffs new m) => ReinterpretC h e new m a -> m a Source #

Reinterpret an effect in terms of newly introduced effects by using an explicit Handler instance.

See Handler for more information.

This combines interpretViaHandler and introUnder in order to introduce the effects new under e, which you then may make use of inside the handler for e.

Derivs (ReinterpretC h e new m) = e ': StripPrefix new (Derivs m)
Prims  (ReinterpretC h e new m) = Prims m

Unlike reinterpret, this does not have a higher-rank type, making it easier to use partially applied, and unlike reinterpretSimple doesn't sacrifice performance.

reinterpret :: forall e new m a. (RepresentationalEff e, KnownList new, HeadEffs new m) => EffHandler e m -> ReinterpretReifiedC e new m a -> m a Source #

Reinterpret an effect in terms of newly introduced effects.

This combines interpret and introUnder in order to introduce the effects new under e, which you then may make use of inside the handler for e.

Derivs (ReinterpretReifiedC e new m) = e ': StripPrefix new (Derivs m)
Prims  (ReinterpretReifiedC e new m) = Prims m

This has a higher-rank type, as it makes use of ReinterpretReifiedC. This makes reinterpret very difficult to use partially applied. In particular, it can't be composed using .. You must use paranthesis or $.

Consider using reinterpretSimple instead if performance is secondary.

Threading constraints

type Threaders cs m p = (p ~ Prims m, SatisfiesAll p cs) Source #

A constraint that Prims m satisfies all the constraints in the list cs.

This is used for threading constraints.

Every interpreter that relies on an underlying non-trivial monad transformer -- such as runState, which uses StateT internally -- must be able to lift all primitive effect handlers of the monad it's transforming so that the resulting transformed monad can also handle the primitive effects.

The ability of a monad transformer to lift handlers of a particular primitive effect is called threading that effect. Threading constraints correspond to the requirement that the primitive effects of the monad that's being transformed can be thread by certain monad transformers.

For example, the runState places the threading constraint StateThreads on Prims m, so that StateC s m can carry all primitive effects that m does.

Threaders is used to handle threading constraints. Threaders '[StateThreads, ExceptThreads] m p allows you to use runState and runError with the carrier m.

Sometimes, you may want to have a local effect which you interpret inside of application code, such as a local State or Error effect. In such cases, try to use split interpretation instead of using interpreters with threading constraints inside of application code. If you can't, then using Threaders is necessary to propagate the threading constraints throughout the application.

The third argument p should always be a polymorphic type variable, which you can simply provide and ignore. It exists as a work-around to the fact that many threading constraints don't actually work if they operate on Prims m directly, since threading constraints often involve quantified constraints, which are fragile in combination with type families -- like Prims.

So Threaders '[StateThreads] m p doesn't expand to StateThreads (Prims m), but rather, (p ~ Prims m, StateThreads p)

class (forall i. Threads (ReaderT i) p) => ReaderThreads p Source #

The most common threading constraint of the library, as it is emitted by -Simple interpreters (interpreters that internally make use of interpretSimple or reinterpretSimple).

ReaderThreads accepts all the primitive effects (intended to be used as such) offered in this library.

Most notably, ReaderThreads accepts Unlift b.

Instances

Instances details
(forall i. Threads (ReaderT i) p) => ReaderThreads p Source # 
Instance details

Defined in Control.Effect.Internal.Union

Effect Introduction

intro1 :: forall e m a. IntroConsistent '[] '[e] m => IntroTopC '[e] m a -> m a Source #

Introduce an effect at the top of the stack -- or rather, reveal an effect previously hidden.

Derivs (IntroTopC '[e] m) = StripPrefix '[e] (Derivs m)
Prims  (IntroTopC '[e] m) = Prims m

intro :: forall new m a. (KnownList new, IntroConsistent '[] new m) => IntroTopC new m a -> m a Source #

Introduce multiple effects on the top of the effect stack -- or rather, reveal effects previously hidden.

Derivs (IntroTopC new m) = StripPrefix new (Derivs m)
Prims  (IntroTopC new m) = Prims m

introUnder1 :: forall new e m a. IntroConsistent '[e] '[new] m => IntroUnderC e '[new] m a -> m a Source #

Introduce an effect under the top effect of the effect stack -- or rather, reveal that effect which was previously hidden.

Derivs (IntroUnderC e '[new] m) = e ': StripPrefix [e, new] (Derivs m)
Prims  (IntroUnderC e '[new] m) = Prims m

introUnder :: forall new e m a. (KnownList new, IntroConsistent '[e] new m) => IntroUnderC e new m a -> m a Source #

Introduce multiple effects under the top effect of the effect stack -- or rather, reveal those effects which were previously hidden.

Derivs (IntroUnderC e new m) = e ': StripPrefix (e ': new) (Derivs m)
Prims  (IntroUnderC e new m) = Prims m

introUnderMany :: forall top new m a. (KnownList top, KnownList new, IntroConsistent top new m) => IntroUnderManyC top new m a -> m a Source #

Introduce multiple effects under a number of top effects of the effect stack -- or rather, reveal those effects which were previously hidden.

Derivs (IntroUnderManyC top new m) = Append top (StripPrefix (Append top new) (Derivs m))
Prims  (IntroUnderManyC top new m) = Prims m

type HeadEff e m = (IntroConsistent '[] '[e] m, Carrier m) Source #

A constraint that the effect stack of m -- Derivs m -- begins with the effect e.

Note that unlike Eff, this does not give Bundle special treatment.

type HeadEffs new m = (IntroConsistent '[] new m, Carrier m) Source #

A constraint that the effect stack of m -- Derivs m -- begins with new.

Note that unlike Effs, this does not give Bundle special treatment.

Combining effect carriers

data CompositionC ts m a Source #

Composition of a list of carrier transformers.

This is useful when you have multiple interpretations whose carriers you'd like to treat as one larger object, such that lift lifts past all those carriers.

For example:

data Counter m a where
  Probe :: Counter m Int

type CounterC = CompositionC
  '[ ReinterpretSimpleC Counter '[State Int]
   , StateC Int
   ]

runCounter :: (Carrier m, Threaders '[StateThreads] m p)
           => CounterC m a
           -> m a
runCounter =
   runState 0
 . reinterpretSimple (case
     Probe -> state' (s -> (s+1,s))
   )
 . runComposition

Then you have lift :: Monad m => m a -> CounterC m a

Instances

Instances details
(Monad b, MonadBase b (CompositionBaseT ts m)) => MonadBase b (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

liftBase :: b α -> CompositionC ts m α #

MonadBaseControl b (CompositionBaseT ts m) => MonadBaseControl b (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Associated Types

type StM (CompositionC ts m) a #

Methods

liftBaseWith :: (RunInBase (CompositionC ts m) b -> b a) -> CompositionC ts m a #

restoreM :: StM (CompositionC ts m) a -> CompositionC ts m a #

MonadTrans (CompositionBaseT ts) => MonadTrans (CompositionC ts) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

lift :: Monad m => m a -> CompositionC ts m a #

MonadTransControl (CompositionBaseT ts) => MonadTransControl (CompositionC ts) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Associated Types

type StT (CompositionC ts) a #

Methods

liftWith :: Monad m => (Run (CompositionC ts) -> m a) -> CompositionC ts m a #

restoreT :: Monad m => m (StT (CompositionC ts) a) -> CompositionC ts m a #

Monad (CompositionBaseT ts m) => Monad (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

(>>=) :: CompositionC ts m a -> (a -> CompositionC ts m b) -> CompositionC ts m b #

(>>) :: CompositionC ts m a -> CompositionC ts m b -> CompositionC ts m b #

return :: a -> CompositionC ts m a #

Functor (CompositionBaseT ts m) => Functor (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

fmap :: (a -> b) -> CompositionC ts m a -> CompositionC ts m b #

(<$) :: a -> CompositionC ts m b -> CompositionC ts m a #

MonadFix (CompositionBaseT ts m) => MonadFix (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

mfix :: (a -> CompositionC ts m a) -> CompositionC ts m a #

MonadFail (CompositionBaseT ts m) => MonadFail (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

fail :: String -> CompositionC ts m a #

Applicative (CompositionBaseT ts m) => Applicative (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

pure :: a -> CompositionC ts m a #

(<*>) :: CompositionC ts m (a -> b) -> CompositionC ts m a -> CompositionC ts m b #

liftA2 :: (a -> b -> c) -> CompositionC ts m a -> CompositionC ts m b -> CompositionC ts m c #

(*>) :: CompositionC ts m a -> CompositionC ts m b -> CompositionC ts m b #

(<*) :: CompositionC ts m a -> CompositionC ts m b -> CompositionC ts m a #

MonadIO (CompositionBaseT ts m) => MonadIO (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

liftIO :: IO a -> CompositionC ts m a #

Alternative (CompositionBaseT ts m) => Alternative (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

empty :: CompositionC ts m a #

(<|>) :: CompositionC ts m a -> CompositionC ts m a -> CompositionC ts m a #

some :: CompositionC ts m a -> CompositionC ts m [a] #

many :: CompositionC ts m a -> CompositionC ts m [a] #

MonadPlus (CompositionBaseT ts m) => MonadPlus (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

mzero :: CompositionC ts m a #

mplus :: CompositionC ts m a -> CompositionC ts m a -> CompositionC ts m a #

MonadThrow (CompositionBaseT ts m) => MonadThrow (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

throwM :: Exception e => e -> CompositionC ts m a #

MonadCatch (CompositionBaseT ts m) => MonadCatch (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

catch :: Exception e => CompositionC ts m a -> (e -> CompositionC ts m a) -> CompositionC ts m a #

MonadMask (CompositionBaseT ts m) => MonadMask (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

mask :: ((forall a. CompositionC ts m a -> CompositionC ts m a) -> CompositionC ts m b) -> CompositionC ts m b #

uninterruptibleMask :: ((forall a. CompositionC ts m a -> CompositionC ts m a) -> CompositionC ts m b) -> CompositionC ts m b #

generalBracket :: CompositionC ts m a -> (a -> ExitCase b -> CompositionC ts m c) -> (a -> CompositionC ts m b) -> CompositionC ts m (b, c) #

Carrier (CompositionBaseT ts m) => Carrier (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Associated Types

type Derivs (CompositionC ts m) :: [Effect] Source #

type Prims (CompositionC ts m) :: [Effect] Source #

type StT (CompositionC ts) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

type StT (CompositionC ts) a = StT (CompositionBaseT' (IdentityT :: (Type -> Type) -> Type -> Type) ts) a
type Derivs (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

type Derivs (CompositionC ts m) = Derivs (CompositionBaseT' (IdentityT :: (Type -> Type) -> Type -> Type) ts m)
type Prims (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

type Prims (CompositionC ts m) = Prims (CompositionBaseT' (IdentityT :: (Type -> Type) -> Type -> Type) ts m)
type StM (CompositionC ts m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

type StM (CompositionC ts m) a = StM (CompositionBaseT' (IdentityT :: (Type -> Type) -> Type -> Type) ts m) a

runComposition :: CompositionC ts m a -> CompositionBaseM ts m a Source #

Transform CompositionC [t1, t2, ..., tn] m a to t1 (t2 (... (tn m) ...)) a

Other utilities

newtype Effly m a Source #

A newtype wrapper with instances based around the effects of m when possible; Effly as in "Effectfully."

This is often useful for making use of these instances inside of interpreter handlers, or within application code.

Constructors

Effly 

Fields

Instances

Instances details
MonadBase b m => MonadBase b (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

liftBase :: b α -> Effly m α #

MonadBaseControl b m => MonadBaseControl b (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Associated Types

type StM (Effly m) a #

Methods

liftBaseWith :: (RunInBase (Effly m) b -> b a) -> Effly m a #

restoreM :: StM (Effly m) a -> Effly m a #

MonadTrans (Effly :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

lift :: Monad m => m a -> Effly m a #

MonadTransControl (Effly :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Associated Types

type StT Effly a #

Methods

liftWith :: Monad m => (Run Effly -> m a) -> Effly m a #

restoreT :: Monad m => m (StT Effly a) -> Effly m a #

Monad m => Monad (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

(>>=) :: Effly m a -> (a -> Effly m b) -> Effly m b #

(>>) :: Effly m a -> Effly m b -> Effly m b #

return :: a -> Effly m a #

Functor m => Functor (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

fmap :: (a -> b) -> Effly m a -> Effly m b #

(<$) :: a -> Effly m b -> Effly m a #

Eff Fix m => MonadFix (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

mfix :: (a -> Effly m a) -> Effly m a #

Eff Fail m => MonadFail (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

fail :: String -> Effly m a #

Applicative m => Applicative (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

pure :: a -> Effly m a #

(<*>) :: Effly m (a -> b) -> Effly m a -> Effly m b #

liftA2 :: (a -> b -> c) -> Effly m a -> Effly m b -> Effly m c #

(*>) :: Effly m a -> Effly m b -> Effly m b #

(<*) :: Effly m a -> Effly m b -> Effly m a #

Eff (Embed IO) m => MonadIO (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

liftIO :: IO a -> Effly m a #

Eff Alt m => Alternative (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

empty :: Effly m a #

(<|>) :: Effly m a -> Effly m a -> Effly m a #

some :: Effly m a -> Effly m [a] #

many :: Effly m a -> Effly m [a] #

Eff Alt m => MonadPlus (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

mzero :: Effly m a #

mplus :: Effly m a -> Effly m a -> Effly m a #

Eff ErrorIO m => MonadThrow (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

throwM :: Exception e => e -> Effly m a #

Eff ErrorIO m => MonadCatch (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

catch :: Exception e => Effly m a -> (e -> Effly m a) -> Effly m a #

Effs '[Mask, Bracket, ErrorIO] m => MonadMask (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

mask :: ((forall a. Effly m a -> Effly m a) -> Effly m b) -> Effly m b #

uninterruptibleMask :: ((forall a. Effly m a -> Effly m a) -> Effly m b) -> Effly m b #

generalBracket :: Effly m a -> (a -> ExitCase b -> Effly m c) -> (a -> Effly m b) -> Effly m (b, c) #

Carrier m => Carrier (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Associated Types

type Derivs (Effly m) :: [Effect] Source #

type Prims (Effly m) :: [Effect] Source #

type StT (Effly :: (Type -> Type) -> Type -> Type) a Source # 
Instance details

Defined in Control.Effect.Internal.Effly

type StT (Effly :: (Type -> Type) -> Type -> Type) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

type Derivs (Effly m) = Derivs m
type Prims (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

type Prims (Effly m) = Prims m
type StM (Effly m) a Source # 
Instance details

Defined in Control.Effect.Internal.Effly

type StM (Effly m) a = StM m a

subsume :: (Carrier m, Member e (Derivs m)) => SubsumeC e m a -> m a Source #

Interpret an effect in terms of another, identical effect.

This is very rarely useful, but one use-case is to transform reinterpreters into regular interpreters.

For example, subsume . reinterpretSimple @e h is morally equivalent to interpretSimple @e h

Reexports from other modules

class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase (b :: Type -> Type) (m :: Type -> Type) | m -> b where #

Methods

liftBase :: b α -> m α #

Lift a computation from the base monad

Instances

Instances details
MonadBase [] [] 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: [α] -> [α] #

MonadBase Maybe Maybe 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: Maybe α -> Maybe α #

MonadBase IO IO 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: IO α -> IO α #

MonadBase Identity Identity 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: Identity α -> Identity α #

MonadBase STM STM 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: STM α -> STM α #

MonadBase b m => MonadBase b (MaybeT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> MaybeT m α #

MonadBase b m => MonadBase b (ListT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ListT m α #

MonadBase b m => MonadBase b (ErrorIOToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.ErrorIO

Methods

liftBase :: b α -> ErrorIOToIOC m α #

MonadBase b m => MonadBase b (ConcToIOC m) Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

liftBase :: b α -> ConcToIOC m α #

MonadBase b m => MonadBase b (TraceListC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

liftBase :: b α -> TraceListC m α #

MonadBase b m => MonadBase b (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

liftBase :: b α -> ListT m α #

MonadBase b m => MonadBase b (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

liftBase :: b α -> NonDetC m α #

MonadBase b m => MonadBase b (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

liftBase :: b α -> CullCutC m α #

MonadBase b m => MonadBase b (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

liftBase :: b α -> LogicC m α #

MonadBase b m => MonadBase b (InterpretFailSimpleC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftBase :: b α -> InterpretFailSimpleC m α #

MonadBase b m => MonadBase b (FailC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftBase :: b α -> FailC m α #

MonadBase b m => MonadBase b (AltMaybeC m) Source # 
Instance details

Defined in Control.Effect.Alt

Methods

liftBase :: b α -> AltMaybeC m α #

MonadBase b m => MonadBase b (InterpretAltSimpleC m) Source # 
Instance details

Defined in Control.Effect.Alt

Methods

liftBase :: b α -> InterpretAltSimpleC m α #

Monad m => MonadBase m (Itself m) Source # 
Instance details

Defined in Control.Effect.Internal.Itself

Methods

liftBase :: m α -> Itself m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> WriterT w m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> WriterT w m α #

MonadBase b m => MonadBase b (StateT s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (StateT s m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (SelectT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> SelectT r m α #

MonadBase b m => MonadBase b (ReaderT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ReaderT r m α #

MonadBase b m => MonadBase b (IdentityT m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> IdentityT m α #

MonadBase b m => MonadBase b (ExceptT e m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ExceptT e m α #

(Error e, MonadBase b m) => MonadBase b (ErrorT e m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ErrorT e m α #

(Monoid w, MonadBase b m) => MonadBase b (AccumT w m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> AccumT w m α #

(Monad b, MonadBase b (CompositionBaseT ts m)) => MonadBase b (CompositionC ts m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

liftBase :: b α -> CompositionC ts m α #

MonadBase b m => MonadBase b (Effly m) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

liftBase :: b α -> Effly m α #

MonadBase b m => MonadBase b (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> InterpretPrimSimpleC e m α #

MonadBase b m => MonadBase b (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> InterpretSimpleC e m α #

MonadBase b m => MonadBase b (EmbedC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

liftBase :: b α -> EmbedC m α #

MonadBase b m => MonadBase b (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

liftBase :: b α -> RunMC m α #

MonadBase b m => MonadBase b (WriterCPS s m) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

liftBase :: b α -> WriterCPS s m α #

(Monoid o, MonadBase b m) => MonadBase b (WriterLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> WriterLazyC o m α #

(Monoid o, MonadBase b m) => MonadBase b (ListenLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> ListenLazyC o m α #

(Monoid o, MonadBase b m) => MonadBase b (TellLazyC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> TellLazyC o m α #

MonadBase b m => MonadBase b (WriterC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> WriterC o m α #

MonadBase b m => MonadBase b (ListenC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> ListenC o m α #

MonadBase b m => MonadBase b (TellC o m) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

liftBase :: b α -> TellC o m α #

MonadBase b m => MonadBase b (StateLazyC s m) Source # 
Instance details

Defined in Control.Effect.Internal.State

Methods

liftBase :: b α -> StateLazyC s m α #

MonadBase b m => MonadBase b (StateC s m) Source # 
Instance details

Defined in Control.Effect.Internal.State

Methods

liftBase :: b α -> StateC s m α #

MonadBase b m => MonadBase b (ReaderC i m) Source # 
Instance details

Defined in Control.Effect.Internal.Reader

Methods

liftBase :: b α -> ReaderC i m α #

MonadBase b m => MonadBase b (UnwrapTopC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Methods

liftBase :: b α -> UnwrapTopC e m α #

MonadBase b m => MonadBase b (UnwrapC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Methods

liftBase :: b α -> UnwrapC e m α #

MonadBase b m => MonadBase b (ErrorToIOSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> ErrorToIOSimpleC e m α #

MonadBase b m => MonadBase b (InterpretErrorSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> InterpretErrorSimpleC e m α #

MonadBase b m => MonadBase b (ErrorToIOAsExcC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> ErrorToIOAsExcC e m α #

MonadBase b m => MonadBase b (ErrorToErrorIOAsExcC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> ErrorToErrorIOAsExcC e m α #

MonadBase b m => MonadBase b (ErrorC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> ErrorC e m α #

MonadBase b m => MonadBase b (ThrowC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> ThrowC e m α #

MonadBase b m => MonadBase b (SafeErrorToErrorIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToErrorIOSimpleC exc m α #

MonadBase b m => MonadBase b (SafeErrorToIOSimpleC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToIOSimpleC exc m α #

MonadBase b m => MonadBase b (SafeErrorC exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorC exc m α #

MonadBase b m => MonadBase b (FreshEnumC uniq m) Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

liftBase :: b α -> FreshEnumC uniq m α #

MonadBase b m => MonadBase b (WriterTVarC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> WriterTVarC o m α #

MonadBase b m => MonadBase b (ListenTVarC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> ListenTVarC o m α #

MonadBase b m => MonadBase b (WriterToBracketC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> WriterToBracketC o m α #

MonadBase b m => MonadBase b (WriterIntoEndoWriterC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> WriterIntoEndoWriterC o m α #

MonadBase b m => MonadBase b (ListenIntoEndoListenC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> ListenIntoEndoListenC o m α #

MonadBase b m => MonadBase b (TellListLazyC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> TellListLazyC o m α #

MonadBase b m => MonadBase b (TellListC o m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

liftBase :: b α -> TellListC o m α #

MonadBase b m => MonadBase b (FreeT f m) Source # 
Instance details

Defined in Control.Monad.Trans.Free.Church.Alternate

Methods

liftBase :: b α -> FreeT f m α #

MonadBase b m => MonadBase b (ShiftC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

liftBase :: b α -> ShiftC r m α #

MonadBase b m => MonadBase b (ContC r m) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

liftBase :: b α -> ContC r m α #

MonadBase b m => MonadBase b (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

liftBase :: b α -> SteppedC e m α #

MonadBase b m => MonadBase b (InterceptRC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

liftBase :: b α -> InterceptRC e m α #

MonadBase b m => MonadBase b (ListenSteppedC w m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

liftBase :: b α -> ListenSteppedC w m α #

MonadBase b m => MonadBase b (InterceptContC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

liftBase :: b α -> InterceptContC e m α #

MonadBase b m => MonadBase b (InterpretFailC h m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

liftBase :: b α -> InterpretFailC h m α #

MonadBase b m => MonadBase b (InterpretAltC h m) Source # 
Instance details

Defined in Control.Effect.Alt

Methods

liftBase :: b α -> InterpretAltC h m α #

MonadBase b m => MonadBase b (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

liftBase :: b α -> SubsumeC e m α #

MonadBase b m => MonadBase b (ContT r m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ContT r m α #

MonadBase b m => MonadBase b (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

liftBase :: b α -> IntroC top new m α #

MonadBase b m => MonadBase b (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> ReinterpretSimpleC e new m α #

MonadBase b m => MonadBase b (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> InterpretC h e m α #

MonadBase b m => MonadBase b (InterpretPrimC s e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> InterpretPrimC s e m α #

MonadBase b m => MonadBase b (UnionC l m) Source # 
Instance details

Defined in Control.Effect.Union

Methods

liftBase :: b α -> UnionC l m α #

MonadBase b m => MonadBase b (WrapC e e' m) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Methods

liftBase :: b α -> WrapC e e' m α #

MonadBase b m => MonadBase b (SelectC s r m) Source # 
Instance details

Defined in Control.Effect.Internal.Select

Methods

liftBase :: b α -> SelectC s r m α #

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

Defined in Control.Monad.Base

Methods

liftBase :: b α -> RWST r w s m α #

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

Defined in Control.Monad.Base

Methods

liftBase :: b α -> RWST r w s m α #

MonadBase b (t (u m)) => MonadBase b (ComposeT t u m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

liftBase :: b α -> ComposeT t u m α #

MonadBase b m => MonadBase b (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> ReinterpretC h e new m α #

MonadBase b' m => MonadBase b' (UnionizeC b m) Source # 
Instance details

Defined in Control.Effect.Union

Methods

liftBase :: b' α -> UnionizeC b m α #

MonadBase b' m => MonadBase b' (UnionizeHeadC b m) Source # 
Instance details

Defined in Control.Effect.Union

Methods

liftBase :: b' α -> UnionizeHeadC b m α #

MonadBase b m => MonadBase b (ErrorToIOC' s s' e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> ErrorToIOC' s s' e m α #

MonadBase b m => MonadBase b (InterpretErrorC' s s' e m) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

liftBase :: b α -> InterpretErrorC' s s' e m α #

MonadBase b m => MonadBase b (SafeErrorToErrorIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToErrorIOC' s s' exc m α #

MonadBase b m => MonadBase b (SafeErrorToIOC' s s' exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> SafeErrorToIOC' s s' exc m α #

MonadBase b m => MonadBase b (ExceptionallyC eff exc m) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

liftBase :: b α -> ExceptionallyC eff exc m α #

(Reifies sHandler (HandlerCState p m z), Monad z, Monad m) => MonadBase m (HandlerC sHandler sReform r p m z) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: m α -> HandlerC sHandler sReform r p m z α #

(Monad m, MonadBase b z, Coercible z m) => MonadBase b (GainBaseControlC b z m) Source # 
Instance details

Defined in Control.Effect.BaseControl

Methods

liftBase :: b α -> GainBaseControlC b z m α #

MonadBase (Either e) (Either e) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: Either e α -> Either e α #

MonadBase (ST s) (ST s) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: ST s α -> ST s α #

MonadBase (ST s) (ST s) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: ST s α -> ST s α #

MonadBase ((->) r :: Type -> Type) ((->) r :: Type -> Type) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: (r -> α) -> r -> α #

class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a monad transformation:

Methods

lift :: Monad m => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.

Instances

Instances details
MonadTrans MaybeT 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

lift :: Monad m => m a -> MaybeT m a #

MonadTrans ListT 
Instance details

Defined in Control.Monad.Trans.List

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans ErrorIOToIOC Source # 
Instance details

Defined in Control.Effect.Internal.ErrorIO

Methods

lift :: Monad m => m a -> ErrorIOToIOC m a #

MonadTrans ConcToIOC Source # 
Instance details

Defined in Control.Effect.Internal.Conc

Methods

lift :: Monad m => m a -> ConcToIOC m a #

MonadTrans TraceListC Source # 
Instance details

Defined in Control.Effect.Trace

Methods

lift :: Monad m => m a -> TraceListC m a #

MonadTrans ListT Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans NonDetC Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

lift :: Monad m => m a -> NonDetC m a #

MonadTrans CullCutC Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

lift :: Monad m => m a -> CullCutC m a #

MonadTrans LogicC Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

lift :: Monad m => m a -> LogicC m a #

MonadTrans InterpretFailSimpleC Source # 
Instance details

Defined in Control.Effect.Fail

Methods

lift :: Monad m => m a -> InterpretFailSimpleC m a #

MonadTrans FailC Source # 
Instance details

Defined in Control.Effect.Fail

Methods

lift :: Monad m => m a -> FailC m a #

MonadTrans AltMaybeC Source # 
Instance details

Defined in Control.Effect.Alt

Methods

lift :: Monad m => m a -> AltMaybeC m a #

MonadTrans InterpretAltSimpleC Source # 
Instance details

Defined in Control.Effect.Alt

Methods

lift :: Monad m => m a -> InterpretAltSimpleC m a #

MonadTrans (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

lift :: Monad m => m a -> StateT s m a #

MonadTrans (ReaderT r) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

lift :: Monad m => m a -> ReaderT r m a #

MonadTrans (ErrorT e) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

lift :: Monad m => m a -> ErrorT e m a #

MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

lift :: Monad m => m a -> IdentityT m a #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

lift :: Monad m => m a -> WriterT w m a #

Monoid w => MonadTrans (AccumT w) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

lift :: Monad m => m a -> AccumT w m a #

MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (SelectT r) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

lift :: Monad m => m a -> SelectT r m a #

MonadTrans (CompositionBaseT ts) => MonadTrans (CompositionC ts) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

lift :: Monad m => m a -> CompositionC ts m a #

MonadTrans (Effly :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Effly

Methods

lift :: Monad m => m a -> Effly m a #

MonadTrans (InterpretPrimSimpleC e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> InterpretPrimSimpleC e m a #

MonadTrans (InterpretSimpleC e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> InterpretSimpleC e m a #

MonadTrans (EmbedC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

lift :: Monad m => m a -> EmbedC m a #

MonadTrans (RunMC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

lift :: Monad m => m a -> RunMC m a #

MonadTrans (WriterCPS s) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

lift :: Monad m => m a -> WriterCPS s m a #

Monoid o => MonadTrans (WriterLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> WriterLazyC o m a #

Monoid o => MonadTrans (ListenLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> ListenLazyC o m a #

Monoid o => MonadTrans (TellLazyC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> TellLazyC o m a #

MonadTrans (WriterC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> WriterC o m a #

MonadTrans (ListenC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> ListenC o m a #

MonadTrans (TellC o) Source # 
Instance details

Defined in Control.Effect.Internal.Writer

Methods

lift :: Monad m => m a -> TellC o m a #

MonadTrans (UnliftC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Unlift

Methods

lift :: Monad m => m a -> UnliftC m a #

MonadTrans (StateLazyC s) Source # 
Instance details

Defined in Control.Effect.Internal.State

Methods

lift :: Monad m => m a -> StateLazyC s m a #

MonadTrans (StateC s) Source # 
Instance details

Defined in Control.Effect.Internal.State

Methods

lift :: Monad m => m a -> StateC s m a #

MonadTrans (HoistC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Regional

Methods

lift :: Monad m => m a -> HoistC m a #

MonadTrans (ReaderC i) Source # 
Instance details

Defined in Control.Effect.Internal.Reader

Methods

lift :: Monad m => m a -> ReaderC i m a #

MonadTrans (HoistOptionC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Optional

Methods

lift :: Monad m => m a -> HoistOptionC m a #

MonadTrans (UnwrapTopC e) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Methods

lift :: Monad m => m a -> UnwrapTopC e m a #

MonadTrans (UnwrapC e) Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Methods

lift :: Monad m => m a -> UnwrapC e m a #

MonadTrans (ErrorToIOSimpleC e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> ErrorToIOSimpleC e m a #

MonadTrans (InterpretErrorSimpleC e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> InterpretErrorSimpleC e m a #

MonadTrans (ErrorToIOAsExcC e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> ErrorToIOAsExcC e m a #

MonadTrans (ErrorToErrorIOAsExcC e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> ErrorToErrorIOAsExcC e m a #

MonadTrans (ErrorC e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> ErrorC e m a #

MonadTrans (ThrowC e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> ThrowC e m a #

MonadTrans (SafeErrorToErrorIOSimpleC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToErrorIOSimpleC exc m a #

MonadTrans (SafeErrorToIOSimpleC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToIOSimpleC exc m a #

MonadTrans (SafeErrorC exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorC exc m a #

MonadTrans (BaseControlC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.BaseControl

Methods

lift :: Monad m => m a -> BaseControlC m a #

MonadTrans (FreshEnumC uniq) Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

lift :: Monad m => m a -> FreshEnumC uniq m a #

MonadTrans (WriterTVarC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> WriterTVarC o m a #

MonadTrans (ListenTVarC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> ListenTVarC o m a #

MonadTrans (WriterToBracketC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> WriterToBracketC o m a #

MonadTrans (WriterIntoEndoWriterC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> WriterIntoEndoWriterC o m a #

MonadTrans (ListenIntoEndoListenC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> ListenIntoEndoListenC o m a #

MonadTrans (TellListLazyC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> TellListLazyC o m a #

MonadTrans (TellListC o) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

lift :: Monad m => m a -> TellListC o m a #

MonadTrans (FreeT f) Source # 
Instance details

Defined in Control.Monad.Trans.Free.Church.Alternate

Methods

lift :: Monad m => m a -> FreeT f m a #

MonadTrans (ShiftC s) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

lift :: Monad m => m a -> ShiftC s m a #

MonadTrans (ContC s) Source # 
Instance details

Defined in Control.Effect.Internal.Cont

Methods

lift :: Monad m => m a -> ContC s m a #

MonadTrans (SteppedC e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Stepped

Methods

lift :: Monad m => m a -> SteppedC e m a #

MonadTrans (InterceptRC e) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

lift :: Monad m => m a -> InterceptRC e m a #

MonadTrans (ListenSteppedC w) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

lift :: Monad m => m a -> ListenSteppedC w m a #

MonadTrans (InterceptContC e) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

Methods

lift :: Monad m => m a -> InterceptContC e m a #

MonadTrans (InterpretFailC h) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

lift :: Monad m => m a -> InterpretFailC h m a #

MonadTrans (InterpretAltC h) Source # 
Instance details

Defined in Control.Effect.Alt

Methods

lift :: Monad m => m a -> InterpretAltC h m a #

MonadTrans (ContT r) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

lift :: Monad m => m a -> ContT r m a #

MonadTrans (SubsumeC e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

lift :: Monad m => m a -> SubsumeC e m a #

MonadTrans (IntroC top new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

lift :: Monad m => m a -> IntroC top new m a #

MonadTrans (ReinterpretSimpleC e new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> ReinterpretSimpleC e new m a #

MonadTrans (InterpretC h e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> InterpretC h e m a #

MonadTrans (InterpretPrimC s e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> InterpretPrimC s e m a #

MonadTrans (UnionC l :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Union

Methods

lift :: Monad m => m a -> UnionC l m a #

MonadTrans (WrapC e e') Source # 
Instance details

Defined in Control.Effect.Internal.Newtype

Methods

lift :: Monad m => m a -> WrapC e e' m a #

MonadTrans (SelectC s r) Source # 
Instance details

Defined in Control.Effect.Internal.Select

Methods

lift :: Monad m => m a -> SelectC s r m a #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

lift :: Monad m => m a -> RWST r w s m a #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

lift :: Monad m => m a -> RWST r w s m a #

(MonadTrans t, MonadTrans u, forall (m :: Type -> Type). Monad m => Monad (u m)) => MonadTrans (ComposeT t u) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Compose

Methods

lift :: Monad m => m a -> ComposeT t u m a #

MonadTrans (ReinterpretC h e new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> ReinterpretC h e new m a #

MonadTrans (UnionizeC b :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Union

Methods

lift :: Monad m => m a -> UnionizeC b m a #

MonadTrans (UnionizeHeadC b :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Union

Methods

lift :: Monad m => m a -> UnionizeHeadC b m a #

MonadTrans (ErrorToIOC' s s' e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> ErrorToIOC' s s' e m a #

MonadTrans (InterpretErrorC' s s' e) Source # 
Instance details

Defined in Control.Effect.Internal.Error

Methods

lift :: Monad m => m a -> InterpretErrorC' s s' e m a #

MonadTrans (SafeErrorToErrorIOC' s s' exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToErrorIOC' s s' exc m a #

MonadTrans (SafeErrorToIOC' s s' exc) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> SafeErrorToIOC' s s' exc m a #

MonadTrans (ExceptionallyC eff exc :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal.Exceptional

Methods

lift :: Monad m => m a -> ExceptionallyC eff exc m a #

MonadTrans (GainBaseControlC b z :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.BaseControl

Methods

lift :: Monad m => m a -> GainBaseControlC b z m a #

Carriers and other misc. types

type RunC = Identity Source #

The identity carrier, which carries no effects at all.

data RunMC m a Source #

The carrier for runM, which carries no effects but Embed m.

Instances

Instances details
MonadBase b m => MonadBase b (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

liftBase :: b α -> RunMC m α #

MonadBaseControl b m => MonadBaseControl b (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type StM (RunMC m) a #

Methods

liftBaseWith :: (RunInBase (RunMC m) b -> b a) -> RunMC m a #

restoreM :: StM (RunMC m) a -> RunMC m a #

MonadTrans (RunMC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

lift :: Monad m => m a -> RunMC m a #

MonadTransControl (RunMC :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type StT RunMC a #

Methods

liftWith :: Monad m => (Run RunMC -> m a) -> RunMC m a #

restoreT :: Monad m => m (StT RunMC a) -> RunMC m a #

Monad m => Monad (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

(>>=) :: RunMC m a -> (a -> RunMC m b) -> RunMC m b #

(>>) :: RunMC m a -> RunMC m b -> RunMC m b #

return :: a -> RunMC m a #

Functor m => Functor (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

fmap :: (a -> b) -> RunMC m a -> RunMC m b #

(<$) :: a -> RunMC m b -> RunMC m a #

MonadFix m => MonadFix (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

mfix :: (a -> RunMC m a) -> RunMC m a #

MonadFail m => MonadFail (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

fail :: String -> RunMC m a #

Applicative m => Applicative (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

pure :: a -> RunMC m a #

(<*>) :: RunMC m (a -> b) -> RunMC m a -> RunMC m b #

liftA2 :: (a -> b -> c) -> RunMC m a -> RunMC m b -> RunMC m c #

(*>) :: RunMC m a -> RunMC m b -> RunMC m b #

(<*) :: RunMC m a -> RunMC m b -> RunMC m a #

MonadIO m => MonadIO (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

liftIO :: IO a -> RunMC m a #

Alternative m => Alternative (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

empty :: RunMC m a #

(<|>) :: RunMC m a -> RunMC m a -> RunMC m a #

some :: RunMC m a -> RunMC m [a] #

many :: RunMC m a -> RunMC m [a] #

MonadPlus m => MonadPlus (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

mzero :: RunMC m a #

mplus :: RunMC m a -> RunMC m a -> RunMC m a #

MonadThrow m => MonadThrow (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

throwM :: Exception e => e -> RunMC m a #

MonadCatch m => MonadCatch (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

catch :: Exception e => RunMC m a -> (e -> RunMC m a) -> RunMC m a #

MonadMask m => MonadMask (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

mask :: ((forall a. RunMC m a -> RunMC m a) -> RunMC m b) -> RunMC m b #

uninterruptibleMask :: ((forall a. RunMC m a -> RunMC m a) -> RunMC m b) -> RunMC m b #

generalBracket :: RunMC m a -> (a -> ExitCase b -> RunMC m c) -> (a -> RunMC m b) -> RunMC m (b, c) #

Monad m => Carrier (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type Derivs (RunMC m) :: [Effect] Source #

type Prims (RunMC m) :: [Effect] Source #

type StT (RunMC :: (Type -> Type) -> Type -> Type) a Source # 
Instance details

Defined in Control.Effect.Embed

type StT (RunMC :: (Type -> Type) -> Type -> Type) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

type Derivs (RunMC m) = '[Embed m]
type Prims (RunMC m) Source # 
Instance details

Defined in Control.Effect.Embed

type Prims (RunMC m) = '[] :: [Effect]
type StM (RunMC m) a Source # 
Instance details

Defined in Control.Effect.Embed

type StM (RunMC m) a = StM m a

data InterpretSimpleC (e :: Effect) (m :: * -> *) a Source #

Instances

Instances details
MonadBase b m => MonadBase b (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> InterpretSimpleC e m α #

MonadBaseControl b m => MonadBaseControl b (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StM (InterpretSimpleC e m) a #

MonadTrans (InterpretSimpleC e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> InterpretSimpleC e m a #

Monad m => Monad (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

(>>=) :: InterpretSimpleC e m a -> (a -> InterpretSimpleC e m b) -> InterpretSimpleC e m b #

(>>) :: InterpretSimpleC e m a -> InterpretSimpleC e m b -> InterpretSimpleC e m b #

return :: a -> InterpretSimpleC e m a #

Functor m => Functor (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fmap :: (a -> b) -> InterpretSimpleC e m a -> InterpretSimpleC e m b #

(<$) :: a -> InterpretSimpleC e m b -> InterpretSimpleC e m a #

MonadFix m => MonadFix (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mfix :: (a -> InterpretSimpleC e m a) -> InterpretSimpleC e m a #

MonadFail m => MonadFail (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fail :: String -> InterpretSimpleC e m a #

Applicative m => Applicative (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

pure :: a -> InterpretSimpleC e m a #

(<*>) :: InterpretSimpleC e m (a -> b) -> InterpretSimpleC e m a -> InterpretSimpleC e m b #

liftA2 :: (a -> b -> c) -> InterpretSimpleC e m a -> InterpretSimpleC e m b -> InterpretSimpleC e m c #

(*>) :: InterpretSimpleC e m a -> InterpretSimpleC e m b -> InterpretSimpleC e m b #

(<*) :: InterpretSimpleC e m a -> InterpretSimpleC e m b -> InterpretSimpleC e m a #

MonadIO m => MonadIO (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

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

Alternative m => Alternative (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

MonadPlus m => MonadPlus (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

MonadThrow m => MonadThrow (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

throwM :: Exception e0 => e0 -> InterpretSimpleC e m a #

MonadCatch m => MonadCatch (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

catch :: Exception e0 => InterpretSimpleC e m a -> (e0 -> InterpretSimpleC e m a) -> InterpretSimpleC e m a #

MonadMask m => MonadMask (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mask :: ((forall a. InterpretSimpleC e m a -> InterpretSimpleC e m a) -> InterpretSimpleC e m b) -> InterpretSimpleC e m b #

uninterruptibleMask :: ((forall a. InterpretSimpleC e m a -> InterpretSimpleC e m a) -> InterpretSimpleC e m b) -> InterpretSimpleC e m b #

generalBracket :: InterpretSimpleC e m a -> (a -> ExitCase b -> InterpretSimpleC e m c) -> (a -> InterpretSimpleC e m b) -> InterpretSimpleC e m (b, c) #

(Threads (ReaderT (ReifiedHandler e m)) (Prims m), RepresentationalEff e, Carrier m) => Carrier (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (InterpretSimpleC e m) :: [Effect] Source #

type Prims (InterpretSimpleC e m) :: [Effect] Source #

type Derivs (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Derivs (InterpretSimpleC e m) = e ': Derivs m
type Prims (InterpretSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (InterpretSimpleC e m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (InterpretSimpleC e m) a = StM (ReaderT (ReifiedHandler e m) m) a

data InterpretC (h :: *) (e :: Effect) (m :: * -> *) a Source #

Instances

Instances details
MonadBase b m => MonadBase b (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> InterpretC h e m α #

MonadBaseControl b m => MonadBaseControl b (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StM (InterpretC h e m) a #

Methods

liftBaseWith :: (RunInBase (InterpretC h e m) b -> b a) -> InterpretC h e m a #

restoreM :: StM (InterpretC h e m) a -> InterpretC h e m a #

MonadTrans (InterpretC h e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> InterpretC h e m a #

MonadTransControl (InterpretC h e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StT (InterpretC h e) a #

Methods

liftWith :: Monad m => (Run (InterpretC h e) -> m a) -> InterpretC h e m a #

restoreT :: Monad m => m (StT (InterpretC h e) a) -> InterpretC h e m a #

Monad m => Monad (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

(>>=) :: InterpretC h e m a -> (a -> InterpretC h e m b) -> InterpretC h e m b #

(>>) :: InterpretC h e m a -> InterpretC h e m b -> InterpretC h e m b #

return :: a -> InterpretC h e m a #

Functor m => Functor (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fmap :: (a -> b) -> InterpretC h e m a -> InterpretC h e m b #

(<$) :: a -> InterpretC h e m b -> InterpretC h e m a #

MonadFix m => MonadFix (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mfix :: (a -> InterpretC h e m a) -> InterpretC h e m a #

MonadFail m => MonadFail (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fail :: String -> InterpretC h e m a #

Applicative m => Applicative (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

pure :: a -> InterpretC h e m a #

(<*>) :: InterpretC h e m (a -> b) -> InterpretC h e m a -> InterpretC h e m b #

liftA2 :: (a -> b -> c) -> InterpretC h e m a -> InterpretC h e m b -> InterpretC h e m c #

(*>) :: InterpretC h e m a -> InterpretC h e m b -> InterpretC h e m b #

(<*) :: InterpretC h e m a -> InterpretC h e m b -> InterpretC h e m a #

MonadIO m => MonadIO (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftIO :: IO a -> InterpretC h e m a #

Alternative m => Alternative (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

empty :: InterpretC h e m a #

(<|>) :: InterpretC h e m a -> InterpretC h e m a -> InterpretC h e m a #

some :: InterpretC h e m a -> InterpretC h e m [a] #

many :: InterpretC h e m a -> InterpretC h e m [a] #

MonadPlus m => MonadPlus (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mzero :: InterpretC h e m a #

mplus :: InterpretC h e m a -> InterpretC h e m a -> InterpretC h e m a #

MonadThrow m => MonadThrow (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

throwM :: Exception e0 => e0 -> InterpretC h e m a #

MonadCatch m => MonadCatch (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

catch :: Exception e0 => InterpretC h e m a -> (e0 -> InterpretC h e m a) -> InterpretC h e m a #

MonadMask m => MonadMask (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mask :: ((forall a. InterpretC h e m a -> InterpretC h e m a) -> InterpretC h e m b) -> InterpretC h e m b #

uninterruptibleMask :: ((forall a. InterpretC h e m a -> InterpretC h e m a) -> InterpretC h e m b) -> InterpretC h e m b #

generalBracket :: InterpretC h e m a -> (a -> ExitCase b -> InterpretC h e m c) -> (a -> InterpretC h e m b) -> InterpretC h e m (b, c) #

(Carrier m, Handler h e m) => Carrier (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (InterpretC h e m) :: [Effect] Source #

type Prims (InterpretC h e m) :: [Effect] Source #

type StT (InterpretC h e) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StT (InterpretC h e) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Derivs (InterpretC h e m) = e ': Derivs m
type Prims (InterpretC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Prims (InterpretC h e m) = Prims m
type StM (InterpretC h e m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (InterpretC h e m) a = StM m a

type InterpretReifiedC e m a = forall s. ReifiesHandler s e m => InterpretC (ViaReifiedH s) e m a Source #

data ReinterpretSimpleC e new m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> ReinterpretSimpleC e new m α #

MonadBaseControl b m => MonadBaseControl b (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StM (ReinterpretSimpleC e new m) a #

Methods

liftBaseWith :: (RunInBase (ReinterpretSimpleC e new m) b -> b a) -> ReinterpretSimpleC e new m a #

restoreM :: StM (ReinterpretSimpleC e new m) a -> ReinterpretSimpleC e new m a #

MonadTrans (ReinterpretSimpleC e new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> ReinterpretSimpleC e new m a #

Monad m => Monad (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

(>>=) :: ReinterpretSimpleC e new m a -> (a -> ReinterpretSimpleC e new m b) -> ReinterpretSimpleC e new m b #

(>>) :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m b -> ReinterpretSimpleC e new m b #

return :: a -> ReinterpretSimpleC e new m a #

Functor m => Functor (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fmap :: (a -> b) -> ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m b #

(<$) :: a -> ReinterpretSimpleC e new m b -> ReinterpretSimpleC e new m a #

MonadFix m => MonadFix (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mfix :: (a -> ReinterpretSimpleC e new m a) -> ReinterpretSimpleC e new m a #

MonadFail m => MonadFail (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fail :: String -> ReinterpretSimpleC e new m a #

Applicative m => Applicative (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

pure :: a -> ReinterpretSimpleC e new m a #

(<*>) :: ReinterpretSimpleC e new m (a -> b) -> ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m b #

liftA2 :: (a -> b -> c) -> ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m b -> ReinterpretSimpleC e new m c #

(*>) :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m b -> ReinterpretSimpleC e new m b #

(<*) :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m b -> ReinterpretSimpleC e new m a #

MonadIO m => MonadIO (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftIO :: IO a -> ReinterpretSimpleC e new m a #

Alternative m => Alternative (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

empty :: ReinterpretSimpleC e new m a #

(<|>) :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m a #

some :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m [a] #

many :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m [a] #

MonadPlus m => MonadPlus (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mzero :: ReinterpretSimpleC e new m a #

mplus :: ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m a #

MonadThrow m => MonadThrow (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

throwM :: Exception e0 => e0 -> ReinterpretSimpleC e new m a #

MonadCatch m => MonadCatch (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

catch :: Exception e0 => ReinterpretSimpleC e new m a -> (e0 -> ReinterpretSimpleC e new m a) -> ReinterpretSimpleC e new m a #

MonadMask m => MonadMask (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mask :: ((forall a. ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m a) -> ReinterpretSimpleC e new m b) -> ReinterpretSimpleC e new m b #

uninterruptibleMask :: ((forall a. ReinterpretSimpleC e new m a -> ReinterpretSimpleC e new m a) -> ReinterpretSimpleC e new m b) -> ReinterpretSimpleC e new m b #

generalBracket :: ReinterpretSimpleC e new m a -> (a -> ExitCase b -> ReinterpretSimpleC e new m c) -> (a -> ReinterpretSimpleC e new m b) -> ReinterpretSimpleC e new m (b, c) #

(Threads (ReaderT (ReifiedHandler e m)) (Prims m), RepresentationalEff e, KnownList new, HeadEffs new m, Carrier m) => Carrier (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (ReinterpretSimpleC e new m) :: [Effect] Source #

type Prims (ReinterpretSimpleC e new m) :: [Effect] Source #

type Derivs (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Prims (ReinterpretSimpleC e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (ReinterpretSimpleC e new m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (ReinterpretSimpleC e new m) a = StM (IntroC '[e] new (InterpretSimpleC e m)) a

data ReinterpretC h e new m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftBase :: b α -> ReinterpretC h e new m α #

MonadBaseControl b m => MonadBaseControl b (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StM (ReinterpretC h e new m) a #

Methods

liftBaseWith :: (RunInBase (ReinterpretC h e new m) b -> b a) -> ReinterpretC h e new m a #

restoreM :: StM (ReinterpretC h e new m) a -> ReinterpretC h e new m a #

MonadTrans (ReinterpretC h e new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

lift :: Monad m => m a -> ReinterpretC h e new m a #

MonadTransControl (ReinterpretC h e new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StT (ReinterpretC h e new) a #

Methods

liftWith :: Monad m => (Run (ReinterpretC h e new) -> m a) -> ReinterpretC h e new m a #

restoreT :: Monad m => m (StT (ReinterpretC h e new) a) -> ReinterpretC h e new m a #

Monad m => Monad (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

(>>=) :: ReinterpretC h e new m a -> (a -> ReinterpretC h e new m b) -> ReinterpretC h e new m b #

(>>) :: ReinterpretC h e new m a -> ReinterpretC h e new m b -> ReinterpretC h e new m b #

return :: a -> ReinterpretC h e new m a #

Functor m => Functor (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fmap :: (a -> b) -> ReinterpretC h e new m a -> ReinterpretC h e new m b #

(<$) :: a -> ReinterpretC h e new m b -> ReinterpretC h e new m a #

MonadFix m => MonadFix (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mfix :: (a -> ReinterpretC h e new m a) -> ReinterpretC h e new m a #

MonadFail m => MonadFail (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fail :: String -> ReinterpretC h e new m a #

Applicative m => Applicative (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

pure :: a -> ReinterpretC h e new m a #

(<*>) :: ReinterpretC h e new m (a -> b) -> ReinterpretC h e new m a -> ReinterpretC h e new m b #

liftA2 :: (a -> b -> c) -> ReinterpretC h e new m a -> ReinterpretC h e new m b -> ReinterpretC h e new m c #

(*>) :: ReinterpretC h e new m a -> ReinterpretC h e new m b -> ReinterpretC h e new m b #

(<*) :: ReinterpretC h e new m a -> ReinterpretC h e new m b -> ReinterpretC h e new m a #

MonadIO m => MonadIO (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftIO :: IO a -> ReinterpretC h e new m a #

Alternative m => Alternative (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

empty :: ReinterpretC h e new m a #

(<|>) :: ReinterpretC h e new m a -> ReinterpretC h e new m a -> ReinterpretC h e new m a #

some :: ReinterpretC h e new m a -> ReinterpretC h e new m [a] #

many :: ReinterpretC h e new m a -> ReinterpretC h e new m [a] #

MonadPlus m => MonadPlus (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mzero :: ReinterpretC h e new m a #

mplus :: ReinterpretC h e new m a -> ReinterpretC h e new m a -> ReinterpretC h e new m a #

MonadThrow m => MonadThrow (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

throwM :: Exception e0 => e0 -> ReinterpretC h e new m a #

MonadCatch m => MonadCatch (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

catch :: Exception e0 => ReinterpretC h e new m a -> (e0 -> ReinterpretC h e new m a) -> ReinterpretC h e new m a #

MonadMask m => MonadMask (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mask :: ((forall a. ReinterpretC h e new m a -> ReinterpretC h e new m a) -> ReinterpretC h e new m b) -> ReinterpretC h e new m b #

uninterruptibleMask :: ((forall a. ReinterpretC h e new m a -> ReinterpretC h e new m a) -> ReinterpretC h e new m b) -> ReinterpretC h e new m b #

generalBracket :: ReinterpretC h e new m a -> (a -> ExitCase b -> ReinterpretC h e new m c) -> (a -> ReinterpretC h e new m b) -> ReinterpretC h e new m (b, c) #

(Handler h e m, Carrier m, KnownList new, IntroConsistent ('[] :: [Effect]) new m) => Carrier (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type Derivs (ReinterpretC h e new m) :: [Effect] Source #

type Prims (ReinterpretC h e new m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (ReinterpretC h e new m)) (ReinterpretC h e new m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (ReinterpretC h e new m)) (Prims (ReinterpretC h e new m)) (ReinterpretC h e new m) z a Source #

algDerivs :: Algebra' (Derivs (ReinterpretC h e new m)) (ReinterpretC h e new m) a Source #

type StT (ReinterpretC h e new) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StT (ReinterpretC h e new) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Derivs (ReinterpretC h e new m) = Derivs (IntroUnderC e new (InterpretC h e m))
type Prims (ReinterpretC h e new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Prims (ReinterpretC h e new m) = Prims (IntroUnderC e new (InterpretC h e m))
type StM (ReinterpretC h e new m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (ReinterpretC h e new m) a = StM (IntroC '[e] new (InterpretC h e m)) a

type ReinterpretReifiedC e new m a = forall s. ReifiesHandler s e m => ReinterpretC (ViaReifiedH s) e new m a Source #

type IntroConsistent top new m = Append top (Append new (StripPrefix new (StripPrefix top (Derivs m)))) ~ Derivs m Source #

A constraint that the effect stack of m -- Derivs m -- begins with Append top new.

data IntroC (top :: [Effect]) (new :: [Effect]) (m :: * -> *) a Source #

Instances

Instances details
MonadBase b m => MonadBase b (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

liftBase :: b α -> IntroC top new m α #

MonadBaseControl b m => MonadBaseControl b (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type StM (IntroC top new m) a #

Methods

liftBaseWith :: (RunInBase (IntroC top new m) b -> b a) -> IntroC top new m a #

restoreM :: StM (IntroC top new m) a -> IntroC top new m a #

MonadTrans (IntroC top new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

lift :: Monad m => m a -> IntroC top new m a #

MonadTransControl (IntroC top new) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type StT (IntroC top new) a #

Methods

liftWith :: Monad m => (Run (IntroC top new) -> m a) -> IntroC top new m a #

restoreT :: Monad m => m (StT (IntroC top new) a) -> IntroC top new m a #

Monad m => Monad (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

(>>=) :: IntroC top new m a -> (a -> IntroC top new m b) -> IntroC top new m b #

(>>) :: IntroC top new m a -> IntroC top new m b -> IntroC top new m b #

return :: a -> IntroC top new m a #

Functor m => Functor (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

fmap :: (a -> b) -> IntroC top new m a -> IntroC top new m b #

(<$) :: a -> IntroC top new m b -> IntroC top new m a #

MonadFix m => MonadFix (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

mfix :: (a -> IntroC top new m a) -> IntroC top new m a #

MonadFail m => MonadFail (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

fail :: String -> IntroC top new m a #

Applicative m => Applicative (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

pure :: a -> IntroC top new m a #

(<*>) :: IntroC top new m (a -> b) -> IntroC top new m a -> IntroC top new m b #

liftA2 :: (a -> b -> c) -> IntroC top new m a -> IntroC top new m b -> IntroC top new m c #

(*>) :: IntroC top new m a -> IntroC top new m b -> IntroC top new m b #

(<*) :: IntroC top new m a -> IntroC top new m b -> IntroC top new m a #

MonadIO m => MonadIO (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

liftIO :: IO a -> IntroC top new m a #

Alternative m => Alternative (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

empty :: IntroC top new m a #

(<|>) :: IntroC top new m a -> IntroC top new m a -> IntroC top new m a #

some :: IntroC top new m a -> IntroC top new m [a] #

many :: IntroC top new m a -> IntroC top new m [a] #

MonadPlus m => MonadPlus (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

mzero :: IntroC top new m a #

mplus :: IntroC top new m a -> IntroC top new m a -> IntroC top new m a #

MonadThrow m => MonadThrow (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

throwM :: Exception e => e -> IntroC top new m a #

MonadCatch m => MonadCatch (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

catch :: Exception e => IntroC top new m a -> (e -> IntroC top new m a) -> IntroC top new m a #

MonadMask m => MonadMask (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Methods

mask :: ((forall a. IntroC top new m a -> IntroC top new m a) -> IntroC top new m b) -> IntroC top new m b #

uninterruptibleMask :: ((forall a. IntroC top new m a -> IntroC top new m a) -> IntroC top new m b) -> IntroC top new m b #

generalBracket :: IntroC top new m a -> (a -> ExitCase b -> IntroC top new m c) -> (a -> IntroC top new m b) -> IntroC top new m (b, c) #

(Carrier m, KnownList top, KnownList new, IntroConsistent top new m) => Carrier (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

Associated Types

type Derivs (IntroC top new m) :: [Effect] Source #

type Prims (IntroC top new m) :: [Effect] Source #

Methods

algPrims :: Algebra' (Prims (IntroC top new m)) (IntroC top new m) a Source #

reformulate :: Monad z => Reformulation' (Derivs (IntroC top new m)) (Prims (IntroC top new m)) (IntroC top new m) z a Source #

algDerivs :: Algebra' (Derivs (IntroC top new m)) (IntroC top new m) a Source #

type StT (IntroC top new) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type StT (IntroC top new) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type Derivs (IntroC top new m) = Append top (RestDerivs top new m)
type Prims (IntroC top new m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type Prims (IntroC top new m) = Prims m
type StM (IntroC top new m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Intro

type StM (IntroC top new m) a = StM m a

type IntroUnderC e = IntroC '[e] Source #

type IntroUnderManyC = IntroC Source #

Synonym for IntroC to match introUnderMany

class KnownList l Source #

Minimal complete definition

singList

Instances

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

Defined in Control.Effect.Internal.KnownList

Methods

singList :: SList '[] Source #

KnownList xs => KnownList (x ': xs :: [a]) Source # 
Instance details

Defined in Control.Effect.Internal.KnownList

Methods

singList :: SList (x ': xs) Source #

data SubsumeC (e :: Effect) m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

liftBase :: b α -> SubsumeC e m α #

MonadBaseControl b m => MonadBaseControl b (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type StM (SubsumeC e m) a #

Methods

liftBaseWith :: (RunInBase (SubsumeC e m) b -> b a) -> SubsumeC e m a #

restoreM :: StM (SubsumeC e m) a -> SubsumeC e m a #

MonadTrans (SubsumeC e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

lift :: Monad m => m a -> SubsumeC e m a #

MonadTransControl (SubsumeC e :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type StT (SubsumeC e) a #

Methods

liftWith :: Monad m => (Run (SubsumeC e) -> m a) -> SubsumeC e m a #

restoreT :: Monad m => m (StT (SubsumeC e) a) -> SubsumeC e m a #

Monad m => Monad (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

(>>=) :: SubsumeC e m a -> (a -> SubsumeC e m b) -> SubsumeC e m b #

(>>) :: SubsumeC e m a -> SubsumeC e m b -> SubsumeC e m b #

return :: a -> SubsumeC e m a #

Functor m => Functor (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

fmap :: (a -> b) -> SubsumeC e m a -> SubsumeC e m b #

(<$) :: a -> SubsumeC e m b -> SubsumeC e m a #

MonadFix m => MonadFix (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

mfix :: (a -> SubsumeC e m a) -> SubsumeC e m a #

MonadFail m => MonadFail (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

fail :: String -> SubsumeC e m a #

Applicative m => Applicative (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

pure :: a -> SubsumeC e m a #

(<*>) :: SubsumeC e m (a -> b) -> SubsumeC e m a -> SubsumeC e m b #

liftA2 :: (a -> b -> c) -> SubsumeC e m a -> SubsumeC e m b -> SubsumeC e m c #

(*>) :: SubsumeC e m a -> SubsumeC e m b -> SubsumeC e m b #

(<*) :: SubsumeC e m a -> SubsumeC e m b -> SubsumeC e m a #

MonadIO m => MonadIO (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

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

Alternative m => Alternative (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

empty :: SubsumeC e m a #

(<|>) :: SubsumeC e m a -> SubsumeC e m a -> SubsumeC e m a #

some :: SubsumeC e m a -> SubsumeC e m [a] #

many :: SubsumeC e m a -> SubsumeC e m [a] #

MonadPlus m => MonadPlus (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

mzero :: SubsumeC e m a #

mplus :: SubsumeC e m a -> SubsumeC e m a -> SubsumeC e m a #

MonadThrow m => MonadThrow (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

throwM :: Exception e0 => e0 -> SubsumeC e m a #

MonadCatch m => MonadCatch (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

catch :: Exception e0 => SubsumeC e m a -> (e0 -> SubsumeC e m a) -> SubsumeC e m a #

MonadMask m => MonadMask (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Methods

mask :: ((forall a. SubsumeC e m a -> SubsumeC e m a) -> SubsumeC e m b) -> SubsumeC e m b #

uninterruptibleMask :: ((forall a. SubsumeC e m a -> SubsumeC e m a) -> SubsumeC e m b) -> SubsumeC e m b #

generalBracket :: SubsumeC e m a -> (a -> ExitCase b -> SubsumeC e m c) -> (a -> SubsumeC e m b) -> SubsumeC e m (b, c) #

(Carrier m, Member e (Derivs m)) => Carrier (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

Associated Types

type Derivs (SubsumeC e m) :: [Effect] Source #

type Prims (SubsumeC e m) :: [Effect] Source #

type StT (SubsumeC e :: (Type -> Type) -> Type -> Type) a Source # 
Instance details

Defined in Control.Effect.Internal

type StT (SubsumeC e :: (Type -> Type) -> Type -> Type) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

type Derivs (SubsumeC e m) = e ': Derivs m
type Prims (SubsumeC e m) Source # 
Instance details

Defined in Control.Effect.Internal

type Prims (SubsumeC e m) = Prims m
type StM (SubsumeC e m) a Source # 
Instance details

Defined in Control.Effect.Internal

type StM (SubsumeC e m) a = StM m a