katip-0.8.5.0: A structured logging framework.

Safe HaskellNone
LanguageHaskell2010

Katip

Contents

Description

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:

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!"

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 using initLogEnv.
  • Add Scribes using registerScribe.
  • Either use KatipT or KatipContextT for a pre-built transformer stack or add Katip and KatipContext instances to your own transformer stack. If you do the latter, you may want to look in the examples dir for some tips on composing contexts and namespaces.
  • Define some structured log data throughout your application and implement ToObject and LogItem 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

Framework Types

newtype Namespace Source #

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"].

Constructors

Namespace 

Fields

Instances
Eq Namespace Source # 
Instance details

Defined in Katip.Core

Ord Namespace Source # 
Instance details

Defined in Katip.Core

Read Namespace Source # 
Instance details

Defined in Katip.Core

Show Namespace Source # 
Instance details

Defined in Katip.Core

IsString Namespace Source # 
Instance details

Defined in Katip.Core

Generic Namespace Source # 
Instance details

Defined in Katip.Core

Associated Types

type Rep Namespace :: Type -> Type #

Semigroup Namespace Source # 
Instance details

Defined in Katip.Core

Monoid Namespace Source # 
Instance details

Defined in Katip.Core

Lift Namespace Source # 
Instance details

Defined in Katip.Core

Methods

lift :: Namespace -> Q Exp #

ToJSON Namespace Source # 
Instance details

Defined in Katip.Core

FromJSON Namespace Source # 
Instance details

Defined in Katip.Core

type Rep Namespace Source # 
Instance details

Defined in Katip.Core

