Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Includes all of the APIs youll need to use Katip. Be sure to
check out the included examples
directory for an example of
usage.
Here's a basic example:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} import Control.Exception import Katip main :: IO () main = do handleScribe <- mkHandleScribe ColorIfTerminal stdout (permitItem InfoS) V2 let makeLogEnv = registerScribe "stdout" handleScribe defaultScribeSettings =<< initLogEnv "MyApp" "production" -- closeScribes will stop accepting new logs, flush existing ones and clean up resources bracket makeLogEnv closeScribes $ \le -> do let initialContext = () -- this context will be attached to every log in your app and merged w/ subsequent contexts let initialNamespace = "main" runKatipContextT le initialContext initialNamespace $ do $(logTM) InfoS "Hello Katip" -- This adds a namespace to the current namespace and merges a piece of contextual data into your context katipAddNamespace "additional_namespace" $ katipAddContext (sl "some_context" True) $ do $(logTM) WarningS "Now we're getting fancy" katipNoLogging $ do $(logTM) DebugS "You will never see this!"
And here is the output:
[2021-06-14 20:24:24][MyApp.main][Info][yourhostname][PID 14420][ThreadId 27][main:Main app/Main.hs:26:9] Hello Katip [2021-06-14 20:24:24][MyApp.main.additional_namespace][Warning][yourhostname][PID 14420][ThreadId 27][some_context:True][main:Main app/Main.hs:29:11] Now we're getting fancy
Another common case that you have some sort of App monad that's based on ReaderT with some Config state. This is a perfect place to insert read-only katip state:
import Katip as K data Config = Config { logNamespace :: K.Namespace , logContext :: K.LogContexts , logEnv :: K.LogEnv -- whatever other read-only config you need } newtype App m a = App { unApp :: ReaderT Config m a } deriving (Functor, Applicative, Monad, MonadIO, MonadReader Config) -- these are necessary -- These instances get even easier with lenses! instance (MonadIO m) => K.Katip (App m) where getLogEnv = asks logEnv -- with lens: -- getLogEnv = view logEnv localLogEnv f (App m) = App (local (\s -> s { logEnv = f (logEnv s)}) m) -- with lens: -- localLogEnv f (App m) = App (local (over logEnv f) m) instance (MonadIO m) => K.KatipContext (App m) where getKatipContext = asks logContext -- with lens: -- getKatipContext = view logContext localKatipContext f (App m) = App (local (\s -> s { logContext = f (logContext s)}) m) -- with lens: -- localKatipContext f (App m) = App (local (over logContext f) m) getKatipNamespace = asks logNamespace -- with lens: -- getKatipNamespace = view logNamespace localKatipNamespace f (App m) = App (local (\s -> s { logNamespace = f (logNamespace s)}) m) -- with lens: -- localKatipNamespace f (App m) = App (local (over logNamespace f) m)
To get up and running, the workflow is generally:
- Set up a
LogEnv
usinginitLogEnv
. - Add
Scribe
s usingregisterScribe
. - Either use
KatipT
orKatipContextT
for a pre-built transformer stack or addKatip
andKatipContext
instances to your own transformer stack. If you do the latter, you may want to look in theexamples
dir for some tips on composing contexts and namespaces. - Define some structured log data throughout your application and
implement
ToObject
andLogItem
for them. - Begin logging with
logT
,logTM
, etc. - Define your own
Scribe
if you need to output to some as-yet unsupported format or service. If you think it would be useful to others, consider releasing your own package.
Synopsis
- newtype Namespace = Namespace {
- unNamespace :: [Text]
- newtype Environment = Environment {}
- data Severity
- renderSeverity :: Severity -> Text
- textToSeverity :: Text -> Maybe Severity
- data Verbosity
- class ToObject a where
- class ToObject a => LogItem a where
- payloadKeys :: Verbosity -> a -> PayloadSelection
- data Item a = Item {}
- newtype ThreadIdText = ThreadIdText {}
- data PayloadSelection
- data Scribe = Scribe {
- liPush :: forall a. LogItem a => Item a -> IO ()
- scribeFinalizer :: IO ()
- scribePermitItem :: PermitFunc
- data LogEnv = LogEnv {}
- data SimpleLogPayload
- sl :: ToJSON a => Text -> a -> SimpleLogPayload
- defaultScribeSettings :: ScribeSettings
- data ScribeSettings
- scribeBufferSize :: Lens' ScribeSettings Int
- _scribeBufferSize :: ScribeSettings -> Int
- itemApp :: forall a. Lens' (Item a) Namespace
- itemEnv :: forall a. Lens' (Item a) Environment
- itemSeverity :: forall a. Lens' (Item a) Severity
- itemThread :: forall a. Lens' (Item a) ThreadIdText
- itemHost :: forall a. Lens' (Item a) HostName
- itemProcess :: forall a. Lens' (Item a) ProcessID
- itemPayload :: forall a a. Lens (Item a) (Item a) a a
- itemMessage :: forall a. Lens' (Item a) LogStr
- itemTime :: forall a. Lens' (Item a) UTCTime
- itemNamespace :: forall a. Lens' (Item a) Namespace
- itemLoc :: forall a. Lens' (Item a) (Maybe Loc)
- logEnvHost :: Lens' LogEnv HostName
- logEnvPid :: Lens' LogEnv ProcessID
- logEnvApp :: Lens' LogEnv Namespace
- logEnvEnv :: Lens' LogEnv Environment
- logEnvTimer :: Lens' LogEnv (IO UTCTime)
- logEnvScribes :: Lens' LogEnv (Map Text ScribeHandle)
- newtype KatipT m a = KatipT {}
- runKatipT :: LogEnv -> KatipT m a -> m a
- initLogEnv :: Namespace -> Environment -> IO LogEnv
- registerScribe :: Text -> Scribe -> ScribeSettings -> LogEnv -> IO LogEnv
- unregisterScribe :: Text -> LogEnv -> LogEnv
- clearScribes :: LogEnv -> LogEnv
- closeScribes :: LogEnv -> IO LogEnv
- closeScribe :: Text -> LogEnv -> IO LogEnv
- newtype LogStr = LogStr {}
- logStr :: StringConv a Text => a -> LogStr
- ls :: StringConv a Text => a -> LogStr
- showLS :: Show a => a -> LogStr
- class MonadIO m => Katip m where
- getLogEnv :: m LogEnv
- localLogEnv :: (LogEnv -> LogEnv) -> m a -> m a
- logF :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Severity -> LogStr -> m ()
- logMsg :: (Applicative m, Katip m) => Namespace -> Severity -> LogStr -> m ()
- logT :: ExpQ
- logLoc :: (Applicative m, LogItem a, Katip m, HasCallStack) => a -> Namespace -> Severity -> LogStr -> m ()
- logItem :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Maybe Loc -> Severity -> LogStr -> m ()
- logKatipItem :: (Applicative m, LogItem a, Katip m) => Item a -> m ()
- logException :: (Katip m, LogItem a, MonadCatch m, Applicative m) => a -> Namespace -> Severity -> m b -> m b
- 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
- 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
- data AnyLogContext
- data LogContexts
- liftPayload :: LogItem a => a -> LogContexts
- katipAddNamespace :: KatipContext m => Namespace -> m a -> m a
- katipAddContext :: (LogItem i, KatipContext m) => i -> m a -> m a
- katipNoLogging :: Katip m => m a -> m a
- mkHandleScribe :: ColorStrategy -> Handle -> PermitFunc -> Verbosity -> IO Scribe
- mkHandleScribeWithFormatter :: (forall a. LogItem a => ItemFormatter a) -> ColorStrategy -> Handle -> PermitFunc -> Verbosity -> IO Scribe
- mkFileScribe :: FilePath -> PermitFunc -> Verbosity -> IO Scribe
- data ColorStrategy
- type ItemFormatter a = Bool -> Verbosity -> Item a -> Builder
- bracketFormat :: LogItem a => ItemFormatter a
- jsonFormat :: LogItem a => ItemFormatter a
- type PermitFunc = forall a. Item a -> IO Bool
- permitAND :: PermitFunc -> PermitFunc -> PermitFunc
- permitOR :: PermitFunc -> PermitFunc -> PermitFunc
- permitItem :: Monad m => Severity -> Item a -> m Bool
- payloadObject :: LogItem a => Verbosity -> a -> Object
- itemJson :: LogItem a => Verbosity -> Item a -> Value
- data KatipContextT m a
- runKatipContextT :: LogItem c => LogEnv -> c -> Namespace -> KatipContextT m a -> m a
Framework Types
Represents a heirarchy of namespaces going from general to specific. For instance: ["processname", "subsystem"]. Note that single-segment namespaces can be created using IsString/OverloadedStrings, so "foo" will result in Namespace ["foo"].
Namespace | |
|
Instances
FromJSON Namespace Source # | |
Defined in Katip.Core | |
ToJSON Namespace Source # | |
IsString Namespace Source # | |
Defined in Katip.Core fromString :: String -> Namespace # | |
Monoid Namespace Source # | |
Semigroup Namespace Source # | |
Generic Namespace Source # | |
Read Namespace Source # | |
Show Namespace Source # | |
Eq Namespace Source # | |
Ord Namespace Source # | |
Defined in Katip.Core | |
Lift Namespace Source # | |
type Rep Namespace Source # | |
Defined in Katip.Core |
newtype Environment Source #
Application environment, like prod
, devel
, testing
.
Instances
DebugS | Debug messages |
InfoS | Information |
NoticeS | Normal runtime Conditions |
WarningS | General Warnings |
ErrorS | General Errors |
CriticalS | Severe situations |
AlertS | Take immediate action |
EmergencyS | System is unusable |
Instances
FromJSON Severity Source # | |
Defined in Katip.Core | |
ToJSON Severity Source # | |
Bounded Severity Source # | |
Enum Severity Source # | |
Generic Severity Source # | |
Read Severity Source # | |
Show Severity Source # | |
Eq Severity Source # | |
Ord Severity Source # | |
Lift Severity Source # | |
type Rep Severity Source # | |
Defined in Katip.Core type Rep Severity = D1 ('MetaData "Severity" "Katip.Core" "katip-0.8.8.0-95MhLZz6WfQCivGava09U3" 'False) (((C1 ('MetaCons "DebugS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InfoS" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NoticeS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WarningS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CriticalS" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AlertS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmergencyS" 'PrefixI 'False) (U1 :: Type -> Type)))) |
renderSeverity :: Severity -> Text Source #
Verbosity controls the amount of information (columns) a Scribe
emits during logging.
The convention is:
- V0
implies no additional payload information is included in message.
- V3
implies the maximum amount of payload information.
- Anything in between is left to the discretion of the developer.
Instances
class ToObject a where Source #
Katip requires JSON objects to be logged as context. This
typeclass provides a default instance which uses ToJSON and
produces an empty object if toJSON
results in any type other than
object. If you have a type you want to log that produces an Array
or Number for example, you'll want to write an explicit instance
here. You can trivially add a ToObject instance for something with
a ToJSON instance like:
instance ToObject Foo
Nothing
Instances
ToObject Object Source # | |
ToObject SimpleLogPayload Source # | |
Defined in Katip.Core toObject :: SimpleLogPayload -> Object Source # | |
ToObject LogContexts Source # | |
Defined in Katip.Monadic toObject :: LogContexts -> Object Source # | |
ToObject () Source # | |
Defined in Katip.Core |
class ToObject a => LogItem a where Source #
Payload objects need instances of this class. LogItem makes it so
that you can have very verbose items getting logged with lots of
extra fields but under normal circumstances, if your scribe is
configured for a lower verbosity level, it will only log a
selection of those keys. Furthermore, each Scribe
can be
configured with a different Verbosity
level. You could even use
registerScribe
, unregisterScribe
, and clearScribes
to at
runtime swap out your existing scribes for more verbose debugging
scribes if you wanted to.
When defining payloadKeys
, don't redundantly declare the same
keys for higher levels of verbosity. Each level of verbosity
automatically and recursively contains all keys from the level
before it.
payloadKeys :: Verbosity -> a -> PayloadSelection Source #
List of keys in the JSON object that should be included in message.
Instances
LogItem SimpleLogPayload Source # | |
Defined in Katip.Core | |
LogItem LogContexts Source # | |
Defined in Katip.Monadic payloadKeys :: Verbosity -> LogContexts -> PayloadSelection Source # | |
LogItem () Source # | |
Defined in Katip.Core payloadKeys :: Verbosity -> () -> PayloadSelection Source # |
This has everything each log message will contain.
Item | |
|
Instances
newtype ThreadIdText Source #
Instances
data PayloadSelection Source #
Field selector by verbosity within JSON payload.
Instances
Monoid PayloadSelection Source # | |
Defined in Katip.Core | |
Semigroup PayloadSelection Source # | |
Defined in Katip.Core (<>) :: PayloadSelection -> PayloadSelection -> PayloadSelection # sconcat :: NonEmpty PayloadSelection -> PayloadSelection # stimes :: Integral b => b -> PayloadSelection -> PayloadSelection # | |
Show PayloadSelection Source # | |
Defined in Katip.Core showsPrec :: Int -> PayloadSelection -> ShowS # show :: PayloadSelection -> String # showList :: [PayloadSelection] -> ShowS # | |
Eq PayloadSelection Source # | |
Defined in Katip.Core (==) :: PayloadSelection -> PayloadSelection -> Bool # (/=) :: PayloadSelection -> PayloadSelection -> Bool # |
Scribe | |
|
LogEnv | |
|
data SimpleLogPayload Source #
Instances
ToJSON SimpleLogPayload Source # | A built-in convenience log payload that won't log anything on Construct using |
Defined in Katip.Core toJSON :: SimpleLogPayload -> Value # toEncoding :: SimpleLogPayload -> Encoding # toJSONList :: [SimpleLogPayload] -> Value # toEncodingList :: [SimpleLogPayload] -> Encoding # omitField :: SimpleLogPayload -> Bool # | |
Monoid SimpleLogPayload Source # | |
Defined in Katip.Core | |
Semigroup SimpleLogPayload Source # | |
Defined in Katip.Core (<>) :: SimpleLogPayload -> SimpleLogPayload -> SimpleLogPayload # sconcat :: NonEmpty SimpleLogPayload -> SimpleLogPayload # stimes :: Integral b => b -> SimpleLogPayload -> SimpleLogPayload # | |
LogItem SimpleLogPayload Source # | |
Defined in Katip.Core | |
ToObject SimpleLogPayload Source # | |
Defined in Katip.Core toObject :: SimpleLogPayload -> Object Source # |
defaultScribeSettings :: ScribeSettings Source #
Reasonable defaults for a scribe. Buffer size of 4096.
data ScribeSettings Source #
Instances
Show ScribeSettings Source # | |
Defined in Katip.Core showsPrec :: Int -> ScribeSettings -> ShowS # show :: ScribeSettings -> String # showList :: [ScribeSettings] -> ShowS # | |
Eq ScribeSettings Source # | |
Defined in Katip.Core (==) :: ScribeSettings -> ScribeSettings -> Bool # (/=) :: ScribeSettings -> ScribeSettings -> Bool # |
lens
-compatible Lenses
itemThread :: forall a. Lens' (Item a) ThreadIdText Source #
A Built-in Monad For Simple Logging
A concrete monad you can use to run logging actions. Use this if
you prefer an explicit monad transformer stack and adding layers as
opposed to implementing Katip
for your monad.
Instances
Initializing Loggers
:: Namespace | A base namespace for this application |
-> Environment | Current run environment (e.g. |
-> IO LogEnv |
Create a reasonable default InitLogEnv. Uses an AutoUpdate
which
updates the timer every 1ms. If you need even more timestamp
precision at the cost of performance, consider setting
_logEnvTimer
with getCurrentTime
.
Add a scribe to the list. All future log calls will go to this scribe in addition to the others. Writes will be buffered per the ScribeSettings to prevent slow scribes from slowing down logging. Writes will be dropped if the buffer fills.
Dropping scribes temporarily
Remove a scribe from the environment. This does not finalize
the scribe. This mainly only makes sense to use with something like
MonadReader's local
function to temporarily disavow a single
logger for a block of code.
clearScribes :: LogEnv -> LogEnv Source #
Unregister all scribes. Note that this is not for closing or
finalizing scribes, use closeScribes
for that. This mainly only
makes sense to use with something like MonadReader's local
function to temporarily disavow any loggers for a block of code.
Finalizing scribes at shutdown
closeScribes :: LogEnv -> IO LogEnv Source #
Call this at the end of your program. This is a blocking call that stop writing to a scribe's queue, waits for the queue to empty, finalizes each scribe in the log environment and then removes it. Finalizers are all run even if one of them throws, but the exception will be re-thrown at the end.
Finalize a scribe. The scribe is removed from the environment, its finalizer is called so that it can never be written to again and all pending writes are flushed. Note that this will throw any exceptions yoru finalizer will throw, and that LogEnv is immutable, so it will not be removed in that case.
Logging Functions
Log message with Builder underneath; use <>
to concat in O(1).
Katip
Logging Functions
These logging functions use the basic Katip
constraint and thus
will require varying degrees of explicit detail such as Namespace
and individual log items to be passed in. These can be described as
the primitives of Katip logging. If you find yourself making multiple
log statements within a logical logging context for your app, you may
want to look into the KatipContext
family of logging functions like
logFM
and logTM
. KatipContext
in most applications should be
considered the default. Here's an example of the pain point:
doDatabaseThings = do connId <- getConnectionId logF (ConnectionIDContext connId) "database" InfoS "Doing database stuff" -- ... logF (ConnectionIDContext connId) "database" InfoS "Wow, passing in the same context is getting tedious"
Another pain point to look out for is nesting actions that log in each other. Let's say you were writing a web app. You want to capture some detail such as the user's ID in the logs, but you also want that info to show up in doDatabaseThings' logs so you can associate those two pieces of information:
webRequestHandler = do uid <- getUserId logF (UserIDContext uid) "web" InfoS "Starting web request" doDatabaseThings
In the above example, doDatabaseThings would overwrite that
UserIDContext with its own context and namespace. Sometimes this is
what you want and that's why logF
and other functions which only
require Katip
exist. If you are interested in combining log
contexts and namespaces, see KatipContext
.
class MonadIO m => Katip m where Source #
Monads where katip logging actions can be performed. Katip is the most basic logging monad. You will typically use this directly if you either don't want to use namespaces/contexts heavily or if you want to pass in specific contexts and/or namespaces at each log site.
For something more powerful, look at the docs for KatipContext
,
which keeps a namespace and merged context. You can write simple
functions that add additional namespacing and merges additional
context on the fly.
localLogEnv
was added to allow for lexically-scoped modifications
of the log env that are reverted when the supplied monad
completes. katipNoLogging
, for example, uses this to temporarily
pause log outputs.
Instances
MonadIO m => Katip (KatipT m) Source # | |
MonadIO m => Katip (KatipContextT m) Source # | |
Defined in Katip.Monadic getLogEnv :: KatipContextT m LogEnv Source # localLogEnv :: (LogEnv -> LogEnv) -> KatipContextT m a -> KatipContextT m a Source # | |
MonadIO m => Katip (NoLoggingT m) Source # | |
Defined in Katip.Monadic getLogEnv :: NoLoggingT m LogEnv Source # localLogEnv :: (LogEnv -> LogEnv) -> NoLoggingT m a -> NoLoggingT m a Source # | |
Katip m => Katip (ResourceT m) Source # | |
Katip m => Katip (MaybeT m) Source # | |
Katip m => Katip (ExceptT s m) Source # | |
Katip m => Katip (ReaderT s m) Source # | |
Katip m => Katip (StateT s m) Source # | |
Katip m => Katip (StateT s m) Source # | |
(Katip m, Monoid s) => Katip (WriterT s m) Source # | |
(Katip m, Monoid s) => Katip (WriterT s m) Source # | |
(Katip m, Monoid w) => Katip (RWST r w s m) Source # | |
(Katip m, Monoid w) => Katip (RWST r w s m) Source # | |
:: (Applicative m, LogItem a, Katip m) | |
=> a | Contextual payload for the log |
-> Namespace | Specific namespace of the message. |
-> Severity | Severity of the message |
-> LogStr | The log message |
-> m () |
Log with full context, but without any code location.
logMsg :: (Applicative m, Katip m) => Namespace -> Severity -> LogStr -> m () Source #
Log a message without any payload/context or code location.
Loc
-tagged logging when using template-haskell.
$(logT) obj mempty InfoS "Hello world"
logLoc :: (Applicative m, LogItem a, Katip m, HasCallStack) => a -> Namespace -> Severity -> LogStr -> m () Source #
Loc
-tagged logging using Stack
when available.
This function does not require template-haskell as it
automatically uses implicit-callstacks
when the code is compiled using GHC > 7.8. Using an older version of the
compiler will result in the emission of a log line without any location information,
so be aware of it. Users using GHC <= 7.8 may want to use the template-haskell function
logT
for maximum compatibility.
logLoc obj mempty InfoS "Hello world"
logItem :: (Applicative m, LogItem a, Katip m) => a -> Namespace -> Maybe Loc -> Severity -> LogStr -> m () Source #
Log with everything, including a source code location. This is
very low level and you typically can use logT
in its place.
logKatipItem :: (Applicative m, LogItem a, Katip m) => Item a -> m () Source #
Log already constructed Item
. This is the lowest level function that other log*
functions use.
It can be useful when implementing centralised logging services.
:: (Katip m, LogItem a, MonadCatch m, Applicative m) | |
=> a | Log context |
-> Namespace | Namespace |
-> Severity | Severity |
-> m b | Main action being run |
-> m b |
Perform an action while logging any exceptions that may occur.
Inspired by onException
.
>>>
> logException () mempty ErrorS (error "foo")
KatipContext
: Logging With Context
These logging functions use the KatipContext
constraint which is a
superclass of Katip
that also has a mechanism for keeping track of
the current context and namespace. This means a few things:
- Functions that use
KatipContext
likelogFM
andlogTM
do not require you to pass inLogItem
s orNamespaces
, they pull them from the monadic environment. - It becomes easy to add functions which add namespaces and/or contexts to the current stack of them. You can (and should) make that action scoped to a monadic action so that when it finishes, the previous context and namespace will be automatically restored.
KatipContextT
provides a simple, ReaderT
-based implementation of
the KatipContext
typeclass, and provides katipAddContext
and
katipAddNamespace
functions to append to the context for the
duration of a block:
main = do le <- initLogEnv MyApp "production" -- set up scribes here runKatipContext le () "main" $ do katipAddNamespace "nextlevel" $ do $(logTM) InfoS "Logs here will have namespace MyApp.main.nextlevel" katipAddContext TrivialContext $ do $(logTM) InfoS "Logs here will have context from TrivialContext" katipAddContext AnotherContext $ do $(logTM) InfoS "Logs here will have context from TrivialContext *merged with* context from AnotherContext!" $(logTM) InfoS "Log context restored to () and namespace to MyApp.main"
katipAddNamespace
and katipAddContext
are one-liners, implemented
in terms of local
from MonadReader
. If you have a custom monad
transformer stack and want to add your own version of these, check out
<https://github.com/Soostone/katip/tree/master/katip/examples these
examples>.
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.
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
:: (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.
:: (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
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
ToJSON LogContexts Source # | |
Defined in Katip.Monadic toJSON :: LogContexts -> Value # toEncoding :: LogContexts -> Encoding # toJSONList :: [LogContexts] -> Value # toEncodingList :: [LogContexts] -> Encoding # omitField :: LogContexts -> Bool # | |
Monoid LogContexts Source # | |
Defined in Katip.Monadic mempty :: LogContexts # mappend :: LogContexts -> LogContexts -> LogContexts # mconcat :: [LogContexts] -> LogContexts # | |
Semigroup LogContexts Source # | |
Defined in Katip.Monadic (<>) :: LogContexts -> LogContexts -> LogContexts # sconcat :: NonEmpty LogContexts -> LogContexts # stimes :: Integral b => b -> LogContexts -> LogContexts # | |
LogItem LogContexts Source # | |
Defined in Katip.Monadic payloadKeys :: Verbosity -> LogContexts -> PayloadSelection Source # | |
ToObject LogContexts Source # | |
Defined in Katip.Monadic 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.
Temporarily Changing Logging Behavior
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.
katipNoLogging :: Katip m => m a -> m a Source #
Disable all scribes for the given monadic action, then restore them afterwards. Works in any Katip monad.
Included Scribes
mkHandleScribe :: ColorStrategy -> Handle -> PermitFunc -> Verbosity -> IO Scribe Source #
Logs to a file handle such as stdout, stderr, or a file. Contexts and other information will be flattened out into bracketed fields. For example:
[2016-05-11 21:01:15][MyApp][Info][myhost.example.com][PID 1724][ThreadId 1154][main:Helpers.Logging Helpers/Logging.hs:32:7] Started [2016-05-11 21:01:15][MyApp.confrabulation][Debug][myhost.example.com][PID 1724][ThreadId 1154][confrab_factor:42.0][main:Helpers.Logging Helpers/Logging.hs:41:9] Confrabulating widgets, with extra namespace and context [2016-05-11 21:01:15][MyApp][Info][myhost.example.com][PID 1724][ThreadId 1154][main:Helpers.Logging Helpers/Logging.hs:43:7] Namespace and context are back to normal
Returns the newly-created Scribe
. The finalizer flushes the
handle. Handle mode is set to LineBuffering
automatically.
mkHandleScribeWithFormatter :: (forall a. LogItem a => ItemFormatter a) -> ColorStrategy -> Handle -> PermitFunc -> Verbosity -> IO Scribe Source #
Logs to a file handle such as stdout, stderr, or a file. Takes a custom
ItemFormatter
that can be used to format Item
as needed.
Returns the newly-created Scribe
. The finalizer flushes the
handle. Handle mode is set to LineBuffering
automatically.
mkFileScribe :: FilePath -> PermitFunc -> Verbosity -> IO Scribe Source #
A specialization of mkHandleScribe
that takes a FilePath
instead of a Handle
. It is responsible for opening the file in
AppendMode
and will close the file handle on
closeScribe
/closeScribes
. Does not do log coloring. Sets handle
to LineBuffering
mode.
data ColorStrategy Source #
ColorLog Bool | Whether to use color control chars in log output |
ColorIfTerminal | Color if output is a terminal |
Instances
Show ColorStrategy Source # | |
Defined in Katip.Scribes.Handle showsPrec :: Int -> ColorStrategy -> ShowS # show :: ColorStrategy -> String # showList :: [ColorStrategy] -> ShowS # | |
Eq ColorStrategy Source # | |
Defined in Katip.Scribes.Handle (==) :: ColorStrategy -> ColorStrategy -> Bool # (/=) :: ColorStrategy -> ColorStrategy -> Bool # |
type ItemFormatter a = Bool -> Verbosity -> Item a -> Builder Source #
A custom ItemFormatter for logging Item
s. Takes a Value
indicating
whether to colorize the output, Verbosity
of output, and an Item
to
format.
See bracketFormat
and jsonFormat
for examples.
bracketFormat :: LogItem a => ItemFormatter a Source #
A traditional bracketed
log format. Contexts and other information will
be flattened out into bracketed fields. For example:
[2016-05-11 21:01:15][MyApp][Info][myhost.example.com][PID 1724][ThreadId 1154][main:Helpers.Logging Helpers/Logging.hs:32:7] Started [2016-05-11 21:01:15][MyApp.confrabulation][Debug][myhost.example.com][PID 1724][ThreadId 1154][confrab_factor:42.0][main:Helpers.Logging Helpers/Logging.hs:41:9] Confrabulating widgets, with extra namespace and context [2016-05-11 21:01:15][MyApp][Info][myhost.example.com][PID 1724][ThreadId 1154][main:Helpers.Logging Helpers/Logging.hs:43:7] Namespace and context are back to normal
jsonFormat :: LogItem a => ItemFormatter a Source #
Logs items as JSON. This can be useful in circumstances where you already have infrastructure that is expecting JSON to be logged to a standard stream or file. For example:
{"at":"2018-10-02T21:50:30.4523848Z","env":"production","ns":["MyApp"],"data":{},"app":["MyApp"],"msg":"Started","pid":"10456","loc":{"loc_col":9,"loc_pkg":"main","loc_mod":"Helpers.Logging","loc_fn":"Helpers\\Logging.hs","loc_ln":44},"host":"myhost.example.com","sev":"Info","thread":"ThreadId 139"} {"at":"2018-10-02T21:50:30.4523848Z","env":"production","ns":["MyApp","confrabulation"],"data":{"confrab_factor":42},"app":["MyApp"],"msg":"Confrabulating widgets, with extra namespace and context","pid":"10456","loc":{"loc_col":11,"loc_pkg":"main","loc_mod":"Helpers.Logging","loc_fn":"Helpers\\Logging.hs","loc_ln":53},"host":"myhost.example.com","sev":"Debug","thread":"ThreadId 139"} {"at":"2018-10-02T21:50:30.4523848Z","env":"production","ns":["MyApp"],"data":{},"app":["MyApp"],"msg":"Namespace and context are back to normal","pid":"10456","loc":{"loc_col":9,"loc_pkg":"main","loc_mod":"Helpers.Logging","loc_fn":"Helpers\\Logging.hs","loc_ln":55},"host":"myhost.example.com","sev":"Info","thread":"ThreadId 139"}
Tools for implementing Scribes
type PermitFunc = forall a. Item a -> IO Bool Source #
Scribes are handlers of incoming items. Each registered scribe knows how to push a log item somewhere.
Guidelines for writing your own Scribe
Scribes should always take a Severity
and Verbosity
.
Severity is used to exclude log messages that are lower than
the provided Severity. For instance, if the user passes InfoS,
DebugS items should be ignored. Katip provides the permitItem
utility for this. The user or the scribe may use permitAND
and
permitOR
to further customize this filtering, even dynamically if
they wish to.
Verbosity is used to select keys from the log item's payload. Each
LogItem
instance describes what keys should be retained for each
Verbosity level. Use the payloadObject
utility for extracting the keys
that should be written.
Scribes provide a finalizer IO action (scribeFinalizer
) that is
meant to synchronously flush any remaining writes and clean up any
resources acquired when the scribe was created. Internally, katip
keeps a buffer for each scribe's writes. When closeScribe
or
closeScribes
is called, that buffer stops accepting new log
messages and after the last item in its buffer is sent to liPush
,
calls the finalizer. Thus, when the finalizer returns, katip can
assume that all resources are cleaned up and all log messages are
durably written.
While katip internally buffers messages per ScribeSettings
, it
sends them one at a time to the scribe. Depending on the scribe
itself, it may make sense for that scribe to keep its own internal
buffer to batch-send logs if writing items one at a time is not
efficient. The scribe implementer must be sure that on
finalization, all writes are committed synchronously.
Signature of a function passed to Scribe
constructor and
mkScribe* functions that decides which messages to be
logged. Typically filters based on Severity
, but can be
combined with other, custom logic with permitAND
and permitOR
permitAND :: PermitFunc -> PermitFunc -> PermitFunc Source #
AND together 2 permit functions
permitOR :: PermitFunc -> PermitFunc -> PermitFunc Source #
OR together 2 permit functions
permitItem :: Monad m => Severity -> Item a -> m Bool Source #
Should this item be logged given the user's maximum severity?
Most new scribes will use this as a base for their PermitFunc
payloadObject :: LogItem a => Verbosity -> a -> Object Source #
Constrain payload based on verbosity. Backends should use this to automatically bubble higher verbosity levels to lower ones.
itemJson :: LogItem a => Verbosity -> Item a -> Value Source #
Convert log item to its JSON representation while trimming its payload based on the desired verbosity. Backends that push JSON messages should use this to obtain their payload.
KatipContextT - Utility transformer that provides Katip and KatipContext instances
data 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
Instances
runKatipContextT :: LogItem c => LogEnv -> c -> Namespace -> KatipContextT m a -> m a Source #