lumberjack-0.1.0.0: Trek through your code forest and make logs

Copyright(c) Galois Inc. 2020
Maintainerkquick@galois.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Lumberjack

Contents

Description

|

This module defines a general logging facility that can be used to output log messages to various targets.

Synopsis

Interface for Logging

newtype LogAction m msg Source #

The LogAction holds the ability to log a message of type msg (the second parameter) via a monad m (the first parameter).

LogActions are semigroup and monoid combineable, which results in both LogActions being taken (or no action in the case of mempty), and contravariant to allow the msg to be modified via function prior to being logged (as well as Divisible and Decidable).

Constructors

LogAction 

Fields

Instances
Contravariant (LogAction m) Source # 
Instance details

Defined in Lumberjack

Methods

contramap :: (a -> b) -> LogAction m b -> LogAction m a #

(>$) :: b -> LogAction m b -> LogAction m a #

Applicative m => Divisible (LogAction m) Source # 
Instance details

Defined in Lumberjack

Methods

divide :: (a -> (b, c)) -> LogAction m b -> LogAction m c -> LogAction m a #

conquer :: LogAction m a #

Applicative m => Decidable (LogAction m) Source # 
Instance details

Defined in Lumberjack

Methods

lose :: (a -> Void) -> LogAction m a #

choose :: (a -> Either b c) -> LogAction m b -> LogAction m c -> LogAction m a #

Applicative m => Semigroup (LogAction m a) Source # 
Instance details

Defined in Lumberjack

Methods

(<>) :: LogAction m a -> LogAction m a -> LogAction m a #

sconcat :: NonEmpty (LogAction m a) -> LogAction m a #

stimes :: Integral b => b -> LogAction m a -> LogAction m a #

Applicative m => Monoid (LogAction m a) Source # 
Instance details

Defined in Lumberjack

Methods

mempty :: LogAction m a #

mappend :: LogAction m a -> LogAction m a -> LogAction m a #

mconcat :: [LogAction m a] -> LogAction m a #

class Monad m => HasLog msg m where Source #

Any monad which will support retrieving or adjusting a LogAction must support the HasLog class.

Methods

getLogAction :: m (LogAction m msg) Source #

class (Monad m, HasLog msg m) => LoggingMonad msg m where Source #

Methods

adjustLogAction :: (forall k. LogAction k msg -> LogAction k msg) -> m a -> m a Source #

writeLogM :: HasLog msg m => msg -> m () Source #

This invokes the LogAction's logging handler in a monadic context where the logging handler can be retrieved via the HasLog class's getLogAction function.

Logging Utilities

safeLogAction :: MonadCatch m => LogAction m msg -> LogAction m msg Source #

Ensures that the LogAction does not fail if the logging operation itself throws an exception (the exception is ignored).

logFilter :: Applicative m => (msg -> Bool) -> LogAction m msg -> LogAction m msg Source #

The logFilter can be used on a LogAction to determine which messages the LogAction should be invoked for (only those for which the filter function returns True).

Default LogMessage

data Severity Source #

The Severity indicates the relative importance of the logging message. This can be useful for filtering log messages.

Constructors

Debug 
Info 
Warning 
Error 
Instances
Eq Severity Source # 
Instance details

Defined in Lumberjack

Ord Severity Source # 
Instance details

Defined in Lumberjack

Show Severity Source # 
Instance details

Defined in Lumberjack

Pretty Severity Source # 
Instance details

Defined in Lumberjack

Methods

pretty :: Severity -> Doc ann #

prettyList :: [Severity] -> Doc ann #

data LogType Source #

The LogType indicates what type of message this is. These are printed on the log line and can be used for filtering different types of log messages.

Instances
Eq LogType Source # 
Instance details

Defined in Lumberjack

Methods

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

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

Show LogType Source # 
Instance details

Defined in Lumberjack

Pretty LogType Source # 
Instance details

Defined in Lumberjack

Methods

pretty :: LogType -> Doc ann #

prettyList :: [LogType] -> Doc ann #

data LogMessage Source #

Each logged output is described by a LogMessage object.

Constructors

LogMessage 
Instances
Semigroup LogMessage Source # 
Instance details

Defined in Lumberjack

Monoid LogMessage Source # 
Instance details

Defined in Lumberjack

Pretty LogMessage Source # 
Instance details

Defined in Lumberjack

Methods

pretty :: LogMessage -> Doc ann #

prettyList :: [LogMessage] -> Doc ann #

msgWith :: LogMessage Source #

Helper routine to return an empty LogMessage, whose fields can then be updated.

type WithLog msg m = HasLog msg m Source #

This type is a Constraint that should be applied to any client function that will perform logging in a monad context. The msg is the type of message that will be logged, and the m is the monad under which the logging is performed.

withLogTag :: LoggingMonad LogMessage m => Text -> Text -> m a -> m a Source #

Log messages can have any number of key/value tags applied to them. This function establishes a new key/value tag pair that will be in effect for the monadic operation passed as the third argument. withLogTag tname tval op = local (adjustLogAction $ addLogTag tname tval) op

addLogActionTime :: MonadIO m => LogAction m LogMessage -> LogAction m LogMessage Source #

Add the current timestamp to the LogMessage being logged

Output formatting for LogMessage

cvtLogMessageToPlainText :: LogMessage -> Text Source #

Standard function for converting a LogMessage into plain Text (no colors or bolding, just text). This can be used as the default converter for a logger (via contramap).

cvtLogMessageToANSITermText :: LogMessage -> Text Source #

Standard function to convert a LogMessage into Text with ANSI terminal colors and bolding and other styling. This can be used as the default converter for a logger (via contramap).

Helpers and convenience functions

logFunctionCall :: MonadIO m => LogAction m LogMessage -> Text -> m a -> m a Source #

A wrapper for a monadic function call that will log on entry (Debug) and exit (Info) from the function, and note the total amount of time taken during execution of the function. Note that no strictness is applied to the internal monadic operation, so the time taken may be misleading. Like logFunctionCallM but needs an explicit LogAction whereas logFunctionCallM will retrieve the LogAction from the current monadic context.

logFunctionCallM :: (MonadIO m, WithLog LogMessage m) => Text -> m a -> m a Source #

A wrapper for a monadic function call that will log on entry (Debug) and exit (Info) from the function, and note the total amount of time taken during execution of the function. Note that no strictness is applied to the internal monadic operation, so the time taken may be misleading.

logProgress :: MonadIO m => LogAction m LogMessage -> Text -> m () Source #

Called to output a log message to indicate that some progress has been made.

logProgressM :: (MonadIO m, WithLog LogMessage m) => Text -> m () Source #

Called to output a log message within a Logging monad to indicate that some progress has been made.

tshow :: Show a => a -> Text Source #

This is a helper because the LogMessage normally wants a Text, but show delivers a String.

defaultGetIOLogAction :: MonadIO m => LogAction m Text Source #

When using a simple IO monad, there is no ability to store a LogAction in the base monad. The client can specify a specific HasLog instance for IO that is appropriate to that client, and that HasLog can optionally use the defaultGetIOLogAction as the getLogAction implementation to log pretty messages with ANSI styling to stdout.

instance HasLog Env Text IO where
    getLogAction = return defaultGetIOLogAction
    ...

Orphan instances

Pretty UTCTime Source # 
Instance details

Methods

pretty :: UTCTime -> Doc ann #

prettyList :: [UTCTime] -> Doc ann #