type Rep Namespace = D1 (MetaData "Namespace" "Katip.Core" "katip-0.8.5.0-L71m4manfVnHjtNmXtAPdW" True) (C1 (MetaCons "Namespace" PrefixI True) (S1 (MetaSel (Just "unNamespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])))

newtype Environment Source #

Application environment, like prod, devel, testing.

Constructors

Environment 

Fields

Instances
Eq Environment Source # 
Instance details

Defined in Katip.Core

Ord Environment Source # 
Instance details

Defined in Katip.Core

Read Environment Source # 
Instance details

Defined in Katip.Core

Show Environment Source # 
Instance details

Defined in Katip.Core

IsString Environment Source # 
Instance details

Defined in Katip.Core

Generic Environment Source # 
Instance details

Defined in Katip.Core

Associated Types

type Rep Environment :: Type -> Type #

ToJSON Environment Source # 
Instance details

Defined in Katip.Core

FromJSON Environment Source # 
Instance details

Defined in Katip.Core

type Rep Environment Source # 
Instance details

Defined in Katip.Core

type Rep Environment = D1 (MetaData "Environment" "Katip.Core" "katip-0.8.5.0-L71m4manfVnHjtNmXtAPdW" True) (C1 (MetaCons "Environment" PrefixI True) (S1 (MetaSel (Just "getEnvironment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Severity Source #

Constructors

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
Bounded Severity Source # 
Instance details

Defined in Katip.Core

Enum Severity Source # 
Instance details

Defined in Katip.Core

Eq Severity Source # 
Instance details

Defined in Katip.Core

Ord Severity Source # 
Instance details

Defined in Katip.Core

Read Severity Source # 
Instance details

Defined in Katip.Core

Show Severity Source # 
Instance details

Defined in Katip.Core

Generic Severity Source # 
Instance details

Defined in Katip.Core

Associated Types

type Rep Severity :: Type -> Type #

Methods

from :: Severity -> Rep Severity x #

to :: Rep Severity x -> Severity #

Lift Severity Source # 
Instance details

Defined in Katip.Core

Methods

lift :: Severity -> Q Exp #

ToJSON Severity Source # 
Instance details

Defined in Katip.Core

FromJSON Severity Source # 
Instance details

Defined in Katip.Core

type Rep Severity Source # 
Instance details

Defined in Katip.Core

type Rep Severity = D1 (MetaData "Severity" "Katip.Core" "katip-0.8.5.0-L71m4manfVnHjtNmXtAPdW" 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))))

data Verbosity 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.

Constructors

V0 
V1 
V2 
V3 
Instances
Bounded Verbosity Source # 
Instance details

Defined in Katip.Core

Enum Verbosity Source # 
Instance details

Defined in Katip.Core

Eq Verbosity Source # 
Instance details

Defined in Katip.Core

Ord Verbosity Source # 
Instance details

Defined in Katip.Core

Read Verbosity Source # 
Instance details

Defined in Katip.Core

Show Verbosity Source # 
Instance details

Defined in Katip.Core

Generic Verbosity Source # 
Instance details

Defined in Katip.Core

Associated Types

type Rep Verbosity :: Type -> Type #

Lift Verbosity Source # 
Instance details

Defined in Katip.Core

Methods

lift :: Verbosity -> Q Exp #

ToJSON Verbosity Source # 
Instance details

Defined in Katip.Core

FromJSON Verbosity Source # 
Instance details

Defined in Katip.Core

type Rep Verbosity Source # 
Instance details

Defined in Katip.Core

type Rep Verbosity = D1 (MetaData "Verbosity" "Katip.Core" "katip-0.8.5.0-L71m4manfVnHjtNmXtAPdW" False) ((C1 (MetaCons "V0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "V1" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "V2" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "V3" PrefixI False) (U1 :: Type -> Type)))

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

Minimal complete definition

Nothing

Methods

toObject :: a -> Object Source #

toObject :: ToJSON a => a -> Object Source #

Instances
ToObject () Source # 
Instance details

Defined in Katip.Core

Methods

toObject :: () -> Object Source #

ToObject Object Source # 
Instance details

Defined in Katip.Core

ToObject SimpleLogPayload Source # 
Instance details

Defined in Katip.Core

ToObject LogContexts Source # 
Instance details

Defined in Katip.Monadic

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.

Methods

payloadKeys :: Verbosity -> a -> PayloadSelection Source #

List of keys in the JSON object that should be included in message.

Instances
LogItem () Source # 
Instance details

Defined in Katip.Core

LogItem SimpleLogPayload Source # 
Instance details

Defined in Katip.Core

LogItem LogContexts Source # 
Instance details

Defined in Katip.Monadic

data Item a Source #

This has everything each log message will contain.

Instances
Functor Item Source # 
Instance details

Defined in Katip.Core

Methods

fmap :: (a -> b) -> Item a -> Item b #

(<$) :: a -> Item b -> Item a #

Eq a => Eq (Item a) Source # 
Instance details

Defined in Katip.Core

Methods

(==) :: Item a -> Item a -> Bool #

(/=) :: Item a -> Item a -> Bool #

Show a => Show (Item a) Source # 
Instance details

Defined in Katip.Core

Methods

showsPrec :: Int -> Item a -> ShowS #

show :: Item a -> String #

showList :: [Item a] -> ShowS #

Generic (Item a) Source # 
Instance details

Defined in Katip.Core

Associated Types

type Rep (Item a) :: Type -> Type #

Methods

from :: Item a -> Rep (Item a) x #

to :: Rep (Item a) x -> Item a #

ToJSON a => ToJSON (Item a) Source # 
Instance details

Defined in Katip.Core

FromJSON a => FromJSON (Item a) Source # 
Instance details

Defined in Katip.Core

type Rep (Item a) Source # 
Instance details

Defined in Katip.Core

data Scribe Source #

Constructors

Scribe 

Fields

  • liPush :: forall a. LogItem a => Item a -> IO ()

    How do we write an item to the scribe's output?

  • scribeFinalizer :: IO ()

    Provide a blocking finalizer to call when your scribe is removed. All pending writes should be flushed synchronously. If this is not relevant to your scribe, return () is fine.

  • scribePermitItem :: PermitFunc

    Provide a filtering function to allow the item to be logged, or not. It can check Severity or some string in item's body. The initial value of this is usually created from permitItem. Scribes and users can customize this by ANDing or ORing onto the default with permitAND or permitOR

Instances
Semigroup Scribe Source #

Combine two scribes. Publishes to the left scribe if the left would permit the item and to the right scribe if the right would permit the item. Finalizers are called in sequence from left to right.

Instance details

Defined in Katip.Core

Monoid Scribe Source # 
Instance details

Defined in Katip.Core

data LogEnv Source #

Constructors

LogEnv 

Fields

data SimpleLogPayload Source #

Instances
Semigroup SimpleLogPayload Source # 
Instance details

Defined in Katip.Core

Monoid SimpleLogPayload Source # 
Instance details

Defined in Katip.Core

ToJSON SimpleLogPayload Source #

A built-in convenience log payload that won't log anything on V0, but will log everything in any other level of verbosity. Intended for easy in-line usage without having to define new log types.

Construct using sl and combine multiple tuples using <> from Monoid.

Instance details

Defined in Katip.Core

LogItem SimpleLogPayload Source # 
Instance details

Defined in Katip.Core

ToObject SimpleLogPayload Source # 
Instance details

Defined in Katip.Core

sl :: ToJSON a => Text -> a -> SimpleLogPayload Source #

Construct a simple log from any JSON item.

defaultScribeSettings :: ScribeSettings Source #

Reasonable defaults for a scribe. Buffer size of 4096.

lens-compatible Lenses

itemApp :: forall a. Lens' (Item a) Namespace Source #

itemHost :: forall a. Lens' (Item a) HostName Source #

itemPayload :: forall a a. Lens (Item a) (Item a) a a Source #

itemMessage :: forall a. Lens' (Item a) LogStr Source #

itemTime :: forall a. Lens' (Item a) UTCTime Source #

itemLoc :: forall a. Lens' (Item a) (Maybe Loc) Source #

A Built-in Monad For Simple Logging

newtype KatipT m a Source #

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.

Constructors

KatipT 

Fields

Instances
MonadTrans KatipT Source # 
Instance details

Defined in Katip.Core

Methods

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

MonadTransControl KatipT Source # 
Instance details

Defined in Katip.Core

Associated Types

type StT KatipT a :: Type #

Methods

liftWith :: Monad m => (Run KatipT -> m a) -> KatipT m a #

restoreT :: Monad m => m (StT KatipT a) -> KatipT m a #

MonadBase b m => MonadBase b (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

liftBase :: b α -> KatipT m α #

MonadBaseControl b m => MonadBaseControl b (KatipT m) Source # 
Instance details

Defined in Katip.Core

Associated Types

type StM (KatipT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (KatipT m) b -> b a) -> KatipT m a #

restoreM :: StM (KatipT m) a -> KatipT m a #

Monad m => Monad (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

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

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

return :: a -> KatipT m a #

fail :: String -> KatipT m a #

Functor m => Functor (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

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

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

MonadFail m => MonadFail (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

fail :: String -> KatipT m a #

Applicative m => Applicative (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

pure :: a -> KatipT m a #

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

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

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

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

MonadIO m => MonadIO (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

liftIO :: IO a -> KatipT m a #

MonadThrow m => MonadThrow (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

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

MonadCatch m => MonadCatch (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

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

MonadMask m => MonadMask (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

mask :: ((forall a. KatipT m a -> KatipT m a) -> KatipT m b) -> KatipT m b #

uninterruptibleMask :: ((forall a. KatipT m a -> KatipT m a) -> KatipT m b) -> KatipT m b #

generalBracket :: KatipT m a -> (a -> ExitCase b -> KatipT m c) -> (a -> KatipT m b) -> KatipT m (b, c) #

MonadResource m => MonadResource (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

liftResourceT :: ResourceT IO a -> KatipT m a #

MonadUnliftIO m => MonadUnliftIO (KatipT m) Source # 
Instance details

Defined in Katip.Core

Methods

withRunInIO :: ((forall a. KatipT m a -> IO a) -> IO b) -> KatipT m b #

MonadIO m => Katip (KatipT m) Source # 
Instance details

Defined in Katip.Core

(Monad m, KatipContext m) => KatipContext (KatipT m) Source # 
Instance details

Defined in Katip.Monadic

type StT KatipT a Source # 
Instance details

Defined in Katip.Core

type StT KatipT a = a
type StM (KatipT m) a Source # 
Instance details

Defined in Katip.Core

type StM (KatipT m) a = ComposeSt KatipT m a

runKatipT :: LogEnv -> KatipT m a -> m a Source #

Execute KatipT on a log env.

Initializing Loggers

initLogEnv Source #

Arguments

:: Namespace

A base namespace for this application

-> Environment

Current run environment (e.g. prod vs. devel)

-> IO LogEnv 

Create a reasonable default InitLogEnv. Uses an AutoUdate which updates the timer every 1ms. If you need even more timestamp precision at the cost of performance, consider setting _logEnvTimer with getCurrentTime.

registerScribe Source #

Arguments

:: Text

Name the scribe

-> Scribe 
-> ScribeSettings 
-> LogEnv 
-> IO LogEnv 

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

unregisterScribe Source #

Arguments

:: Text

Name of the scribe

-> LogEnv 
-> LogEnv 

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.

closeScribe Source #

Arguments

:: Text

Name of the scribe

-> LogEnv 
-> IO LogEnv 

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

newtype LogStr Source #

Log message with Builder underneath; use <> to concat in O(1).

Constructors

LogStr 

Fields

Instances
Eq LogStr Source # 
Instance details

Defined in Katip.Core

Methods

(==) :: LogStr -> LogStr -> Bool #

(/=) :: LogStr -> LogStr -> Bool #

Show LogStr Source # 
Instance details

Defined in Katip.Core

IsString LogStr Source # 
Instance details

Defined in Katip.Core

Methods

fromString :: String -> LogStr #

Generic LogStr Source # 
Instance details

Defined in Katip.Core

Associated Types

type Rep LogStr :: Type -> Type #

Methods

from :: LogStr -> Rep LogStr x #

to :: Rep LogStr x -> LogStr #

Semigroup LogStr Source # 
Instance details

Defined in Katip.Core

Monoid LogStr Source # 
Instance details

Defined in Katip.Core

FromJSON LogStr Source # 
Instance details

Defined in Katip.Core

type Rep LogStr Source # 
Instance details

Defined in Katip.Core

type Rep LogStr = D1 (MetaData "LogStr" "Katip.Core" "katip-0.8.5.0-L71m4manfVnHjtNmXtAPdW" True) (C1 (MetaCons "LogStr" PrefixI True) (S1 (MetaSel (Just "unLogStr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Builder)))

logStr :: StringConv a Text => a -> LogStr Source #

Pack any string-like thing into a LogStr. This will automatically work on String, ByteString, Text and any of the lazy variants.

ls :: StringConv a Text => a -> LogStr Source #

Shorthand for logStr

showLS :: Show a => a -> LogStr Source #

Convert any showable type into a LogStr.

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.

Methods

getLogEnv :: m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> m a -> m a Source #

Instances
Katip m => Katip (MaybeT m) Source # 
Instance details

Defined in Katip.Core

Katip m => Katip (ResourceT m) Source # 
Instance details

Defined in Katip.Core

MonadIO m => Katip (KatipT m) Source # 
Instance details

Defined in Katip.Core

MonadIO m => Katip (NoLoggingT m) Source # 
Instance details

Defined in Katip.Monadic

MonadIO m => Katip (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Katip m => Katip (ExceptT s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: ExceptT s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> ExceptT s m a -> ExceptT s m a Source #

(Katip m, Monoid s) => Katip (WriterT s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: WriterT s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> WriterT s m a -> WriterT s m a Source #

Katip m => Katip (StateT s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: StateT s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> StateT s m a -> StateT s m a Source #

Katip m => Katip (StateT s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: StateT s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> StateT s m a -> StateT s m a Source #

(Katip m, Monoid s) => Katip (WriterT s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: WriterT s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> WriterT s m a -> WriterT s m a Source #

Katip m => Katip (ReaderT s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: ReaderT s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> ReaderT s m a -> ReaderT s m a Source #

(Katip m, Monoid w) => Katip (RWST r w s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: RWST r w s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> RWST r w s m a -> RWST r w s m a Source #

(Katip m, Monoid w) => Katip (RWST r w s m) Source # 
Instance details

Defined in Katip.Core

Methods

getLogEnv :: RWST r w s m LogEnv Source #

localLogEnv :: (LogEnv -> LogEnv) -> RWST r w s m a -> RWST r w s m a Source #

logF Source #

Arguments

:: (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.

logT :: ExpQ Source #

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.

logException Source #

Arguments

:: (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:

  1. Functions that use KatipContext like logFM and logTM do not require you to pass in LogItems or Namespaces, they pull them from the monadic environment.
  2. 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.

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
(KatipContext m, Katip (MaybeT m)) => KatipContext (MaybeT m) Source # 
Instance details

Defined in Katip.Monadic

(KatipContext m, Katip (ResourceT m)) => KatipContext (ResourceT m) Source # 
Instance details

Defined in Katip.Monadic

(Monad m, KatipContext m) => KatipContext (KatipT m) Source # 
Instance details

Defined in Katip.Monadic

MonadIO m => KatipContext (NoLoggingT m) Source # 
Instance details

Defined in Katip.Monadic

MonadIO m => KatipContext (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

(KatipContext m, Katip (IdentityT m)) => KatipContext (IdentityT m) Source # 
Instance details

Defined in Katip.Monadic

(KatipContext m, Katip (ExceptT e m)) => KatipContext (ExceptT e m) Source # 
Instance details

Defined in Katip.Monadic

(Monoid w, KatipContext m, Katip (WriterT w m)) => KatipContext (WriterT w m) Source # 
Instance details

Defined in Katip.Monadic

(KatipContext m, Katip (StateT s m)) => KatipContext (StateT s m) Source # 
Instance details

Defined in Katip.Monadic

(KatipContext m, Katip (StateT s m)) => KatipContext (StateT s m) Source # 
Instance details

Defined in Katip.Monadic

(Monoid w, KatipContext m, Katip (WriterT w m)) => KatipContext (WriterT w m) Source # 
Instance details

Defined in Katip.Monadic

(KatipContext m, Katip (ReaderT r m)) => KatipContext (ReaderT r m) Source # 
Instance details

Defined in Katip.Monadic

(Monoid w, KatipContext m, Katip (RWST r w s m)) => KatipContext (RWST r w s m) Source # 
Instance details

Defined in Katip.Monadic

(Monoid w, KatipContext m, Katip (RWST r w s m)) => KatipContext (RWST r w s m) Source # 
Instance details

Defined in Katip.Monadic

logFM Source #

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.

logTM :: ExpQ Source #

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.

Location will be logged from the module that invokes logLocM so be aware that wrapping logLocM will make location reporting useless.

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.

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

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.

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 #

Constructors

ColorLog Bool

Whether to use color control chars in log output

ColorIfTerminal

Color if output is a terminal

type ItemFormatter a = Bool -> Verbosity -> Item a -> Builder Source #

A custom ItemFormatter for logging Items. 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
MonadTrans KatipContextT Source # 
Instance details

Defined in Katip.Monadic

Methods

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

MonadTransControl KatipContextT Source # 
Instance details

Defined in Katip.Monadic

Associated Types

type StT KatipContextT a :: Type #

Methods

liftWith :: Monad m => (Run KatipContextT -> m a) -> KatipContextT m a #

restoreT :: Monad m => m (StT KatipContextT a) -> KatipContextT m a #

MonadBase b m => MonadBase b (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

liftBase :: b α -> KatipContextT m α #

MonadBaseControl b m => MonadBaseControl b (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Associated Types

type StM (KatipContextT m) a :: Type #

MonadWriter w m => MonadWriter w (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

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

tell :: w -> KatipContextT m () #

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

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

MonadState s m => MonadState s (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

get :: KatipContextT m s #

put :: s -> KatipContextT m () #

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

MonadReader r m => MonadReader r (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

ask :: KatipContextT m r #

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

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

MonadError e m => MonadError e (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

throwError :: e -> KatipContextT m a #

catchError :: KatipContextT m a -> (e -> KatipContextT m a) -> KatipContextT m a #

Monad m => Monad (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

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

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

return :: a -> KatipContextT m a #

fail :: String -> KatipContextT m a #

Functor m => Functor (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

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

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

MonadFix m => MonadFix (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

mfix :: (a -> KatipContextT m a) -> KatipContextT m a #

MonadFail m => MonadFail (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

fail :: String -> KatipContextT m a #

Applicative m => Applicative (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

pure :: a -> KatipContextT m a #

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

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

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

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

Alternative m => Alternative (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

MonadPlus m => MonadPlus (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

MonadIO m => MonadIO (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

liftIO :: IO a -> KatipContextT m a #

MonadThrow m => MonadThrow (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

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

MonadCatch m => MonadCatch (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

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

MonadMask m => MonadMask (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

mask :: ((forall a. KatipContextT m a -> KatipContextT m a) -> KatipContextT m b) -> KatipContextT m b #

uninterruptibleMask :: ((forall a. KatipContextT m a -> KatipContextT m a) -> KatipContextT m b) -> KatipContextT m b #

generalBracket :: KatipContextT m a -> (a -> ExitCase b -> KatipContextT m c) -> (a -> KatipContextT m b) -> KatipContextT m (b, c) #

MonadResource m => MonadResource (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

MonadUnliftIO m => MonadUnliftIO (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

Methods

withRunInIO :: ((forall a. KatipContextT m a -> IO a) -> IO b) -> KatipContextT m b #

MonadIO m => Katip (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

MonadIO m => KatipContext (KatipContextT m) Source # 
Instance details

Defined in Katip.Monadic

type StT KatipContextT a Source # 
Instance details

Defined in Katip.Monadic

type StM (KatipContextT m) a Source # 
Instance details

Defined in Katip.Monadic