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

Control.Effect.Internal

Synopsis

Documentation

class Monad m => Carrier m where 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.

Methods

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

An m-based Algebra (i.e effect handler) over the union of the primitive effects: effects that aren't formulated in terms of other effects. See Prims.

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

Any Carrier m must provide a way to describe the derived effects it carries in terms of the primitive effects.

reformulate is that decription: given any monad z such that z lifts m, then a z-based Algebra (i.e. effect handler) over the derived effects can be created out of a z-based Algebra over the primitive effects.

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

An m-based algebra (i.e. effect handler) over the union of derived effects (see Derivs m).

This is what send makes use of.

algDerivs is subject to the law:

algDerivs = reformulate id algPrims

which serves as the default implementation.

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 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.

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)

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)

type family SatisfiesAll (q :: k) cs :: Constraint where ... Source #

Equations

SatisfiesAll q '[] = () 
SatisfiesAll q (c ': cs) = (c q, SatisfiesAll q cs) 

type RunC = Identity Source #

The identity carrier, which carries no effects at all.

run :: RunC a -> a Source #

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

newtype SubsumeC (e :: Effect) m a Source #

Constructors

SubsumeC 

Fields

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

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