rescue-0.4.2.1: More understandable exceptions
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Rescue

Description

Rescue semantics & helpers

Essentially a type-directed version of Catch.

This is the opposite of Raise, which embeds en error. Rescue takes a potential error out of the surrounding context and either handles or exposes it.

Synopsis

Documentation

attemptM :: MonadRescue m => m a -> (Either (ErrorCase m) a -> m b) -> m b Source #

Simpler helper to eliminate the bind operator from an attempt flow

>>> type MyErrs = '[FooErr, BarErr]
>>> :{
boom :: Rescue MyErrs String
boom = raise FooErr
:}
>>> :{
attempt boom >>= \case
  Left  err -> return ("err: " ++ show err)
  Right val -> return val
:}
RescueT (Identity (Right "err: Identity FooErr"))
>>> :{
attemptM boom $ \case
  Left  err -> return ("err: " ++ show err)
  Right val -> return val
:}
RescueT (Identity (Right "err: Identity FooErr"))

Recover from exceptions

rescue :: (Bifunctor m, ElemRemove err errs) => (err -> OpenUnion (Remove err errs)) -> m (OpenUnion errs) a -> m (OpenUnion (Remove err errs)) a Source #

rescueT :: (MonadTransError t errs m, MonadRaise (t (Remove err errs) m), CheckErrors (t (Remove err errs) m), ElemRemove err (Errors (t errs m)), Remove err (Errors (t errs m)) ~ Errors (t (Remove err errs) m)) => (err -> t (Remove err errs) m a) -> t errs m a -> t (Remove err errs) m a Source #

Handle and eliminate a single error

rescueM :: (MonadBase (m (OpenUnion wide)) (m (OpenUnion (Remove err wide))), MonadRescue (m (OpenUnion wide)), MonadRaise (m (OpenUnion narrow)), wide ~ Errors (m (OpenUnion wide)), narrow ~ Errors (m (OpenUnion narrow)), narrow ~ Remove err wide, CheckErrors (m (OpenUnion narrow)), ElemRemove err wide) => (err -> m (OpenUnion narrow) a) -> m (OpenUnion wide) a -> m (OpenUnion narrow) a Source #

rescueBase :: (MonadRescue wide, MonadBase wide narrow, MonadRaise narrow, CheckErrors narrow, Remove err (Errors wide) ~ Errors narrow, ElemRemove err (Errors wide)) => (err -> narrow a) -> wide a -> narrow a Source #

The more generic (MonadBase-ified) version of handle

rescueEach :: (Bifunctor m, ToOpenProduct handlerTuple (ReturnX (OpenUnion targetErrs) errs)) => handlerTuple -> m (OpenUnion errs) a -> m (OpenUnion targetErrs) a Source #

rescueEachM :: (sourceErrs ~ Errors (m (OpenUnion sourceErrs)), MonadRescue (m (OpenUnion sourceErrs)), MonadBase (m (OpenUnion sourceErrs)) (m (OpenUnion targetErrs)), ToOpenProduct handlerTuple (ReturnX (m (OpenUnion targetErrs) a) sourceErrs)) => handlerTuple -> m (OpenUnion sourceErrs) a -> m (OpenUnion targetErrs) a Source #

rescueEachT :: (sourceErrs ~ Errors (t sourceErrs m), MonadTransError t sourceErrs m, ToOpenProduct handlerTuple (ReturnX (t targetErrs m a) sourceErrs)) => handlerTuple -> t sourceErrs m a -> t targetErrs m a Source #

rescueAll :: (MonadRescue (m (OpenUnion errs)), MonadBase (m (OpenUnion errs)) (m ()), errs ~ Errors (m (OpenUnion errs))) => (OpenUnion errs -> m () a) -> m (OpenUnion errs) a -> m () a Source #

Guaranteed runs

reattempt :: MonadRescue m => Natural -> m a -> m a Source #

retry without asynchoronous exception cleanup. Useful when not dealing with external resources that may be dangerous to close suddenly.

report :: (MonadRescue m, RaisesOnly m errs, CheckErrors m) => (ErrorCase m -> m ()) -> m a -> m a Source #

lastly :: (CheckErrors m, MonadRescue m) => m a -> m b -> m a Source #

Run an additional step, and throw away the result. Return the result of the action passed.

Error access

mapError :: (MonadRescue m, MonadBase m n, MonadRaise n, CheckErrors n) => (ErrorCase m -> ErrorCase n) -> m a -> n a Source #

replaceError :: (MonadRescue m, MonadBase m n, MonadRaise n, n `Raises` err) => err -> m a -> n a Source #

asNotFound :: forall n m a. (MonadRescue m, MonadBase m n, MonadRaise n, n `Raises` NotFound a) => m a -> n a Source #

Reexports