fused-effects-0.5.0.1: A fast, flexible, fused effect system.
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Carrier

Synopsis

Documentation

class HFunctor h where Source #

Higher-order functors of kind (* -> *) -> (* -> *) map functors to functors.

All effects must be HFunctors.

Minimal complete definition

Nothing

Methods

fmap' :: Functor (h f) => (a -> b) -> h f a -> h f b Source #

Deprecated: fmap' has been subsumed by fmap.

Apply a handler specified as a natural transformation to both higher-order and continuation positions within an HFunctor.

hmap :: Functor m => (forall x. m x -> n x) -> h m a -> h n a Source #

Higher-order functor map of a natural transformation over higher-order positions within the effect.

A definition for hmap over first-order effects can be derived automatically provided a Generic1 instance is available.

default hmap :: (Functor m, Generic1 (h m), Generic1 (h n), GHFunctor m n (Rep1 (h m)) (Rep1 (h n))) => (forall x. m x -> n x) -> h m a -> h n a Source #

Instances

Instances details
HFunctor Pure Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Pure f) => (a -> b) -> Pure f a -> Pure f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Pure m a -> Pure n a Source #

HFunctor Resource Source # 
Instance details

Defined in Control.Effect.Resource

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Resource f) => (a -> b) -> Resource f a -> Resource f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Resource m a -> Resource n a Source #

HFunctor Random Source # 
Instance details

Defined in Control.Effect.Random

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Random f) => (a -> b) -> Random f a -> Random f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Random m a -> Random n a Source #

HFunctor NonDet Source # 
Instance details

Defined in Control.Effect.NonDet

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (NonDet f) => (a -> b) -> NonDet f a -> NonDet f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> NonDet m a -> NonDet n a Source #

HFunctor Fresh Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Fresh f) => (a -> b) -> Fresh f a -> Fresh f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Fresh m a -> Fresh n a Source #

HFunctor Fail Source # 
Instance details

Defined in Control.Effect.Fail

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Fail f) => (a -> b) -> Fail f a -> Fail f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Fail m a -> Fail n a Source #

HFunctor Cut Source # 
Instance details

Defined in Control.Effect.Cut

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Cut f) => (a -> b) -> Cut f a -> Cut f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Cut m a -> Cut n a Source #

HFunctor Cull Source # 
Instance details

Defined in Control.Effect.Cull

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Cull f) => (a -> b) -> Cull f a -> Cull f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Cull m a -> Cull n a Source #

HFunctor Trace Source # 
Instance details

Defined in Control.Effect.Trace

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Trace f) => (a -> b) -> Trace f a -> Trace f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Trace m a -> Trace n a Source #

HFunctor (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (State s f) => (a -> b) -> State s f a -> State s f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> State s m a -> State s n a Source #

HFunctor (Reader r) Source # 
Instance details

Defined in Control.Effect.Reader

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Reader r f) => (a -> b) -> Reader r f a -> Reader r f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Reader r m a -> Reader r n a Source #

Functor sig => HFunctor (Lift sig) Source # 
Instance details

Defined in Control.Effect.Lift

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Lift sig f) => (a -> b) -> Lift sig f a -> Lift sig f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Lift sig m a -> Lift sig n a Source #

HFunctor (Error exc) Source # 
Instance details

Defined in Control.Effect.Error

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Error exc f) => (a -> b) -> Error exc f a -> Error exc f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Error exc m a -> Error exc n a Source #

HFunctor (Resumable err) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Resumable err f) => (a -> b) -> Resumable err f a -> Resumable err f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Resumable err m a -> Resumable err n a Source #

