Copyright | (c) 2021 Xy Ren |
---|---|
License | BSD3 |
Maintainer | xy.r@outlook.com |
Stability | experimental |
Portability | non-portable (GHC only) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Synopsis
- data Error e :: Effect where
- ThrowError :: e -> Error e m a
- CatchError :: m a -> (e -> m a) -> Error e m a
- throwError :: Error e :> es => e -> Eff es a
- catchError :: Error e :> es => Eff es a -> (e -> Eff es a) -> Eff es a
- fromEither :: Error e :> es => Either e a -> Eff es a
- fromException :: forall e es a. (Exception e, '[Error e, IOE] :>> es) => IO a -> Eff es a
- fromExceptionVia :: (Exception ex, '[Error er, IOE] :>> es) => (ex -> er) -> IO a -> Eff es a
- fromExceptionEff :: forall e es a. (Exception e, '[Error e, IOE] :>> es) => Eff es a -> Eff es a
- fromExceptionEffVia :: (Exception ex, '[Error er, IOE] :>> es) => (ex -> er) -> Eff es a -> Eff es a
- note :: Error e :> es => e -> Maybe a -> Eff es a
- catchErrorJust :: Error e :> es => (e -> Maybe b) -> Eff es a -> (b -> Eff es a) -> Eff es a
- catchErrorIf :: Error e :> es => (e -> Bool) -> Eff es a -> (e -> Eff es a) -> Eff es a
- handleError :: Error e :> es => (e -> Eff es a) -> Eff es a -> Eff es a
- handleErrorJust :: Error e :> es => (e -> Maybe b) -> (b -> Eff es a) -> Eff es a -> Eff es a
- handleErrorIf :: Error e :> es => (e -> Bool) -> (e -> Eff es a) -> Eff es a -> Eff es a
- tryError :: Error e :> es => Eff es a -> Eff es (Either e a)
- tryErrorJust :: Error e :> es => (e -> Maybe b) -> Eff es a -> Eff es (Either b a)
- runError :: forall e es a. Eff (Error e ': es) a -> Eff es (Either e a)
- mapError :: forall e e' es. Error e' :> es => (e -> e') -> Eff (Error e ': es) ~> Eff es
Effect
data Error e :: Effect where Source #
An effect capable of breaking out of current control flow by throwing an error of type e
, and handling the
errors thrown from computations. This effect roughly corresponds to the MonadError
typeclass and ExceptT
monad
transformer in mtl
.
ThrowError :: e -> Error e m a | |
CatchError :: m a -> (e -> m a) -> Error e m a |
Operations
:: Error e :> es | |
=> Eff es a | The computation that may throw errors |
-> (e -> Eff es a) | The handler that is called when an error is thrown |
-> Eff es a |
Handle an error if one is thrown from a computation, and then return to normal control flow.
Other ways of throwing errors
fromExceptionVia :: (Exception ex, '[Error er, IOE] :>> es) => (ex -> er) -> IO a -> Eff es a Source #
Like fromException
, but allows to transform the exception into another error type.
fromExceptionEff :: forall e es a. (Exception e, '[Error e, IOE] :>> es) => Eff es a -> Eff es a Source #
fromExceptionEffVia :: (Exception ex, '[Error er, IOE] :>> es) => (ex -> er) -> Eff es a -> Eff es a Source #
Like fromExceptionEff
, but allows to transform the exception into another error type.
note :: Error e :> es => e -> Maybe a -> Eff es a Source #
Try to extract a value from Maybe
, throw an error otherwise.
Other ways of handling errors
catchErrorJust :: Error e :> es => (e -> Maybe b) -> Eff es a -> (b -> Eff es a) -> Eff es a Source #
A variant of catchError
that allows a predicate to choose whether to catch (Just
) or rethrow (Nothing
) the
error.
catchErrorIf :: Error e :> es => (e -> Bool) -> Eff es a -> (e -> Eff es a) -> Eff es a Source #
A variant of catchError
that allows a predicate to choose whether to catch (True
) or rethrow (False
) the
error.
handleError :: Error e :> es => (e -> Eff es a) -> Eff es a -> Eff es a Source #
Flipped version of catchError
.
handleErrorJust :: Error e :> es => (e -> Maybe b) -> (b -> Eff es a) -> Eff es a -> Eff es a Source #
Flipped version of catchErrorJust
.
handleErrorIf :: Error e :> es => (e -> Bool) -> (e -> Eff es a) -> Eff es a -> Eff es a Source #
Flipped version of catchErrorIf
.
tryError :: Error e :> es => Eff es a -> Eff es (Either e a) Source #
Runs a computation, returning a Left
value if an error was thrown.
Interpretations
runError :: forall e es a. Eff (Error e ': es) a -> Eff es (Either e a) Source #
Run an Error
effect.
Caveats
runError
is implemented with Exception
s therefore inherits some of its unexpected behaviors.
Errors thrown in forked threads will not be directly caught by catchError
s in the parent thread. Instead it will
incur an exception, and we won't be quite able to display the details of that exception properly at that point.
Therefore please properly handle the errors in the forked threads separately.
However if you use async
and wait
for the action in the same effect scope (i.e. they get to be interpreted by
the same runError
handler), the error will be caught in the parent thread even if you don't deal with it in the
forked thread. But if you passed the Async
value out of the effect scope and wait
ed for it elsewhere, the error
will again not be caught. The best choice is not to pass Async
values around randomly.