katip-0.1.1.0: A structured logging framework.

Safe HaskellNone
LanguageHaskell2010

Katip.Monadic

Contents

Description

Provides support for treating payloads and namespaces as composable contexts. The common pattern would be to provide a KatipContext instance for your base monad.

Synopsis

Monadic variants of logging functions from Katip.Core

logFM Source

Arguments

:: (Applicative m, KatipContext m, Katip m) 
=> Severity

Severity of the message

-> LogStr

The log message

-> m () 

Log with full context, but without any code location. Automatically supplies payload and namespace.

logTM :: ExpQ Source

Loc-tagged logging when using template-haskell. Automatically supplies payload and namespace.

$(logt) InfoS "Hello world"

logItemM :: (Applicative m, KatipContext m, Katip m) => Maybe Loc -> Severity -> LogStr -> m () Source

Log with everything, including a source code location. This is very low level and you typically can use logTM in its place. Automaticallysupplies payload and namespace.

logExceptionM Source

Arguments

:: (KatipContext m, MonadCatch m, Applicative m) 
=> m a

Main action to run

-> Severity

Severity

-> m a 

Perform an action while logging any exceptions that may occur. Inspired by onException.

>>> > error "foo" `logExceptionM` ErrorS

Machinery for merging typed log payloads/contexts

class Katip m => KatipContext m where Source

A monadic context that has an inherant way to get logging context and namespace. Examples include a web application monad or database monad.

Instances

(KatipContext m, Katip (MaybeT m)) => KatipContext (MaybeT m) 
(KatipContext m, Katip (ListT m)) => KatipContext (ListT m) 
(KatipContext m, Katip (IdentityT m)) => KatipContext (IdentityT m) 
(KatipContext m, Katip (ResourceT m)) => KatipContext (ResourceT m) 
(Monad m, KatipContext m) => KatipContext (KatipT m) 
MonadIO m => KatipContext (KatipContextT m) 
(Monoid w, KatipContext m, Katip (WriterT w m)) => KatipContext (WriterT w m) 
(Monoid w, KatipContext m, Katip (WriterT w m)) => KatipContext (WriterT w m) 
(KatipContext m, Katip (StateT s m)) => KatipContext (StateT s m) 
(KatipContext m, Katip (StateT s m)) => KatipContext (StateT s m) 
(KatipContext m, Katip (ReaderT r m)) => KatipContext (ReaderT r m) 
(KatipContext m, Katip (ExceptT s m)) => KatipContext (ExceptT s m) 
(KatipContext m, Katip (EitherT e m)) => KatipContext (EitherT e m) 
(Monoid w, KatipContext m, Katip (RWST r w s m)) => KatipContext (RWST r w s m) 
(Monoid w, KatipContext m, Katip (RWST r w s m)) => KatipContext (RWST r w s m) 

data AnyLogContext Source

A wrapper around a log context that erases type information so that contexts from multiple layers can be combined intelligently.

data LogContexts Source

Heterogeneous list of log contexts that provides a smart LogContext instance for combining multiple payload policies. This is critical for log contexts deep down in a stack to be able to inject their own context without worrying about other context that has already been set.

liftPayload :: LogItem a => a -> LogContexts Source

Lift a log context into the generic wrapper so that it can combine with the existing log context.

KatipContextT - Utility transformer that provides Katip and KatipContext instances

newtype KatipContextT m a Source

Provides a simple transformer that defines a KatipContext instance for a fixed namespace and context. You will typically only use this if you are forced to run in IO but still want to have your log context. This is the slightly more powerful version of KatipT in that it provides KatipContext instead of just Katip. For instance:

  threadWithLogging = do
    le <- getLogEnv
    ctx <- getKatipContext
    ns <- getKatipNamespace
    forkIO $ runKatipContextT le ctx ns $ do
      $(logTM) InfoS "Look, I can log in IO and retain context!"
      doOtherStuff

Constructors

KatipContextT 

Fields

unKatipContextT :: ReaderT KatipContextTState m a
 

Instances

MonadTrans KatipContextT 
MonadTransControl KatipContextT 
MonadBase b m => MonadBase b (KatipContextT m) 
MonadBaseControl b m => MonadBaseControl b (KatipContextT m) 
MonadWriter w m => MonadWriter w (KatipContextT m) 
MonadState s m => MonadState s (KatipContextT m) 
MonadReader r m => MonadReader r (KatipContextT m) 
MonadError e m => MonadError e (KatipContextT m) 
Alternative m => Alternative (KatipContextT m) 
Monad m => Monad (KatipContextT m) 
Functor m => Functor (KatipContextT m) 
MonadFix m => MonadFix (KatipContextT m) 
MonadPlus m => MonadPlus (KatipContextT m) 
Applicative m => Applicative (KatipContextT m) 
MonadThrow m => MonadThrow (KatipContextT m) 
MonadMask m => MonadMask (KatipContextT m) 
MonadCatch m => MonadCatch (KatipContextT m) 
MonadIO m => MonadIO (KatipContextT m) 
MonadIO m => Katip (KatipContextT m) 
MonadIO m => KatipContext (KatipContextT m) 
type StT KatipContextT a = StT (ReaderT KatipContextTState) a 
type StM (KatipContextT m) a = ComposeSt KatipContextT m a