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

Control.Effect.Primitive

Synopsis

Primitive effects

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.

type Prims m :: [Effect] Source #

The primitive effects that m carries. These are higher-order effects whose handlers aren't expressed in terms of other effects, and thus need to be lifted on a carrier-by-carrier basis.

Never place membership constraints on Prims m. You should only gain access to effects by placing membership constraints on Derivs m.

However, running interpreters may place other kinds of constraints upon Prims m, namely threading constraints, marked by the use of Threaders. If you want to run such an effect interpreter inside application code, you have to propagate such threading constraints through your application.

Prims m should only contain higher-order effects that can't be lifted generically using lift. Any other effects can be placed in Derivs m.

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 #

Interpretation of primitive effects

type EffPrimHandler e m = forall x. e m x -> m x Source #

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

Unlike EffHandlers, EffPrimHandlers have direct access to m, making them significantly more powerful.

That said, you should interpret your own effects as primitives only as a last resort. Every primitive effect comes at the cost of enormous amounts of boilerplate: namely, the need for a ThreadsEff instance for every monad transformer that can thread that effect.

Some effects in this library are intended to be used as primitive effects, such as Regional. Try to use such effects to gain the power you need to interpret your effects instead of defining your own primitive effects, since the primitive effects offered in this library already have ThreadsEff instances defined for them.

interpretPrimSimple

interpretPrimSimple :: forall e m a p. (RepresentationalEff e, Threaders '[ReaderThreads] m p, ReaderThreads '[e], Carrier m) => EffPrimHandler e m -> InterpretPrimSimpleC e m a -> m a Source #

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

Only interpret your own effects as primitives as a last resort. See EffPrimHandler.

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

Note the ReaderThreads '[e] constraint, meaning you need to define a ThreadsEff e (ReaderT i) instance in order to use interpretPrimSimple.

interpretPrimViaHandler

interpretPrimViaHandler :: forall h e m a. PrimHandler h e m => InterpretPrimC h e m a -> m a Source #

Interpret an effect as a new primitive effect by using an explicit PrimHandler instance.

See PrimHandler for more information.

Only interpret your own effects as primitives as a last resort. See EffPrimHandler.

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

The class of effect handlers for primitive effects. Instances of this class can be used together interpretPrimViaHandler in order to interpret primitive 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 PrimHandler instance for it. Then, you can use your handler to interpret effects with interpretPrimViaHandler.

Alternatively, you can use interpretPrim or interpretPrimSimple, which lets you avoid the need to define instances of PrimHandler, but come at other costs.

Only interpret your own effects as primitives as a last resort. See EffPrimHandler.

Instances

Instances details
Carrier m => PrimHandler UnliftH (Unlift m) m Source # 
Instance details

Defined in Control.Effect.Internal.Unlift

(Carrier m, MonadBaseControl b m) => PrimHandler HoistToFinalH (Hoist b) m Source # 
Instance details

Defined in Control.Effect.Internal.Regional

Carrier m => PrimHandler HoistH (Hoist m) m Source # 
Instance details

Defined in Control.Effect.Internal.Regional

Carrier m => PrimHandler HoistOptionH (HoistOption m) m Source # 
Instance details

Defined in Control.Effect.Internal.Optional

(MonadCatch m, Carrier m) => PrimHandler ErrorIOFinalH (Optional ((->) SomeException :: Type -> Type)) m Source # 
Instance details

Defined in Control.Effect.Internal.ErrorIO

Carrier m => PrimHandler BaseControlH (BaseControl m) m Source # 
Instance details

Defined in Control.Effect.Internal.BaseControl

