fused-effects-0.3.0.0: A fast, flexible, fused effect system.

Safe HaskellNone
LanguageHaskell2010

Control.Effect.Carrier

Synopsis

Documentation

class HFunctor h where Source #

Minimal complete definition

hmap

Methods

fmap' :: (a -> b) -> h m a -> h m b Source #

Functor map. This is required to be fmap.

This can go away once we have quantified constraints.

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

Functor map. This is required to be fmap.

This can go away once we have quantified constraints.

hmap :: (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.

Instances
HFunctor Pure Source # 
Instance details

Defined in Control.Effect.Pure

Methods

fmap' :: (a -> b) -> Pure m a -> Pure m b Source #

hmap :: (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' :: (a -> b) -> Resource m a -> Resource m b Source #

hmap :: (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' :: (a -> b) -> Random m a -> Random m b Source #

hmap :: (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' :: (a -> b) -> NonDet m a -> NonDet m b Source #

hmap :: (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' :: (a -> b) -> Fresh m a -> Fresh m b Source #

hmap :: (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' :: (a -> b) -> Fail m a -> Fail m b Source #

hmap :: (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' :: (a -> b) -> Cut m a -> Cut m b Source #

hmap :: (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' :: (a -> b) -> Cull m a -> Cull m b Source #

hmap :: (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' :: (a -> b) -> Trace m a -> Trace m b Source #

hmap :: (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' :: (a -> b) -> State s m a -> State s m b Source #

hmap :: (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' :: (a -> b) -> Reader r m a -> Reader r m b Source #

hmap :: (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' :: (a -> b) -> Lift sig m a -> Lift sig m b Source #

hmap :: (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' :: (a -> b) -> Error exc m a -> Error exc m b Source #

hmap :: (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' :: (a -> b) -> Resumable err m a -> Resumable err m b Source #

hmap :: (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' :: (a -> b) -> Writer w m a -> Writer w m b Source #

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

(HFunctor l, HFunctor r) => HFunctor (l :+: r) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

fmap' :: (a -> b) -> (l :+: r) m a -> (l :+: r) m b Source #

hmap :: (forall x. m x -> n x) -> (l :+: r) m a -> (l :+: r) 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.

Methods

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

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

Instances
Effect Pure Source # 
Instance details

Defined in Control.Effect.Pure

Methods

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

Effect Resource Source # 
Instance details

Defined in Control.Effect.Resource

Methods

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

Effect Random Source # 
Instance details

Defined in Control.Effect.Random

Methods

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

Effect NonDet Source # 
Instance details

Defined in Control.Effect.NonDet

Methods

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

Effect Fresh Source # 
Instance details

Defined in Control.Effect.Fresh

Methods

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

Effect Fail Source # 
Instance details

Defined in Control.Effect.Fail

Methods

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

Effect Cut Source # 
Instance details

Defined in Control.Effect.Cut

Methods

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

Effect Cull Source # 
Instance details

Defined in Control.Effect.Cull

Methods

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

Effect Trace Source # 
Instance details

Defined in Control.Effect.Trace

Methods

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

Effect (State s) Source # 
Instance details

Defined in Control.Effect.State.Internal

Methods

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

Effect (Reader r) Source # 
Instance details

Defined in Control.Effect.Reader

Methods

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

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

Defined in Control.Effect.Lift

Methods

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

Effect (Error exc) Source # 
Instance details

Defined in Control.Effect.Error

Methods

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

Effect (Resumable err) Source # 
Instance details

Defined in Control.Effect.Resumable

Methods

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

Effect (Writer w) Source # 
Instance details

Defined in Control.Effect.Writer

Methods

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

(Effect l, Effect r) => Effect (l :+: r) Source # 
Instance details

Defined in Control.Effect.Sum

Methods

handle :: Functor f => f () -> (forall x. f (m x) -> n (f x)) -> (l :+: r) m (m a) -> (l :+: r) n (n (f 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.

Minimal complete definition

eff

Methods

eff :: sig m (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).

ret :: a -> m a Source #

Deprecated: Use pure instead; ret is a historical alias and will be removed in future versions

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

Instances
Carrier Pure PureC Source # 
Instance details

Defined in Control.Effect.Pure

Methods

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

ret :: a -> PureC a Source #

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

Defined in Control.Effect.Lift

Methods

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

ret :: 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) (ResourceC m a) -> ResourceC m a Source #

ret :: 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) (NonDetC m a) -> NonDetC m a Source #

ret :: 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) (OnceC m a) -> OnceC m a Source #

ret :: 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) (FreshC m a) -> FreshC m a Source #

ret :: 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) (FailC m a) -> FailC m a Source #

ret :: 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) (CutC m a) -> CutC m a Source #

ret :: 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) (CullC m a) -> CullC m a Source #

ret :: a -> CullC m a Source #

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

Defined in Control.Effect.Trace

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

Defined in Control.Effect.Trace

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

Defined in Control.Effect.Trace

(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) (StateC s m a) -> StateC s m a Source #

ret :: 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) (StateC s m a) -> StateC s m a Source #

ret :: 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) (ReaderC r m a) -> ReaderC r m a Source #

ret :: 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) (RandomC g m a) -> RandomC g m a Source #

ret :: 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) (ErrorC e m a) -> ErrorC e m a Source #

ret :: 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) (ResumableWithC err m a) -> ResumableWithC err m a Source #

ret :: 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) (ResumableC err m a) -> ResumableC err m a Source #

ret :: 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) (WriterC w m a) -> WriterC w m a Source #

ret :: a -> WriterC w m a Source #

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

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

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

Thread a Coercible carrier through an HFunctor.

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

handleReader :: HFunctor sig => r -> (forall x. f x -> r -> g x) -> sig f (f a) -> sig g (g a) Source #

Deprecated: Compose carrier types from other carriers and define eff with handleCoercible instead

Thread a Reader-like carrier through an HFunctor.

handleState :: Effect sig => s -> (forall x. f x -> s -> g (s, x)) -> sig f (f a) -> sig g (g (s, a)) Source #

Deprecated: Compose carrier types from other carriers and define eff with handleCoercible instead

Thread a State-like carrier through an Effect.

handleEither :: (Carrier sig g, Effect sig) => (forall x. f x -> g (Either e x)) -> sig f (f a) -> sig g (g (Either e a)) Source #

Deprecated: Compose carrier types from other carriers and define eff with handleCoercible instead

Thread a carrier producing Eithers through an Effect.

handleTraversable :: (Effect sig, Applicative g, Monad m, Traversable m) => (forall x. f x -> g (m x)) -> sig f (f a) -> sig g (g (m a)) Source #

Deprecated: Compose carrier types from other carriers and define eff with handleCoercible instead

Thread a carrier producing values in a Traversable Monad (e.g. '[]') through an Effect.

interpret :: carrier a -> carrier a Source #

Deprecated: Not necessary with monadic carriers; remove or replace with id.

A backwards-compatibility shim, equivalent to id.