Copyright | (c) Galois Inc. 2020 |
---|---|
Maintainer | kquick@galois.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines a general logging facility that can be used to output log messages to various targets.
The LogAction
is the fundamental operation that decides how to
log a provided message.
Code wishing to output a logged message simply uses the LogAction object:
writeLog action msg
For convenience, the LogAction can be stored in the local operating
monad context, from which it can be retrieved (and modified). A
monad which can supply a LogAction is a member of the HasLog class,
and the writeLogM
function will automatically retrieve the
LogAction from the monad and write to it:
writeLogM msg
LogActions can be combined via Semigroup operations (<>) and the
resulting LogAction will perform both actions with each message.
The Monoidal mempty LogAction simply does nothing. For example,
logging to both a file and stdout can be done by logToFile <>
logToStdout
.
LogActions are also Contravariant (and Divisible and Decidable) to allow easy conversion of a LogAction for the base message type into a LogAction for a different message type (or types) that can be converted to (and combined into) the base message type.
Synopsis
- newtype LogAction m msg = LogAction {
- writeLog :: msg -> m ()
- class Monad m => HasLog msg m where
- getLogAction :: m (LogAction m msg)
- class (Monad m, HasLog msg m) => LoggingMonad msg m where
- adjustLogAction :: (forall k. LogAction k msg -> LogAction k msg) -> m a -> m a
- writeLogM :: HasLog msg m => msg -> m ()
- safeLogAction :: MonadCatch m => LogAction m msg -> LogAction m msg
- logFilter :: Applicative m => (msg -> Bool) -> LogAction m msg -> LogAction m msg
- data Severity
- data LogType
- data LogMessage = LogMessage {}
- msgWith :: LogMessage
- type WithLog msg m = HasLog msg m
- withLogTag :: LoggingMonad LogMessage m => Text -> Text -> m a -> m a
- addLogActionTime :: MonadIO m => LogAction m LogMessage -> LogAction m LogMessage
- cvtLogMessageToPlainText :: LogMessage -> Text
- cvtLogMessageToANSITermText :: LogMessage -> Text
- (|#) :: (LogMessage -> a) -> Text -> a
- logFunctionCall :: MonadIO m => LogAction m LogMessage -> Text -> m a -> m a
- logFunctionCallM :: (MonadIO m, WithLog LogMessage m) => Text -> m a -> m a
- logProgress :: MonadIO m => LogAction m LogMessage -> Text -> m ()
- logProgressM :: (MonadIO m, WithLog LogMessage m) => Text -> m ()
- tshow :: Show a => a -> Text
- defaultGetIOLogAction :: MonadIO m => LogAction m Text
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).
Instances
Contravariant (LogAction m) Source # | |
Applicative m => Decidable (LogAction m) Source # | |
Applicative m => Divisible (LogAction m) Source # | |
Applicative m => Monoid (LogAction m a) Source # | |
Applicative m => Semigroup (LogAction m a) Source # | |
class Monad m => HasLog msg m where Source #
Any monad which will support retrieving a LogAction from the
Monad's environment should support the HasLog
class.
getLogAction :: m (LogAction m msg) Source #
class (Monad m, HasLog msg m) => LoggingMonad msg m where Source #
An instance of the LoggingMonad
class can be defined for the
base monadic logging action to allow adjusting that logging action.
This class can only be instantiated (and only needs to be
instantiated) for the base message type; all other message types
will use contramapping to convert their message type to the
LoggingMonad
base message type.
adjustLogAction :: (forall k. LogAction k msg -> LogAction k msg) -> m a -> m a Source #
writeLogM :: HasLog msg m => msg -> m () Source #
This obtains the LogAction
from the current monad's environment
to use for outputting the log message. Most code will use this 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).
LogMessage rich logging type
This is an enhanced message type for the LogAction, containing various auxiliary information associated with the log message. While Lumberjack can be used with other message types, this message type should provide support for most of the common logging auxiliary data and can therefore be used "out of the box".
The Severity indicates the relative importance of the logging message. This can be useful for filtering log messages.
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.
data LogMessage Source #
Each logged output is described by a LogMessage object.
Instances
Monoid LogMessage Source # | |
Defined in Lumberjack mempty :: LogMessage # mappend :: LogMessage -> LogMessage -> LogMessage # mconcat :: [LogMessage] -> LogMessage # | |
Semigroup LogMessage Source # | |
Defined in Lumberjack (<>) :: LogMessage -> LogMessage -> LogMessage # sconcat :: NonEmpty LogMessage -> LogMessage # stimes :: Integral b => b -> LogMessage -> LogMessage # | |
Pretty LogMessage Source # | |
Defined in Lumberjack 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
When the LogMessage
logging type is used, Lumberjack provides a
standard set of output formatting functions. The output uses the
prettyprinter package to generate Doc
output with
annotations specifying the type of markup to be applied to various
portions of the output.
There are multiple rendering functions that can be supplied as
contramap converters to the base LogAction
. One rendering
function outputs a log message in plain text, while the other uses
the prettyprinter-ansi-terminal package to generate various ANSI
highlighting and color codes for writing enhanced output to a TTY.
cvtLogMessageToPlainText :: LogMessage -> Text Source #
Standard LogMessage
rendering function for converting a
LogMessage
into plain Text
(no colors or other highlighting).
This can be used as the default converter for a logger (via
contramap).
cvtLogMessageToANSITermText :: LogMessage -> Text Source #
Standard LogMessage
rendering 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
These functions are not part of the core Logging implementation, but can be useful to clients to perform common or default operations.
(|#) :: (LogMessage -> a) -> Text -> a infixr 0 Source #
This operator is a convenient infix operator for logging a Text
message. This is especially useful when used in conjunction with
the OverloadedStrings
language pragma:
>>>
warning|# "This is your last warning"
>>>
error|# "Failure has occurred"
logFunctionCall :: MonadIO m => LogAction m LogMessage -> Text -> m a -> m a Source #
A wrapper for a function call that will call the provided
LogAction
with a Debug
log on entry to the function and an
Info
log on exit from the function. The total amount of time
taken during execution of the function will be included in the exit
log message. No strictness is applied to the invoked 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 Debug
log on
entry to and Info
log on exit from the function. The exit log
will also note the total amount of time taken during execution of
the function. Be advised 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 in the current activity has been made.
logProgressM :: (MonadIO m, WithLog LogMessage m) => Text -> m () Source #
Called to output a log message within a HasLog
monad to indicate
that some progress in the current activity has been made.
tshow :: Show a => a -> Text Source #
This is a helper function. The LogMessage normally wants a Text,
but show delivers a String, so tshow
can be used to get the
needed format.
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