(Monoid w, Carrier m, Threaders '[SteppedThreads] m p) => PrimHandler ListenSteppedH (ListenPrim w) (SteppedC (Tell w) m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

(FirstOrder e, Carrier m, Threaders '[SteppedThreads] m p) => PrimHandler InterceptH (Unravel (InterceptB e)) (SteppedC e m) Source # 
Instance details

Defined in Control.Effect.Internal.Intercept

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

Defined in Control.Effect.Carrier.Internal.Interpret

interpretPrim

interpretPrim :: forall e m a. (RepresentationalEff e, Carrier m) => EffPrimHandler e m -> InterpretPrimReifiedC e m a -> m a Source #

Interpret an effect as a new primitive effect.

Only interpret your own effects as primitives as a last resort. See EffPrimHandler.

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

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

Consider using interpretPrimSimple instead if performance is secondary.

Threading primitive effects

class Threads t p where Source #

Threads t p is satisfied if ThreadsEff t e instances are defined for each effect e in p. By using the Threads t p constraint, you're able to lift Algebras over p from any monad m to t m. This is useful when defining custom Carrier instances.

Note that you should not place a Threads t p constraint if t is simply a newtype over an existsing monad transformer u that already has ThreadsEff instances defined for it. Instead, you should place a Threads u p constraint, and use its thread by coercing the resulting algebra from Algebra p (u m) to Algebra p (t m)'. That way, you avoid having to define redundant ThreadsEff instances for every newtype of a monad transformer.

Threads forms the basis of threading constraints (see Threaders), and every threading constraint offered in the library makes use of Threads in one way or another.

Methods

thread :: Monad m => Algebra p m -> Algebra p (t m) Source #

Instances

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

Defined in Control.Effect.Internal.Union

Methods

thread :: forall (m :: Type -> Type). Monad m => Algebra '[] m -> Algebra '[] (t m) Source #

(ThreadsEff t e, Threads t p) => Threads t (e ': p) Source # 
Instance details

Defined in Control.Effect.Internal.Union

Methods

thread :: forall (m :: Type -> Type). Monad m => Algebra (e ': p) m -> Algebra (e ': p) (t m) Source #

class RepresentationalEff e => ThreadsEff t e where Source #

An instance of ThreadsEff represents the ability for a monad transformer t to thread a primitive effect e -- i.e. lift handlers of that effect.

Instances of ThreadsEff are accumulated into entire stacks of primitive effects by Threads.

You only need to make ThreadsEff instances for monad transformers that aren't simply newtypes over existing monad transformers. You also don't need to make them for IdentityT.

Methods

threadEff :: Monad m => (forall x. e m x -> m x) -> e (t m) a -> t m a Source #

Instances

Instances details
Monoid s => ThreadsEff ListT (ListenPrim s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. ListenPrim s m x -> m x) -> ListenPrim s (ListT m) a -> ListT m a Source #

ThreadsEff ListT (Regional s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (ListT m) a -> ListT m a Source #

ThreadsEff ListT (ReaderPrim i) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. ReaderPrim i m x -> m x) -> ReaderPrim i (ListT m) a -> ListT m a Source #

Functor s => ThreadsEff ListT (Optional s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ListT m) a -> ListT m a Source #

ThreadsEff ListT (Unravel p) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Unravel p m x -> m x) -> Unravel p (ListT m) a -> ListT m a Source #

Monoid s => ThreadsEff ListT (WriterPrim s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. WriterPrim s m x -> m x) -> WriterPrim s (ListT m) a -> ListT m a Source #

ThreadsEff (ExceptT e) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (ExceptT e m) a -> ExceptT e m a Source #

ThreadsEff (ExceptT e) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (ExceptT e m) a -> ExceptT e m a Source #

ThreadsEff (ExceptT e) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (ExceptT e m) a -> ExceptT e m a Source #

Monoid s => ThreadsEff (WriterT s) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Split Source # 
Instance details

Defined in Control.Effect.Type.Split

Methods

threadEff :: Monad m => (forall x. Split m x -> m x) -> Split (WriterT s m) a -> WriterT s m a Source #

ThreadsEff (StateT s) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT s) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT s) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT s) Split Source # 
Instance details

Defined in Control.Effect.Type.Split

Methods

threadEff :: Monad m => (forall x. Split m x -> m x) -> Split (StateT s m) a -> StateT s m a Source #

ThreadsEff (ReaderT i) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT s) Split Source # 
Instance details

Defined in Control.Effect.Type.Split

Methods

threadEff :: Monad m => (forall x. Split m x -> m x) -> Split (ReaderT s m) a -> ReaderT s m a Source #

ThreadsEff (StateT s) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT s) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT s) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT s) Split Source # 
Instance details

Defined in Control.Effect.Type.Split

Methods

threadEff :: Monad m => (forall x. Split m x -> m x) -> Split (StateT s m) a -> StateT s m a Source #

Monoid s => ThreadsEff (WriterT s) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Split Source # 
Instance details

Defined in Control.Effect.Type.Split

Methods

