error-context-0.1.0.0: Provides API for enriching errors with contexts

Copyright(c) Moritz Clasmeier 2018
LicenseBSD3
Maintainermtesseract@silverratio.net
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Control.Error.Context

Description

Provides an API for enriching errors with contexts.

Synopsis

Documentation

data ErrorContext Source #

Encapsulates the error context — essentially a stack of Text values.

Constructors

ErrorContext [Text] 

data ErrorContextT m a Source #

Data type implementing MonadErrorContext.

Instances

MonadTrans ErrorContextT Source # 

Methods

lift :: Monad m => m a -> ErrorContextT m a #

MonadWriter w m => MonadWriter w (ErrorContextT m) Source # 

Methods

writer :: (a, w) -> ErrorContextT m a #

tell :: w -> ErrorContextT m () #

listen :: ErrorContextT m a -> ErrorContextT m (a, w) #

pass :: ErrorContextT m (a, w -> w) -> ErrorContextT m a #

MonadState s m => MonadState s (ErrorContextT m) Source # 

Methods

get :: ErrorContextT m s #

put :: s -> ErrorContextT m () #

state :: (s -> (a, s)) -> ErrorContextT m a #

MonadReader r m => MonadReader r (ErrorContextT m) Source #

Implement MonadReader for ErrorContextT.

Methods

ask :: ErrorContextT m r #

local :: (r -> r) -> ErrorContextT m a -> ErrorContextT m a #

reader :: (r -> a) -> ErrorContextT m a #

Monad m => Monad (ErrorContextT m) Source # 

Methods

(>>=) :: ErrorContextT m a -> (a -> ErrorContextT m b) -> ErrorContextT m b #

(>>) :: ErrorContextT m a -> ErrorContextT m b -> ErrorContextT m b #

return :: a -> ErrorContextT m a #

fail :: String -> ErrorContextT m a #

Functor m => Functor (ErrorContextT m) Source # 

Methods

fmap :: (a -> b) -> ErrorContextT m a -> ErrorContextT m b #

(<$) :: a -> ErrorContextT m b -> ErrorContextT m a #

Applicative m => Applicative (ErrorContextT m) Source # 

Methods

pure :: a -> ErrorContextT m a #

(<*>) :: ErrorContextT m (a -> b) -> ErrorContextT m a -> ErrorContextT m b #

liftA2 :: (a -> b -> c) -> ErrorContextT m a -> ErrorContextT m b -> ErrorContextT m c #

(*>) :: ErrorContextT m a -> ErrorContextT m b -> ErrorContextT m b #

(<*) :: ErrorContextT m a -> ErrorContextT m b -> ErrorContextT m a #

(MonadCatch m, MonadIO m) => MonadIO (ErrorContextT m) Source # 

Methods

liftIO :: IO a -> ErrorContextT m a #

(MonadCatch m, MonadResource m) => MonadResource (ErrorContextT m) Source #

Implement MonadResource for ErrorContextT.

MonadThrow m => MonadThrow (ErrorContextT m) Source #

Implement MonadThrow for ErrorContextT.

Methods

throwM :: Exception e => e -> ErrorContextT m a #

MonadCatch m => MonadCatch (ErrorContextT m) Source #

Implement MonadCatch for ErrorContextT.

Methods

catch :: Exception e => ErrorContextT m a -> (e -> ErrorContextT m a) -> ErrorContextT m a #

MonadThrow m => MonadErrorContext (ErrorContextT m) Source #

Implement MonadErrorContext for ErrorContextT.

class (Monad m, MonadThrow m) => MonadErrorContext m where Source #

Monad type class providing contextualized errors.

Minimal complete definition

errorContextCollect, withErrorContext

Methods

errorContextCollect Source #

Arguments

:: m ErrorContext

Return the current error context.

withErrorContext Source #

Arguments

:: Text 
-> m a 
-> m a

Execute a monadic action while having the provided Text being pushed to the error context.

runErrorContextT :: ErrorContextT m a -> m a Source #

Unwrap an ErrorContextT. Exceptions of type e thrown in the provided action via throwM will cause an ErrorWithContext e exception to be propagated upwards.

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).

catchJustWithContext :: (MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a Source #

catchAnyWithContext :: MonadCatch m => m a -> (ErrorWithContext SomeException -> m a) -> m a Source #

Context aware version of catchAny.