HFunctor (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

fmap' :: forall (f :: Type -> Type) a b. Functor (Writer w f) => (a -> b) -> Writer w f a -> Writer w f b Source #

hmap :: Functor m => (forall x. m x -> n x) -> Writer w m a -> Writer w n a Source #

(HFunctor f, HFunctor g) => HFunctor (f :+: g) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

fmap' :: forall (f0 :: Type -> Type) a b. Functor ((f :+: g) f0) => (a -> b) -> (f :+: g) f0 a -> (f :+: g) f0 b Source #

hmap :: Functor m => (forall x. m x -> n x) -> (f :+: g) m a -> (f :+: g) n a Source #

class HFunctor sig => Effect sig where Source #

The class of effect types, which must:

  1. Be functorial in their last two arguments, and
  2. Support threading effects in higher-order positions through using the carrier’s suspended state.

All first-order effects (those without existential occurrences of m) admit a default definition of handle provided a Generic1 instance is available for the effect.

Minimal complete definition

Nothing

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> sig m a -> sig n (f a) Source #

Handle any effects in a signature by threading the carrier’s state all the way through to the continuation.

default handle :: (Functor f, Monad m, Generic1 (sig m), Generic1 (sig n), GEffect m n (Rep1 (sig m)) (Rep1 (sig n))) => f () -> (forall x. f (m x) -> n (f x)) -> sig m a -> sig n (f a) Source #

Instances

Instances details
Effect Pure Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Pure m a -> Pure n (f a) Source #

Effect Resource Source # 
Instance details

Defined in Control.Effect.Resource

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Resource m a -> Resource n (f a) Source #

Effect Random Source # 
Instance details

Defined in Control.Effect.Random

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Random m a -> Random n (f a) Source #

Effect NonDet Source # 
Instance details

Defined in Control.Effect.NonDet

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> NonDet m a -> NonDet n (f a) Source #

Effect Fresh Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Fresh m a -> Fresh n (f a) Source #

Effect Fail Source # 
Instance details

Defined in Control.Effect.Fail

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Fail m a -> Fail n (f a) Source #

Effect Cut Source # 
Instance details

Defined in Control.Effect.Cut

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Cut m a -> Cut n (f a) Source #

Effect Cull Source # 
Instance details

Defined in Control.Effect.Cull

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Cull m a -> Cull n (f a) Source #

Effect Trace Source # 
Instance details

Defined in Control.Effect.Trace

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Trace m a -> Trace n (f a) Source #

Effect (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> State s m a -> State s n (f a) Source #

Effect (Reader r) Source # 
Instance details

Defined in Control.Effect.Reader

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Reader r m a -> Reader r n (f a) Source #

Functor sig => Effect (Lift sig) Source # 
Instance details

Defined in Control.Effect.Lift

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Lift sig m a -> Lift sig n (f a) Source #

Effect (Error exc) Source # 
Instance details

Defined in Control.Effect.Error

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Error exc m a -> Error exc n (f a) Source #

Effect (Resumable err) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Resumable err m a -> Resumable err n (f a) Source #

Effect (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

handle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> n (f x)) -> Writer w m a -> Writer w n (f a) Source #

(Effect f, Effect g) => Effect (f :+: g) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

handle :: (Functor f0, Monad m) => f0 () -> (forall x. f0 (m x) -> n (f0 x)) -> (f :+: g) m a -> (f :+: g) n (f0 a) Source #

class (HFunctor sig, Monad m) => Carrier sig m | m -> sig where Source #

The class of carriers (results) for algebras (effect handlers) over signatures (effects), whose actions are given by the eff method.

Methods

eff :: sig m a -> m a Source #

Construct a value in the carrier for an effect signature (typically a sum of a handled effect and any remaining effects).

Instances

Instances details
Carrier Pure PureC Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

eff :: Pure PureC a -> PureC a Source #

(HFunctor eff, Carrier sig m, Member eff sig) => Carrier sig (InterposeC eff m) Source # 
Instance details

Defined in Control.Effect.Interpose

Methods

eff :: sig (InterposeC eff m) a -> InterposeC eff m a Source #

Monad m => Carrier (Lift m) (LiftC m) Source # 
Instance details

Defined in Control.Effect.Lift

Methods

eff :: Lift m (LiftC m) a -> LiftC m a Source #

(Carrier sig m, MonadIO m) => Carrier (Resource :+: sig) (ResourceC m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

eff :: (Resource :+: sig) (ResourceC m) a -> ResourceC m a Source #

(Carrier sig m, Effect sig) => Carrier (NonDet :+: sig) (NonDetC m) Source # 
Instance details

Defined in Control.Effect.NonDet

Methods

eff :: (NonDet :+: sig) (NonDetC m) a -> NonDetC m a Source #

(Carrier sig m, Effect sig) => Carrier (NonDet :+: sig) (OnceC m) Source # 
Instance details

Defined in Control.Effect.Cull

Methods

eff :: (NonDet :+: sig) (OnceC m) a -> OnceC m a Source #

(Carrier sig m, Effect sig) => Carrier (Fresh :+: sig) (FreshC m) Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

eff :: (Fresh :+: sig) (FreshC m) a -> FreshC m a Source #

(Carrier sig m, Effect sig) => Carrier (Fail :+: sig) (FailC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

eff :: (Fail :+: sig) (FailC m) a -> FailC m a Source #

(Carrier sig m, Effect sig) => Carrier (Cut :+: (NonDet :+: sig)) (CutC m) Source # 
Instance details

Defined in Control.Effect.Cut

Methods

eff :: (Cut :+: (NonDet :+: sig)) (CutC m) a -> CutC m a Source #

(Carrier sig m, Effect sig) => Carrier (Cull :+: (NonDet :+: sig)) (CullC m) Source # 
Instance details

Defined in Control.Effect.Cull

Methods

eff :: (Cull :+: (NonDet :+: sig)) (CullC m) a -> CullC m a Source #

(Carrier sig m, Effect sig) => Carrier (Trace :+: sig) (TraceByReturningC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

eff :: (Trace :+: sig) (TraceByReturningC m) a -> TraceByReturningC m a Source #

Carrier sig m => Carrier (Trace :+: sig) (TraceByIgnoringC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

eff :: (Trace :+: sig) (TraceByIgnoringC m) a -> TraceByIgnoringC m a Source #

(MonadIO m, Carrier sig m) => Carrier (Trace :+: sig) (TraceByPrintingC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

eff :: (Trace :+: sig) (TraceByPrintingC m) a -> TraceByPrintingC m a Source #

(HFunctor eff, Carrier sig m) => Carrier (eff :+: sig) (InterpretC eff m) Source # 
Instance details

Defined in Control.Effect.Interpret

Methods

eff :: (eff :+: sig) (InterpretC eff m) a -> InterpretC eff m a Source #

(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Effect.State.Strict

Methods

eff :: (State s :+: sig) (StateC s m) a -> StateC s m a Source #

(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Effect.State.Lazy

Methods

eff :: (State s :+: sig) (StateC s m) a -> StateC s m a Source #

Carrier sig m => Carrier (Reader r :+: sig) (ReaderC r m) Source # 
Instance details

Defined in Control.Effect.Reader

Methods

eff :: (Reader r :+: sig) (ReaderC r m) a -> ReaderC r m a Source #

(Carrier sig m, Effect sig, RandomGen g) => Carrier (Random :+: sig) (RandomC g m) Source # 
Instance details

Defined in Control.Effect.Random

Methods

eff :: (Random :+: sig) (RandomC g m) a -> RandomC g m a Source #

(Carrier sig m, Effect sig) => Carrier (Error e :+: sig) (ErrorC e m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

eff :: (Error e :+: sig) (ErrorC e m) a -> ErrorC e m a Source #

Carrier sig m => Carrier (Resumable err :+: sig) (ResumableWithC err m) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

eff :: (Resumable err :+: sig) (ResumableWithC err m) a -> ResumableWithC err m a Source #

(Carrier sig m, Effect sig) => Carrier (Resumable err :+: sig) (ResumableC err m) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

eff :: (Resumable err :+: sig) (ResumableC err m) a -> ResumableC err m a Source #

(Monoid w, Carrier sig m, Effect sig) => Carrier (Writer w :+: sig) (WriterC w m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

eff :: (Writer w :+: sig) (WriterC w m) a -> WriterC w m a Source #

(HFunctor eff, Carrier sig m, Effect sig) => Carrier (eff :+: sig) (InterpretStateC eff s m) Source # 
Instance details

Defined in Control.Effect.Interpret

Methods

eff :: (eff :+: sig) (InterpretStateC eff s m) a -> InterpretStateC eff s m a Source #

send :: (Member effect sig, Carrier sig m) => effect m a -> m a Source #

Construct a request for an effect to be interpreted by some handler later on.

handlePure :: (HFunctor sig, Functor f) => (forall x. f x -> g x) -> sig f a -> sig g a Source #

Deprecated: handlePure has been subsumed by hmap.

Apply a handler specified as a natural transformation to both higher-order and continuation positions within an HFunctor.

handleCoercible :: (HFunctor sig, Functor f, Coercible f g) => sig f a -> sig g a Source #

Thread a Coercible carrier through an HFunctor.

This is applicable whenever f is Coercible to g, e.g. simple newtypes.

Generic deriving of HFunctor & Effect instances.

class GHFunctor m m' rep rep' where Source #

Generic implementation of HFunctor.

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> rep a -> rep' a Source #

Generic implementation of hmap.

Instances

Instances details
GHFunctor m m' Par1 Par1 Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> Par1 a -> Par1 a Source #

GHFunctor m m' (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> U1 a -> U1 a Source #

GHFunctor m m' (V1 :: Type -> Type) (V1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> V1 a -> V1 a Source #

HFunctor f => GHFunctor m m' (Rec1 (f m)) (Rec1 (f m')) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> Rec1 (f m) a -> Rec1 (f m') a Source #

GHFunctor m m' (Rec1 m) (Rec1 m') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> Rec1 m a -> Rec1 m' a Source #

GHFunctor m m' (K1 R c :: Type -> Type) (K1 R c :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> K1 R c a -> K1 R c a Source #

(GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :*: r) (l' :*: r') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (l :*: r) a -> (l' :*: r') a Source #

(GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :+: r) (l' :+: r') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (l :+: r) a -> (l' :+: r') a Source #

(Functor f, GHFunctor m m' g g') => GHFunctor m m' (f :.: g) (f :.: g') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (f :.: g) a -> (f :.: g') a Source #

GHFunctor m m' rep rep' => GHFunctor m m' (M1 i c rep) (M1 i c rep') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> M1 i c rep a -> M1 i c rep' a Source #

class GEffect m m' rep rep' where Source #

Generic implementation of Effect.

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> rep a -> rep' (f a) Source #

Generic implementation of handle.

Instances

Instances details
GEffect m m' Par1 Par1 Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> Par1 a -> Par1 (f a) Source #

GEffect m m' (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> U1 a -> U1 (f a) Source #

GEffect m m' (V1 :: Type -> Type) (V1 :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> V1 a -> V1 (f a) Source #

Effect f => GEffect m m' (Rec1 (f m)) (Rec1 (f m')) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f0, Monad m) => f0 () -> (forall x. f0 (m x) -> m' (f0 x)) -> Rec1 (f m) a -> Rec1 (f m') (f0 a) Source #

GEffect m m' (Rec1 m) (Rec1 m') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> Rec1 m a -> Rec1 m' (f a) Source #

GEffect m m' (K1 R c :: Type -> Type) (K1 R c :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> K1 R c a -> K1 R c (f a) Source #

(GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :*: r) (l' :*: r') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> (l :*: r) a -> (l' :*: r') (f a) Source #

(GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :+: r) (l' :+: r') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> (l :+: r) a -> (l' :+: r') (f a) Source #

(Functor f, GEffect m m' g g') => GEffect m m' (f :.: g) (f :.: g') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f0, Monad m) => f0 () -> (forall x. f0 (m x) -> m' (f0 x)) -> (f :.: g) a -> (f :.: g') (f0 a) Source #

GEffect m m' rep rep' => GEffect m m' (M1 i c rep) (M1 i c rep') Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> M1 i c rep a -> M1 i c rep' (f a) Source #

Re-exports

run :: PureC a -> a Source #

Run an action exhausted of effects to produce its final result value.

data (f :+: g) (m :: * -> *) k infixr 4 Source #

Constructors

L (f m k) 
R (g m k) 

Instances

Instances details
Member sub sup => Member sub (sub' :+: sup) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. sub m a -> (sub' :+: sup) m a Source #

prj :: forall (m :: Type -> Type) a. (sub' :+: sup) m a -> Maybe (sub m a) Source #

Member sub (sub :+: sup) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. sub m a -> (sub :+: sup) m a Source #

prj :: forall (m :: Type -> Type) a. (sub :+: sup) m a -> Maybe (sub m a) Source #

Generic1 ((f :+: g) m :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Sum

Associated Types

type Rep1 ((f :+: g) m) :: k -> Type #

Methods

from1 :: forall (a :: k). (f :+: g) m a -> Rep1 ((f :+: g) m) a #

to1 :: forall (a :: k). Rep1 ((f :+: g) m) a -> (f :+: g) m a #

(Effect f, Effect g) => Effect (f :+: g) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

handle :: (Functor f0, Monad m) => f0 () -> (forall x. f0 (m x) -> n (f0 x)) -> (f :+: g) m a -> (f :+: g) n (f0 a) Source #

(HFunctor f, HFunctor g) => HFunctor (f :+: g) Source # 
Instance details

Defined in Control.Effect.Carrier

Methods

fmap' :: forall (f0 :: Type -> Type) a b. Functor ((f :+: g) f0) => (a -> b) -> (f :+: g) f0 a -> (f :+: g) f0 b Source #

hmap :: Functor m => (forall x. m x -> n x) -> (f :+: g) m a -> (f :+: g) n a Source #

(Carrier sig m, MonadIO m) => Carrier (Resource :+: sig) (ResourceC m) Source # 
Instance details

Defined in Control.Effect.Resource

Methods

eff :: (Resource :+: sig) (ResourceC m) a -> ResourceC m a Source #

(Carrier sig m, Effect sig) => Carrier (NonDet :+: sig) (NonDetC m) Source # 
Instance details

Defined in Control.Effect.NonDet

Methods

eff :: (NonDet :+: sig) (NonDetC m) a -> NonDetC m a Source #

(Carrier sig m, Effect sig) => Carrier (NonDet :+: sig) (OnceC m) Source # 
Instance details

Defined in Control.Effect.Cull

Methods

eff :: (NonDet :+: sig) (OnceC m) a -> OnceC m a Source #

(Carrier sig m, Effect sig) => Carrier (Fresh :+: sig) (FreshC m) Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

eff :: (Fresh :+: sig) (FreshC m) a -> FreshC m a Source #

(Carrier sig m, Effect sig) => Carrier (Fail :+: sig) (FailC m) Source # 
Instance details

Defined in Control.Effect.Fail

Methods

eff :: (Fail :+: sig) (FailC m) a -> FailC m a Source #

(Carrier sig m, Effect sig) => Carrier (Cut :+: (NonDet :+: sig)) (CutC m) Source # 
Instance details

Defined in Control.Effect.Cut

Methods

eff :: (Cut :+: (NonDet :+: sig)) (CutC m) a -> CutC m a Source #

(Carrier sig m, Effect sig) => Carrier (Cull :+: (NonDet :+: sig)) (CullC m) Source # 
Instance details

Defined in Control.Effect.Cull

Methods

eff :: (Cull :+: (NonDet :+: sig)) (CullC m) a -> CullC m a Source #

(Carrier sig m, Effect sig) => Carrier (Trace :+: sig) (TraceByReturningC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

eff :: (Trace :+: sig) (TraceByReturningC m) a -> TraceByReturningC m a Source #

Carrier sig m => Carrier (Trace :+: sig) (TraceByIgnoringC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

eff :: (Trace :+: sig) (TraceByIgnoringC m) a -> TraceByIgnoringC m a Source #

(MonadIO m, Carrier sig m) => Carrier (Trace :+: sig) (TraceByPrintingC m) Source # 
Instance details

Defined in Control.Effect.Trace

Methods

eff :: (Trace :+: sig) (TraceByPrintingC m) a -> TraceByPrintingC m a Source #

(HFunctor eff, Carrier sig m) => Carrier (eff :+: sig) (InterpretC eff m) Source # 
Instance details

Defined in Control.Effect.Interpret

Methods

eff :: (eff :+: sig) (InterpretC eff m) a -> InterpretC eff m a Source #

(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Effect.State.Strict

Methods

eff :: (State s :+: sig) (StateC s m) a -> StateC s m a Source #

(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # 
Instance details

Defined in Control.Effect.State.Lazy

Methods

eff :: (State s :+: sig) (StateC s m) a -> StateC s m a Source #

Carrier sig m => Carrier (Reader r :+: sig) (ReaderC r m) Source # 
Instance details

Defined in Control.Effect.Reader

Methods

eff :: (Reader r :+: sig) (ReaderC r m) a -> ReaderC r m a Source #

(Carrier sig m, Effect sig, RandomGen g) => Carrier (Random :+: sig) (RandomC g m) Source # 
Instance details

Defined in Control.Effect.Random

Methods

eff :: (Random :+: sig) (RandomC g m) a -> RandomC g m a Source #

(Carrier sig m, Effect sig) => Carrier (Error e :+: sig) (ErrorC e m) Source # 
Instance details

Defined in Control.Effect.Error

Methods

eff :: (Error e :+: sig) (ErrorC e m) a -> ErrorC e m a Source #

Carrier sig m => Carrier (Resumable err :+: sig) (ResumableWithC err m) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

eff :: (Resumable err :+: sig) (ResumableWithC err m) a -> ResumableWithC err m a Source #

(Carrier sig m, Effect sig) => Carrier (Resumable err :+: sig) (ResumableC err m) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

eff :: (Resumable err :+: sig) (ResumableC err m) a -> ResumableC err m a Source #

(Monoid w, Carrier sig m, Effect sig) => Carrier (Writer w :+: sig) (WriterC w m) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

eff :: (Writer w :+: sig) (WriterC w m) a -> WriterC w m a Source #

(HFunctor eff, Carrier sig m, Effect sig) => Carrier (eff :+: sig) (InterpretStateC eff s m) Source # 
Instance details

Defined in Control.Effect.Interpret

Methods

eff :: (eff :+: sig) (InterpretStateC eff s m) a -> InterpretStateC eff s m a Source #

(Functor (f m), Functor (g m)) => Functor ((f :+: g) m) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

fmap :: (a -> b) -> (f :+: g) m a -> (f :+: g) m b #

(<$) :: a -> (f :+: g) m b -> (f :+: g) m a #

(Foldable (f m), Foldable (g m)) => Foldable ((f :+: g) m) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

fold :: Monoid m0 => (f :+: g) m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> (f :+: g) m a -> m0 #

foldMap' :: Monoid m0 => (a -> m0) -> (f :+: g) m a -> m0 #

foldr :: (a -> b -> b) -> b -> (f :+: g) m a -> b #

foldr' :: (a -> b -> b) -> b -> (f :+: g) m a -> b #

foldl :: (b -> a -> b) -> b -> (f :+: g) m a -> b #

foldl' :: (b -> a -> b) -> b -> (f :+: g) m a -> b #

foldr1 :: (a -> a -> a) -> (f :+: g) m a -> a #

foldl1 :: (a -> a -> a) -> (f :+: g) m a -> a #

toList :: (f :+: g) m a -> [a] #

null :: (f :+: g) m a -> Bool #

length :: (f :+: g) m a -> Int #

elem :: Eq a => a -> (f :+: g) m a -> Bool #

maximum :: Ord a => (f :+: g) m a -> a #

minimum :: Ord a => (f :+: g) m a -> a #

sum :: Num a => (f :+: g) m a -> a #

product :: Num a => (f :+: g) m a -> a #

(Traversable (f m), Traversable (g m)) => Traversable ((f :+: g) m) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) m a -> f0 ((f :+: g) m b) #

sequenceA :: Applicative f0 => (f :+: g) m (f0 a) -> f0 ((f :+: g) m a) #

mapM :: Monad m0 => (a -> m0 b) -> (f :+: g) m a -> m0 ((f :+: g) m b) #

sequence :: Monad m0 => (f :+: g) m (m0 a) -> m0 ((f :+: g) m a) #

(Eq (f m k), Eq (g m k)) => Eq ((f :+: g) m k) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

(==) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(/=) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(Ord (f m k), Ord (g m k)) => Ord ((f :+: g) m k) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

compare :: (f :+: g) m k -> (f :+: g) m k -> Ordering #

(<) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(<=) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(>) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

(>=) :: (f :+: g) m k -> (f :+: g) m k -> Bool #

max :: (f :+: g) m k -> (f :+: g) m k -> (f :+: g) m k #

min :: (f :+: g) m k -> (f :+: g) m k -> (f :+: g) m k #

(Show (f m k), Show (g m k)) => Show ((f :+: g) m k) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

showsPrec :: Int -> (f :+: g) m k -> ShowS #

show :: (f :+: g) m k -> String #

showList :: [(f :+: g) m k] -> ShowS #

type Rep1 ((f :+: g) m :: Type -> Type) Source # 
Instance details

Defined in Control.Effect.Sum

type Rep1 ((f :+: g) m :: Type -> Type) = D1 ('MetaData ":+:" "Control.Effect.Sum" "fused-effects-0.5.0.1-inplace" 'False) (C1 ('MetaCons "L" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (f m))) :+: C1 ('MetaCons "R" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (g m))))

class Member (sub :: (* -> *) -> * -> *) sup where Source #

Methods

inj :: sub m a -> sup m a Source #

prj :: sup m a -> Maybe (sub m a) Source #

Instances

Instances details
Member sub sub Source # 
Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. sub m a -> sub m a Source #

prj :: forall (m :: Type -> Type) a. sub m a -> Maybe (sub m a) Source #

Member sub sup => Member sub (sub' :+: sup) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. sub m a -> (sub' :+: sup) m a Source #

prj :: forall (m :: Type -> Type) a. (sub' :+: sup) m a -> Maybe (sub m a) Source #

Member sub (sub :+: sup) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

inj :: forall (m :: Type -> Type) a. sub m a -> (sub :+: sup) m a Source #

prj :: forall (m :: Type -> Type) a. (sub :+: sup) m a -> Maybe (sub m a) Source #