threadEff :: Monad m => (forall x. Split m x -> m x) -> Split (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Bracket Source # 
Instance details

Defined in Control.Effect.Type.Bracket

Methods

threadEff :: Monad m => (forall x. Bracket m x -> m x) -> Bracket (WriterT s m) a -> WriterT s m a Source #

ThreadsEff (WriterT s) Fix Source # 
Instance details

Defined in Control.Effect.Type.Fix

Methods

threadEff :: Monad m => (forall x. Fix m x -> m x) -> Fix (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Mask Source # 
Instance details

Defined in Control.Effect.Type.Mask

Methods

threadEff :: Monad m => (forall x. Mask m x -> m x) -> Mask (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) Split Source # 
Instance details

Defined in Control.Effect.Type.Split

Methods

threadEff :: Monad m => (forall x. Split m x -> m x) -> Split (WriterT s m) a -> WriterT s m a Source #

Monoid threadedMonoid => ThreadsEff (ExceptT e) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (ExceptT e m) a -> ExceptT e m a Source #

ThreadsEff (ExceptT e) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (ExceptT e m) a -> ExceptT e m a Source #

ThreadsEff (ExceptT e) (ReaderPrim threadedInput) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim threadedInput m x -> m x) -> ReaderPrim threadedInput (ExceptT e m) a -> ExceptT e m a Source #

Functor s => ThreadsEff (ExceptT e) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ExceptT e m) a -> ExceptT e m a Source #

ThreadsEff (ExceptT e) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (ExceptT e m) a -> ExceptT e m a Source #

ThreadsEff (ExceptT e) (Unravel p) Source # 
Instance details

Defined in Control.Effect.Type.Unravel

Methods

threadEff :: Monad m => (forall x. Unravel p m x -> m x) -> Unravel p (ExceptT e m) a -> ExceptT e m a Source #

Monoid threadedMonoid => ThreadsEff (ExceptT e) (WriterPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim threadedMonoid m x -> m x) -> WriterPrim threadedMonoid (ExceptT e m) a -> ExceptT e m a Source #

Monoid s => ThreadsEff (WriterT s) (ListenPrim o) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (WriterT s m) a -> WriterT s m a Source #

ThreadsEff (WriterT w) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (WriterT w m) a -> WriterT w m a Source #

Monoid w => ThreadsEff (WriterT w) (ReaderPrim threadedInput) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim threadedInput m x -> m x) -> ReaderPrim threadedInput (WriterT w m) a -> WriterT w m a Source #

(Functor s, Monoid w) => ThreadsEff (WriterT w) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (WriterT w m) a -> WriterT w m a Source #

Monoid w => ThreadsEff (WriterT w) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (WriterT w m) a -> WriterT w m a Source #

Monoid s => ThreadsEff (WriterT s) (WriterPrim o) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim o m x -> m x) -> WriterPrim o (WriterT s m) a -> WriterT s m a Source #

Monoid threadedMonoid => ThreadsEff (StateT s) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT i) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (StateT i m) a -> StateT i m a Source #

ThreadsEff (StateT s) (ReaderPrim threadedInput) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim threadedInput m x -> m x) -> ReaderPrim threadedInput (StateT s m) a -> StateT s m a Source #

Functor s => ThreadsEff (StateT s') (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (StateT s' m) a -> StateT s' m a Source #

ThreadsEff (StateT s) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (StateT s m) a -> StateT s m a Source #

Monoid threadedMonoid => ThreadsEff (StateT s) (WriterPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim threadedMonoid m x -> m x) -> WriterPrim threadedMonoid (StateT s m) a -> StateT s m a Source #

Monoid threadedMonoid => ThreadsEff (ReaderT i) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i') (ReaderPrim i) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim i m x -> m x) -> ReaderPrim i (ReaderT i' m) a -> ReaderT i' m a Source #

ThreadsEff (ReaderT i) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i) (Unlift b) Source # 
Instance details

Defined in Control.Effect.Type.Unlift

Methods

threadEff :: Monad m => (forall x. Unlift b m x -> m x) -> Unlift b (ReaderT i m) a -> ReaderT i m a Source #

ThreadsEff (ReaderT i) (Unravel p) Source # 
Instance details

Defined in Control.Effect.Type.Unravel

Methods

threadEff :: Monad m => (forall x. Unravel p m x -> m x) -> Unravel p (ReaderT i m) a -> ReaderT i m a Source #

Monoid threadedMonoid => ThreadsEff (ReaderT i) (WriterPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim threadedMonoid m x -> m x) -> WriterPrim threadedMonoid (ReaderT i m) a -> ReaderT i m a Source #

Monoid threadedMonoid => ThreadsEff (StateT s) (ListenPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim threadedMonoid m x -> m x) -> ListenPrim threadedMonoid (StateT s m) a -> StateT s m a Source #

ThreadsEff (StateT i) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (StateT i m) a -> StateT i m a Source #

ThreadsEff (StateT s) (ReaderPrim threadedInput) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim threadedInput m x -> m x) -> ReaderPrim threadedInput (StateT s m) a -> StateT s m a Source #

