Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Error exc m k
- throwError :: (Member (Error exc) sig, Carrier sig m) => exc -> m a
- catchError :: (Member (Error exc) sig, Carrier sig m) => m a -> (exc -> m a) -> m a
- runError :: ErrorC exc m a -> m (Either exc a)
- newtype ErrorC e m a = ErrorC {}
- class (HFunctor sig, Monad m) => Carrier sig m | m -> sig
- class Member (sub :: (* -> *) -> * -> *) sup
- run :: PureC a -> a
Error effect
throwError :: (Member (Error exc) sig, Carrier sig m) => exc -> m a Source #
Throw an error, escaping the current computation up to the nearest catchError
(if any).
run (runError (throwError a)) === Left @Int @Int a
catchError :: (Member (Error exc) sig, Carrier sig m) => m a -> (exc -> 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 Resource
fits your use case; if not, use liftIO
with
try
or use Catch
from outside the effect invocation.
run (runError (pure a `catchError` pure)) === Right a
run (runError (throwError a `catchError` pure)) === Right @Int @Int a
run (runError (throwError a `catchError` (throwError @Int))) === Left @Int @Int a
Error carrier
Instances
MonadTrans (ErrorC e) Source # | |
Defined in Control.Effect.Error | |
Monad m => Monad (ErrorC e m) Source # | |
Functor m => Functor (ErrorC e m) Source # | |
MonadFix m => MonadFix (ErrorC e m) Source # | |
Defined in Control.Effect.Error | |
MonadFail m => MonadFail (ErrorC e m) Source # | |
Defined in Control.Effect.Error | |
Applicative m => Applicative (ErrorC e m) Source # | |
Defined in Control.Effect.Error | |
MonadIO m => MonadIO (ErrorC e m) Source # | |
Defined in Control.Effect.Error | |
Alternative m => Alternative (ErrorC e m) Source # | |
(Alternative m, Monad m) => MonadPlus (ErrorC e m) Source # | |
(Carrier sig m, Effect sig) => Carrier (Error e :+: sig) (ErrorC e m) Source # | |
Re-exports
class (HFunctor sig, Monad m) => Carrier sig m | m -> sig Source #
The class of carriers (results) for algebras (effect handlers) over signatures (effects), whose actions are given by the eff
method.