| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Katip.Monadic
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
- logFM :: (Applicative m, KatipContext m) => Severity -> LogStr -> m ()
- logTM :: ExpQ
- logLocM :: (Applicative m, KatipContext m, HasCallStack) => Severity -> LogStr -> m ()
- logItemM :: (Applicative m, KatipContext m, HasCallStack) => Maybe Loc -> Severity -> LogStr -> m ()
- logExceptionM :: (KatipContext m, MonadCatch m, Applicative m) => m a -> Severity -> m a
- class Katip m => KatipContext m where- getKatipContext :: m LogContexts
- localKatipContext :: (LogContexts -> LogContexts) -> m a -> m a
- getKatipNamespace :: m Namespace
- localKatipNamespace :: (Namespace -> Namespace) -> m a -> m a
 
- data AnyLogContext
- data LogContexts
- liftPayload :: LogItem a => a -> LogContexts
- newtype KatipContextT m a = KatipContextT {}
- runKatipContextT :: LogItem c => LogEnv -> c -> Namespace -> KatipContextT m a -> m a
- katipAddNamespace :: KatipContext m => Namespace -> m a -> m a
- katipAddContext :: (LogItem i, KatipContext m) => i -> m a -> m a
- data KatipContextTState = KatipContextTState {- ltsLogEnv :: !LogEnv
- ltsContext :: !LogContexts
- ltsNamespace :: !Namespace
 
- newtype NoLoggingT m a = NoLoggingT {- runNoLoggingT :: m a
 
- askLoggerIO :: (Applicative m, KatipContext m) => m (Severity -> LogStr -> IO ())
Monadic variants of logging functions from Katip.Core
Arguments
| :: (Applicative m, KatipContext 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.
Loc-tagged logging when using template-haskell. Automatically
 supplies payload and namespace.
$(logTM) InfoS "Hello world"
logLocM :: (Applicative m, KatipContext m, HasCallStack) => Severity -> LogStr -> m () Source #
Loc-tagged logging when using getCallStack implicit-callstacks>.
   Automatically supplies payload and namespace.
Same consideration as logLoc applies.
By default, location will be logged from the module that invokes logLocM.
 If you want to use logLocM in a helper, wrap the entire helper in
 withFrozenCallStack to retain the callsite of the helper in the logs.
This function does not require template-haskell. Using GHC <= 7.8 will result
 in the emission of a log line without any location information.
 Users using GHC <= 7.8 may want to use the template-haskell function
 logTM for maximum compatibility.
logLocM InfoS "Hello world"
logItemM :: (Applicative m, KatipContext m, HasCallStack) => 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. Automatically supplies payload and namespace.
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. The local variants are just like local from Reader and
 indeed you can easily implement them with local if you happen to
 be using a Reader in your monad. These give us katipAddNamespace
 and katipAddContext that works with *any* KatipContext, as
 opposed to making users have to implement these functions on their
 own in each app.
Methods
getKatipContext :: m LogContexts Source #
localKatipContext :: (LogContexts -> LogContexts) -> m a -> m a Source #
Temporarily modify the current context for the duration of the
 supplied monad. Used in katipAddContext
getKatipNamespace :: m Namespace Source #
localKatipNamespace :: (Namespace -> Namespace) -> m a -> m a Source #
Temporarily modify the current namespace for the duration of the
 supplied monad. Used in katipAddNamespace
Instances
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. Also note that contexts are treated as a
 sequence and <> will be appended to the right hand side of the
 sequence. If there are conflicting keys in the contexts, the /right
 side will take precedence/, which is counter to how monoid works
 for Map and HashMap, so bear that in mind. The reasoning is
 that if the user is sequentially adding contexts to the right
 side of the sequence, on conflict the intent is to overwrite with
 the newer value (i.e. the rightmost value).
Additional note: you should not mappend LogContexts in any sort of infinite loop, as it retains all data, so that would be a memory leak.
Instances
| Semigroup LogContexts Source # | |
| Defined in Katip.Monadic Methods (<>) :: LogContexts -> LogContexts -> LogContexts # sconcat :: NonEmpty LogContexts -> LogContexts # stimes :: Integral b => b -> LogContexts -> LogContexts # | |
| Monoid LogContexts Source # | |
| Defined in Katip.Monadic Methods mempty :: LogContexts # mappend :: LogContexts -> LogContexts -> LogContexts # mconcat :: [LogContexts] -> LogContexts # | |
| ToJSON LogContexts Source # | |
| Defined in Katip.Monadic Methods toJSON :: LogContexts -> Value # toEncoding :: LogContexts -> Encoding # toJSONList :: [LogContexts] -> Value # toEncodingList :: [LogContexts] -> Encoding # | |
| LogItem LogContexts Source # | |
| Defined in Katip.Monadic Methods payloadKeys :: Verbosity -> LogContexts -> PayloadSelection Source # | |
| ToObject LogContexts Source # | |
| Defined in Katip.Monadic Methods toObject :: LogContexts -> Object Source # | |
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. Just like KatipT, you
 should use this if you prefer an explicit transformer stack and
 don't want to (or cannot) define KatipContext for your monad
 . 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 | |
Instances
runKatipContextT :: LogItem c => LogEnv -> c -> Namespace -> KatipContextT m a -> m a Source #
katipAddNamespace :: KatipContext m => Namespace -> m a -> m a Source #
Append a namespace segment to the current namespace for the given monadic action, then restore the previous state afterwards. Works with anything implementing KatipContext.
katipAddContext :: (LogItem i, KatipContext m) => i -> m a -> m a Source #
Append some context to the current context for the given monadic
 action, then restore the previous state afterwards. Important note:
 be careful using this in a loop. If you're using something like
 forever or replicateM_ that does explicit sharing to avoid a
 memory leak, youll be fine as it will *sequence* calls to
 katipAddNamespace, so each loop will get the same context
 added. If you instead roll your own recursion and you're recursing
 in the action you provide, you'll instead accumulate tons of
 redundant contexts and even if they all merge on log, they are
 stored in a sequence and will leak memory. Works with anything
 implementing KatipContext.
data KatipContextTState Source #
Constructors
| KatipContextTState | |
| Fields 
 | |
newtype NoLoggingT m a Source #
Constructors
| NoLoggingT | |
| Fields 
 | |
Instances
askLoggerIO :: (Applicative m, KatipContext m) => m (Severity -> LogStr -> IO ()) Source #
Convenience function for when you have to integrate with a third party API that takes a generic logging function as an argument.