Functor s => ThreadsEff (StateT s') (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (StateT s' m) a -> StateT s' m a Source #

ThreadsEff (StateT s) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (StateT s m) a -> StateT s m a Source #

Monoid threadedMonoid => ThreadsEff (StateT s) (WriterPrim threadedMonoid) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim threadedMonoid m x -> m x) -> WriterPrim threadedMonoid (StateT s m) a -> StateT s m a Source #

Monoid s => ThreadsEff (WriterT s) (ListenPrim o) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (WriterT s m) a -> WriterT s m a Source #

ThreadsEff (WriterT w) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (WriterT w m) a -> WriterT w m a Source #

Monoid w => ThreadsEff (WriterT w) (ReaderPrim threadedInput) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim threadedInput m x -> m x) -> ReaderPrim threadedInput (WriterT w m) a -> WriterT w m a Source #

(Functor s, Monoid w) => ThreadsEff (WriterT w) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (WriterT w m) a -> WriterT w m a Source #

Monoid w => ThreadsEff (WriterT w) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (WriterT w m) a -> WriterT w m a Source #

Monoid s => ThreadsEff (WriterT s) (WriterPrim o) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim o m x -> m x) -> WriterPrim o (WriterT s m) a -> WriterT s m a Source #

Monoid s => ThreadsEff (WriterT s) (ListenPrim o) Source # 
Instance details

Defined in Control.Effect.Type.ListenPrim

Methods

threadEff :: Monad m => (forall x. ListenPrim o m x -> m x) -> ListenPrim o (WriterT s m) a -> WriterT s m a Source #

Monoid w => ThreadsEff (WriterT w) (Regional s) Source # 
Instance details

Defined in Control.Effect.Type.Regional

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (WriterT w m) a -> WriterT w m a Source #

Monoid w => ThreadsEff (WriterT w) (ReaderPrim i) Source # 
Instance details

Defined in Control.Effect.Type.ReaderPrim

Methods

threadEff :: Monad m => (forall x. ReaderPrim i m x -> m x) -> ReaderPrim i (WriterT w m) a -> WriterT w m a Source #

(Functor s, Monoid w) => ThreadsEff (WriterT w) (Optional s) Source # 
Instance details

Defined in Control.Effect.Type.Optional

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (WriterT w m) a -> WriterT w m a Source #

Monoid w => ThreadsEff (WriterT w) (BaseControl b) Source # 
Instance details

Defined in Control.Effect.Type.Internal.BaseControl

Methods

threadEff :: Monad m => (forall x. BaseControl b m x -> m x) -> BaseControl b (WriterT w m) a -> WriterT w m a Source #

Monoid s => ThreadsEff (WriterT s) (WriterPrim o) Source # 
Instance details

Defined in Control.Effect.Type.WriterPrim

Methods

threadEff :: Monad m => (forall x. WriterPrim o m x -> m x) -> WriterPrim o (WriterT s m) a -> WriterT s m a Source #

ThreadsEff (FreeT f) (ReaderPrim i) Source # 
Instance details

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

Methods

threadEff :: Monad m => (forall x. ReaderPrim i m x -> m x) -> ReaderPrim i (FreeT f m) a -> FreeT f m a Source #

ThreadsEff (FreeT f) (Unravel p) Source # 
Instance details

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

Methods

threadEff :: Monad m => (forall x. Unravel p m x -> m x) -> Unravel p (FreeT f m) a -> FreeT f m a Source #

Functor s => ThreadsEff (FreeT f) (Optional s) Source # 
Instance details

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

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (FreeT f m) a -> FreeT f m a Source #

ThreadsEff (FreeT f) (Regional s) Source # 
Instance details

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

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (FreeT f m) a -> FreeT f m a Source #

Monoid w => ThreadsEff (FreeT f) (ListenPrim w) Source # 
Instance details

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

Methods

threadEff :: Monad m => (forall x. ListenPrim w m x -> m x) -> ListenPrim w (FreeT f m) a -> FreeT f m a Source #

Carriers

data InterpretPrimSimpleC (e :: Effect) (m :: * -> *) a Source #

