| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Effect.Carrier
Synopsis
- class HFunctor h where
- class HFunctor sig => Effect sig where
- class HFunctor sig => Carrier sig h | h -> sig where
- handlePure :: HFunctor sig => (forall x. f x -> g x) -> sig f (f a) -> sig g (g a)
- handleCoercible :: (HFunctor sig, Coercible f g) => sig f (f a) -> sig g (g a)
- handleReader :: HFunctor sig => r -> (forall x. f x -> r -> g x) -> sig f (f a) -> sig g (g a)
- handleState :: Effect sig => s -> (forall x. f x -> s -> g (s, x)) -> sig f (f a) -> sig g (g (s, a))
- handleEither :: (Carrier sig g, Effect sig) => (forall x. f x -> g (Either e x)) -> sig f (f a) -> sig g (g (Either e a))
- 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))
Documentation
class HFunctor h where Source #
Minimal complete definition
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 Fail Source # | |
| HFunctor NonDet Source # | |
| HFunctor Random Source # | |
| HFunctor Resource Source # | |
| HFunctor Fresh Source # | |
| HFunctor Cull Source # | |
| HFunctor Cut Source # | |
| HFunctor Trace Source # | |
| HFunctor Void Source # | |
| Functor sig => HFunctor (Lift sig) Source # | |
| HFunctor (State s) Source # | |
| HFunctor (Resumable err) Source # | |
| HFunctor (Reader r) Source # | |
| HFunctor (Error exc) Source # | |
| HFunctor (Writer w) Source # | |
| (HFunctor l, HFunctor r) => HFunctor (l :+: r) Source # | |
class HFunctor sig => Effect sig where Source #
The class of effect types, which must:
- Be functorial in their last two arguments, and
- Support threading effects in higher-order positions through using the carrier’s suspended state.
Minimal complete definition
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 Fail Source # | |
| Effect NonDet Source # | |
| Effect Random Source # | |
| Effect Resource Source # | |
| Effect Fresh Source # | |
| Effect Cull Source # | |
| Effect Cut Source # | |
| Effect Trace Source # | |
| Effect Void Source # | |
| Functor sig => Effect (Lift sig) Source # | |
| Effect (State s) Source # | |
| Effect (Resumable err) Source # | |
| Effect (Reader r) Source # | |
| Effect (Error exc) Source # | |
| Effect (Writer w) Source # | |
| (Effect l, Effect r) => Effect (l :+: r) Source # | |
class HFunctor sig => Carrier sig h | h -> sig where Source #
The class of carriers (results) for algebras (effect handlers) over signatures (effects), whose actions are given by the ret and eff methods.
Methods
Wrap a return value.
eff :: sig h (h a) -> h a Source #
Construct a value in the carrier for an effect signature (typically a sum of a handled effect and any remaining effects).
Instances
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 #
handleReader :: HFunctor sig => r -> (forall x. f x -> r -> g x) -> sig f (f a) -> sig g (g a) Source #
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 #
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 #
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 #
Thread a carrier producing values in a Traversable Monad (e.g. '[]') through an Effect.