| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Effect.Lift
Contents
Description
Synopsis
- data Lift sig m k = forall a. LiftWith (forall ctx. Functor ctx => ctx () -> (forall a. ctx (m a) -> sig (ctx a)) -> sig (ctx a)) (a -> m k)
- sendM :: (Has (Lift n) sig m, Functor n) => n a -> m a
- sendIO :: Has (Lift IO) sig m => IO a -> m a
- liftWith :: Has (Lift n) sig m => (forall ctx. Functor ctx => ctx () -> (forall a. ctx (m a) -> n (ctx a)) -> n (ctx a)) -> m a
- class (HFunctor sig, Monad m) => Algebra sig m | m -> sig
- class HFunctor sig => Effect sig
- type Has eff sig m = (Members eff sig, Algebra sig m)
- run :: Identity a -> a
Lift effect
Since: 1.0.0.0
Constructors
| forall a. LiftWith (forall ctx. Functor ctx => ctx () -> (forall a. ctx (m a) -> sig (ctx a)) -> sig (ctx a)) (a -> m k) |
sendM :: (Has (Lift n) sig m, Functor n) => n a -> m a Source #
Given a Lift n constraint in a signature carried by m, sendM
promotes arbitrary actions of type n a to m a. It is spiritually
similar to lift from the MonadTrans typeclass.
Since: 1.0.0.0
sendIO :: Has (Lift IO) sig m => IO a -> m a Source #
A type-restricted variant of sendM for IO actions.
This is particularly useful when you have a constraint for the use of Has (Lift IO) sig mliftWith, and want to run an action abstracted over MonadIO. IO has a MonadIO instance, and sendIO’s type restricts the action’s type to IO without further type annotations.
Since: 1.0.2.0
liftWith :: Has (Lift n) sig m => (forall ctx. Functor ctx => ctx () -> (forall a. ctx (m a) -> n (ctx a)) -> n (ctx a)) -> m a Source #
Run actions in an outer context.
This can be used to provide interoperation with base functionality like Control.Exception.:catch
liftWith$ \ ctx hdl ->catch(hdl (m <$ ctx)) (hdl . (<$ ctx) . h)
The higher-order function takes both an initial context, and a handler phrased as the same sort of distributive law as described in the documentation for thread. This handler takes actions lifted into a context functor, which can be either the initial context, or the derived context produced by handling a previous action.
As with MonadBaseControl, care must be taken when lifting functions like Control.Exception. which don’t use the return value of one of their actions, as this can lead to dropped effects.finally
Since: 1.0.0.0
Re-exports
class (HFunctor sig, Monad m) => Algebra sig m | m -> sig Source #
The class of carriers (results) for algebras (effect handlers) over signatures (effects), whose actions are given by the alg method.
Since: 1.0.0.0
Minimal complete definition
Instances
| Algebra Choose NonEmpty Source # | |
| Algebra Empty Maybe Source # | |
| Algebra NonDet [] Source # | |
Defined in Control.Algebra | |
| Algebra sig m => Algebra sig (Alt m) Source # | This instance permits effectful actions to be lifted into the a <|> b <|> c <|> d is equivalent to getAlt (mconcat [a, b, c, d]) Since: 1.0.1.0 |
| Algebra sig m => Algebra sig (Ap m) Source # | This instance permits effectful actions to be lifted into the mappend <$> act1 <*> (mappend <$> act2 <*> act3) is equivalent to getAp (act1 <> act2 <> act3) Since: 1.0.1.0 |
| Algebra sig m => Algebra sig (IdentityT m) Source # | |
| Algebra (Lift IO) IO Source # | |
| Algebra (Lift Identity) Identity Source # | |
| Monad m => Algebra (Lift m) (LiftC m) Source # | |
| Algebra (Error e) (Either e) Source # | |
| Monoid w => Algebra (Writer w) ((,) w) Source # | |
| Algebra (Reader r) ((->) r :: Type -> Type) Source # | |
Defined in Control.Algebra | |
| (Algebra sig m, Effect sig) => Algebra (Choose :+: sig) (ChooseC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Empty :+: sig) (EmptyC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (NonDet :+: sig) (NonDetC m) Source # | |
| (MonadIO m, Algebra sig m) => Algebra (Trace :+: sig) (TraceC m) Source # | |
| Algebra sig m => Algebra (Trace :+: sig) (TraceC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Trace :+: sig) (TraceC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Fail :+: sig) (FailC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Fresh :+: sig) (FreshC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Cut :+: (NonDet :+: sig)) (CutC m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Cull :+: (NonDet :+: sig)) (CullC m) Source # | |
| Algebra sig m => Algebra (Reader r :+: sig) (ReaderT r m) Source # | |
| Algebra sig m => Algebra (Reader r :+: sig) (ReaderC r m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (State s :+: sig) (StateT s m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (State s :+: sig) (StateT s m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (State s :+: sig) (StateC s m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (State s :+: sig) (StateC s m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Throw e :+: sig) (ThrowC e m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Error e :+: sig) (ExceptT e m) Source # | |
| (Algebra sig m, Effect sig) => Algebra (Error e :+: sig) (ErrorC e m) Source # | |
| (Algebra sig m, Effect sig, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # | |
| (Algebra sig m, Effect sig, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # | |
| (Monoid w, Algebra sig m, Effect sig) => Algebra (Writer w :+: sig) (WriterC w m) Source # | |
| (HFunctor eff, HFunctor sig, Reifies s (Handler eff m), Monad m, Algebra sig m) => Algebra (eff :+: sig) (InterpretC s eff m) Source # | |
Defined in Control.Carrier.Interpret Methods alg :: (eff :+: sig) (InterpretC s eff m) a -> InterpretC s eff m a Source # | |
| (LabelledMember label sub sig, HFunctor sub, Algebra sig m) => Algebra (sub :+: sig) (UnderLabel label sub m) Source # | |
Defined in Control.Effect.Labelled Methods alg :: (sub :+: sig) (UnderLabel label sub m) a -> UnderLabel label sub m a Source # | |
| (Algebra sig m, Effect sig, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # | |
| (Algebra sig m, Effect sig, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # | |
| (Algebra (eff :+: sig) (sub m), HFunctor eff, HFunctor sig) => Algebra (Labelled label eff :+: sig) (Labelled label sub m) Source # | |
class HFunctor sig => Effect sig 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 context.
All first-order effects (those without existential occurrences of m) admit a default definition of thread provided a Generic1 instance is available for the effect.
Since: 1.0.0.0
Instances
| Effect Choose Source # | |
| Effect Empty Source # | |
| Effect Trace Source # | |
| Effect Fresh Source # | |
| Effect Cut Source # | |
| Effect Cull Source # | |
| Effect (Catch e) Source # | |
| Functor sig => Effect (Lift sig) Source # | |
| Effect (Reader r) Source # | |
| Effect (State s) Source # | |
| Effect (Throw e) Source # | |
| Effect (Writer w) Source # | |
| (Effect f, Effect g) => Effect (f :+: g) Source # | |
| Effect sub => Effect (Labelled label sub) Source # | |
type Has eff sig m = (Members eff sig, Algebra sig m) Source #
m is a carrier for sig containing eff.
Note that if eff is a sum, it will be decomposed into multiple Member constraints. While this technically allows one to combine multiple unrelated effects into a single Has constraint, doing so has two significant drawbacks:
- Due to a problem with recursive type families, this can lead to significantly slower compiles.
- It defeats
ghc’s warnings for redundant constraints, and thus can lead to a proliferation of redundant constraints as code is changed.