| Copyright | (c) Moritz Clasmeier 2018 |
|---|---|
| License | BSD3 |
| Maintainer | mtesseract@silverratio.net |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Control.Error.Context
Description
Provides an API for enriching errors with contexts.
- class (Monad m, MonadThrow m) => MonadErrorContext m where
- data ErrorContext = ErrorContext {}
- data ErrorContextT m a
- runErrorContextT :: ErrorContextT m a -> m a
- newtype ErrorContextKatipT m a = ErrorContextKatipT {
- runErrorContextKatipT :: m a
- data ErrorWithContext e = ErrorWithContext ErrorContext e
- errorContextualize :: MonadErrorContext m => e -> m (ErrorWithContext e)
- errorContextForget :: ErrorWithContext e -> e
- errorWithContextDump :: (Show e, MonadIO m) => ErrorWithContext e -> m ()
- catchWithoutContext :: forall a e m. (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a
- catchWithContext :: (MonadCatch m, Exception e) => m a -> (ErrorWithContext e -> m a) -> m a
- catchAnyWithContext :: MonadCatch m => m a -> (ErrorWithContext SomeException -> m a) -> m a
- catchAnyWithoutContext :: MonadCatch m => m a -> (SomeException -> m a) -> m a
- ensureExceptionContext :: (MonadCatch m, MonadErrorContext m) => m a -> m a
- tryAnyWithContext :: MonadCatch m => m a -> m (Either (ErrorWithContext SomeException) a)
- tryAnyWithoutContext :: MonadCatch m => m a -> m (Either SomeException a)
- tryWithContext :: (MonadCatch m, Exception e) => m a -> m (Either (ErrorWithContext e) a)
- tryWithoutContext :: (MonadCatch m, Exception e) => m a -> m (Either e a)
Documentation
class (Monad m, MonadThrow m) => MonadErrorContext m where Source #
Monad type class providing contextualized errors.
Minimal complete definition
Methods
Arguments
| :: m ErrorContext | Return the current error context. |
withErrorContext :: ToJSON v => Text -> v -> m a -> m a Source #
withErrorNamespace :: Text -> m a -> m a Source #
Instances
| MonadCatch m => MonadErrorContext (ErrorContextT m) Source # | |
| (MonadCatch m, KatipContext m) => MonadErrorContext (ErrorContextKatipT m) Source # | |
data ErrorContextT m a Source #
Data type implementing MonadErrorContext.
Instances
| MonadTrans ErrorContextT Source # | |
| MonadWriter w m => MonadWriter w (ErrorContextT m) Source # | |
| MonadState s m => MonadState s (ErrorContextT m) Source # | |
| MonadReader r m => MonadReader r (ErrorContextT m) Source # | |
| Monad m => Monad (ErrorContextT m) Source # | |
| Functor m => Functor (ErrorContextT m) Source # | |
| Applicative m => Applicative (ErrorContextT m) Source # | |
| (MonadCatch m, MonadIO m) => MonadIO (ErrorContextT m) Source # | |
| (MonadCatch m, MonadResource m) => MonadResource (ErrorContextT m) Source # | |
| MonadCatch m => MonadThrow (ErrorContextT m) Source # | |
| MonadCatch m => MonadCatch (ErrorContextT m) Source # | |
| MonadCatch m => MonadErrorContext (ErrorContextT m) Source # | |
runErrorContextT :: ErrorContextT m a -> m a Source #
newtype ErrorContextKatipT m a Source #
Data type implementing MonadErrorContext.
Constructors
| ErrorContextKatipT | |
Fields
| |
Instances
| MonadTrans ErrorContextKatipT Source # | |
| MonadWriter w m => MonadWriter w (ErrorContextKatipT m) Source # | |
| MonadState s m => MonadState s (ErrorContextKatipT m) Source # | |
| MonadReader r m => MonadReader r (ErrorContextKatipT m) Source # | |
| Monad m => Monad (ErrorContextKatipT m) Source # | |
| Functor m => Functor (ErrorContextKatipT m) Source # | |
| Applicative m => Applicative (ErrorContextKatipT m) Source # | |
| (KatipContext m, MonadCatch m, MonadIO m) => MonadIO (ErrorContextKatipT m) Source # | |
| (KatipContext m, MonadCatch m, MonadResource m) => MonadResource (ErrorContextKatipT m) Source # | |
| (KatipContext m, MonadCatch m) => MonadThrow (ErrorContextKatipT m) Source # | |
| (KatipContext m, MonadCatch m) => MonadCatch (ErrorContextKatipT m) Source # | |
| (MonadCatch m, KatipContext m) => KatipContext (ErrorContextKatipT m) Source # | |
| (MonadCatch m, KatipContext m, MonadIO m, Katip m) => Katip (ErrorContextKatipT m) Source # | |
| (MonadCatch m, KatipContext m) => MonadErrorContext (ErrorContextKatipT m) Source # | |
data ErrorWithContext e Source #
Boundles an error with an ErrorContext.
Constructors
| ErrorWithContext ErrorContext e |
Instances
| Functor ErrorWithContext Source # | |
| Show e => Show (ErrorWithContext e) Source # | |
| Exception e => Exception (ErrorWithContext e) Source # | An |
errorContextualize :: MonadErrorContext m => e -> m (ErrorWithContext e) Source #
Enrich an error value with an error context.
errorContextForget :: ErrorWithContext e -> e Source #
Forgets the context from an enriched error.
errorWithContextDump :: (Show e, MonadIO m) => ErrorWithContext e -> m () Source #
Dump an error with context to stdout.
catchWithoutContext :: forall a e m. (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a Source #
Like catch, but the handler is required to be context-unaware.
Is also able to catch exceptions with context, in which case the
context will be forgotten before the exception will be provided to
the handler.
catchWithContext :: (MonadCatch m, Exception e) => m a -> (ErrorWithContext e -> m a) -> m a Source #
Like catch, but the handler is required to be context-aware. Is
also able to catch exceptions of type e (without context).
catchAnyWithContext :: MonadCatch m => m a -> (ErrorWithContext SomeException -> m a) -> m a Source #
Context aware version of catchAny.
catchAnyWithoutContext :: MonadCatch m => m a -> (SomeException -> m a) -> m a Source #
Context aware version of catchAny.
ensureExceptionContext :: (MonadCatch m, MonadErrorContext m) => m a -> m a Source #
tryAnyWithContext :: MonadCatch m => m a -> m (Either (ErrorWithContext SomeException) a) Source #
tryAnyWithoutContext :: MonadCatch m => m a -> m (Either SomeException a) Source #
tryWithContext :: (MonadCatch m, Exception e) => m a -> m (Either (ErrorWithContext e) a) Source #
tryWithoutContext :: (MonadCatch m, Exception e) => m a -> m (Either e a) Source #