Instances

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

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

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

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StM (InterpretPrimSimpleC e 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 #

Monad m => Monad (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Functor m => Functor (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fmap :: (a -> b) -> InterpretPrimSimpleC e m a -> InterpretPrimSimpleC e m b #

(<$) :: a -> InterpretPrimSimpleC e m b -> InterpretPrimSimpleC e m a #

MonadFix m => MonadFix (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mfix :: (a -> InterpretPrimSimpleC e m a) -> InterpretPrimSimpleC e m a #

MonadFail m => MonadFail (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fail :: String -> InterpretPrimSimpleC e m a #

Applicative m => Applicative (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

MonadIO m => MonadIO (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

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

Alternative m => Alternative (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

MonadPlus m => MonadPlus (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

MonadThrow m => MonadThrow (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

throwM :: Exception e0 => e0 -> InterpretPrimSimpleC e m a #

MonadCatch m => MonadCatch (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

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

MonadMask m => MonadMask (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

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

type Derivs (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Derivs (InterpretPrimSimpleC e m) = e ': Derivs m
type Prims (InterpretPrimSimpleC e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Prims (InterpretPrimSimpleC e m) = e ': Prims m
type StM (InterpretPrimSimpleC e m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

data InterpretPrimC (s :: *) (e :: Effect) (m :: * -> *) a Source #

Instances

Instances details
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 α #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StM (InterpretPrimC s e m) a #

Methods

liftBaseWith :: (RunInBase (InterpretPrimC s e m) b -> b a) -> InterpretPrimC s e m a #

restoreM :: StM (InterpretPrimC s e m) a -> InterpretPrimC s 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 #

MonadTransControl (InterpretPrimC s e) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

Associated Types

type StT (InterpretPrimC s e) a #

Methods

liftWith :: Monad m => (Run (InterpretPrimC s e) -> m a) -> InterpretPrimC s e m a #

restoreT :: Monad m => m (StT (InterpretPrimC s e) a) -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

(>>=) :: InterpretPrimC s e m a -> (a -> InterpretPrimC s e m b) -> InterpretPrimC s e m b #

(>>) :: InterpretPrimC s e m a -> InterpretPrimC s e m b -> InterpretPrimC s e m b #

return :: a -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fmap :: (a -> b) -> InterpretPrimC s e m a -> InterpretPrimC s e m b #

(<$) :: a -> InterpretPrimC s e m b -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mfix :: (a -> InterpretPrimC s e m a) -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

fail :: String -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

pure :: a -> InterpretPrimC s e m a #

(<*>) :: InterpretPrimC s e m (a -> b) -> InterpretPrimC s e m a -> InterpretPrimC s e m b #

liftA2 :: (a -> b -> c) -> InterpretPrimC s e m a -> InterpretPrimC s e m b -> InterpretPrimC s e m c #

(*>) :: InterpretPrimC s e m a -> InterpretPrimC s e m b -> InterpretPrimC s e m b #

(<*) :: InterpretPrimC s e m a -> InterpretPrimC s e m b -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

liftIO :: IO a -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

empty :: InterpretPrimC s e m a #

(<|>) :: InterpretPrimC s e m a -> InterpretPrimC s e m a -> InterpretPrimC s e m a #

some :: InterpretPrimC s e m a -> InterpretPrimC s e m [a] #

many :: InterpretPrimC s e m a -> InterpretPrimC s e m [a] #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mzero :: InterpretPrimC s e m a #

mplus :: InterpretPrimC s e m a -> InterpretPrimC s e m a -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

throwM :: Exception e0 => e0 -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

catch :: Exception e0 => InterpretPrimC s e m a -> (e0 -> InterpretPrimC s e m a) -> InterpretPrimC s e m a #

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

Defined in Control.Effect.Carrier.Internal.Interpret

Methods

mask :: ((forall a. InterpretPrimC s e m a -> InterpretPrimC s e m a) -> InterpretPrimC s e m b) -> InterpretPrimC s e m b #

uninterruptibleMask :: ((forall a. InterpretPrimC s e m a -> InterpretPrimC s e m a) -> InterpretPrimC s e m b) -> InterpretPrimC s e m b #

generalBracket :: InterpretPrimC s e m a -> (a -> ExitCase b -> InterpretPrimC s e m c) -> (a -> InterpretPrimC s e m b) -> InterpretPrimC s e m (b, c) #

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 #

type StT (InterpretPrimC s e) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StT (InterpretPrimC s e) a = StT (IdentityT :: (Type -> Type) -> Type -> Type) a
type Derivs (InterpretPrimC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Derivs (InterpretPrimC h e m) = e ': Derivs m
type Prims (InterpretPrimC h e m) Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type Prims (InterpretPrimC h e m) = e ': Prims m
type StM (InterpretPrimC s e m) a Source # 
Instance details

Defined in Control.Effect.Carrier.Internal.Interpret

type StM (InterpretPrimC s e m) a = StM m a