Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Catch effect
catchError :: Has (Catch e) sig m => m a -> (e -> m a) -> m a Source #
Run a computation which can throw errors with a handler to run on error.
Errors thrown by the handler will escape up to the nearest enclosing catchError
(if any). Note that this effect does not handle errors thrown from impure contexts such as IO, nor will it handle exceptions thrown from pure code. If you need to handle IO-based errors, consider if fused-effects-exceptions
fits your use case; if not, use liftIO
with try
or use catch
from outside the effect invocation.
runError (throwError
ecatchError
f) = runError (f e)
Since: 0.1.0.0
Re-exports
class 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
Instances
Algebra Choose NonEmpty Source # | |
Algebra Empty Maybe Source # | |
Algebra NonDet List Source # | |
Algebra sig m => Algebra sig (Choosing m) Source # | |
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 (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 (IdentityT m) Source # | |
Algebra (Lift Identity) Identity Source # | |
Algebra (Lift IO) IO Source # | |
Algebra (Error e) (Either e) Source # | |
Monad m => Algebra (Lift m) (LiftC m) Source # | |
Monoid w => Algebra (Writer w) ((,) w) Source # | |
Algebra (Reader r) ((->) r) Source # | |
Algebra sig m => Algebra (Choose :+: sig) (ChooseC m) Source # | |
Algebra sig m => Algebra (Cull :+: (NonDet :+: sig)) (CullC m) Source # | |
Algebra sig m => Algebra (Cut :+: (NonDet :+: sig)) (CutC m) Source # | |
Algebra sig m => Algebra (Empty :+: sig) (EmptyC m) Source # | |
Algebra sig m => Algebra (Empty :+: sig) (EmptyC m) Source # | |
Algebra sig m => Algebra (Empty :+: sig) (MaybeT m) Source # | |
Algebra sig m => Algebra (Fail :+: sig) (FailC m) Source # | |
Algebra sig m => Algebra (Fresh :+: sig) (FreshC m) Source # | |
Algebra sig m => Algebra (Fresh :+: sig) (FreshC m) Source # | |
Algebra sig m => Algebra (NonDet :+: sig) (NonDetC m) Source # | |
Algebra sig m => Algebra (Trace :+: sig) (TraceC 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, Monoid w) => Algebra (Accum w :+: sig) (AccumC w m) Source # | |
(Algebra sig m, Semigroup w, MonadIO m) => Algebra (Accum w :+: sig) (AccumC w m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Accum w :+: sig) (AccumC w m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Accum w :+: sig) (AccumT w m) Source # | |
Algebra sig m => Algebra (Error e :+: sig) (ErrorC e m) Source # | |
Algebra sig m => Algebra (Error e :+: sig) (ErrorC e m) Source # | |
Algebra sig m => Algebra (Error e :+: sig) (ExceptT e m) Source # | |
Algebra sig m => Algebra (Reader r :+: sig) (ReaderC r m) Source # | |
Algebra sig m => Algebra (Reader r :+: sig) (ReaderT r m) Source # | |
Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # | |
(MonadIO m, Algebra sig m) => Algebra (State s :+: sig) (StateC s m) Source # | |
Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # | |
Algebra sig m => Algebra (State s :+: sig) (StateC s m) Source # | |
Algebra sig m => Algebra (State s :+: sig) (StateT s m) Source # | |
Algebra sig m => Algebra (State s :+: sig) (StateT s m) Source # | |
Algebra sig m => Algebra (Throw e :+: sig) (ThrowC e m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterC w m) Source # | |
(Monoid w, Algebra sig m) => Algebra (Writer w :+: sig) (WriterC w m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Writer w :+: sig) (WriterT w m) Source # | |
(Reifies s (Interpreter eff m), Algebra sig m) => Algebra (eff :+: sig) (InterpretC s eff m) Source # | |
Defined in Control.Carrier.Interpret alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (InterpretC s eff m) -> (eff :+: sig) n a -> ctx () -> InterpretC s eff m (ctx a) Source # | |
Algebra (eff :+: sig) (sub m) => Algebra (Labelled label eff :+: sig) (Labelled label sub m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # | |
(Algebra sig m, Monoid w) => Algebra (Reader r :+: (Writer w :+: (State s :+: sig))) (RWST r w s m) Source # | |
(LabelledMember label sub sig, Algebra sig m) => Algebra (sub :+: sig) (UnderLabel label sub m) Source # | |
Defined in Control.Effect.Labelled alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (UnderLabel label sub m) -> (sub :+: sig) n a -> ctx () -> UnderLabel label sub m (ctx a) 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.
Since: 1.0.0.0