logging-effect-1.0.1: A mtl-style monad transformer for general purpose & compositional logging

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Log

Contents

Synopsis

Introduction

logging-effect provides a toolkit for general logging in Haskell programs and libraries. The library consists of the type class MonadLog to add log output to computations, and this library comes with a set of instances to help you decide how this logging should be performed. There are predefined handlers to write to file handles, to accumulate logs purely, or to discard logging entirely.

Unlike other logging libraries available on Hackage, MonadLog does not assume that you will be logging text information. Instead, the choice of logging data is up to you. This leads to a highly compositional form of logging, with the able to reinterpret logs into different formats, and avoid throwing information away if your final output is structured (such as logging to a relational database).

Getting Started

logging-effect is designed to be used via the MonadLog type class and encourages an "mtl" style approach to programming. If you're not familiar with the mtl, this approach uses type classes to keep the choice of monad polymorphic as you program, and you later choose a specific monad transformer stack when you execute your program. For more information, see Aside: A mtl refresher.

Working with logging-effect

Emitting log messages

To add logging to your applications, you will need to make two changes.

First, use the MonadLog type class to indicate that a computation has access to logging. MonadLog is parameterized on the type of messages that you intend to log. In this example, we will log Text that is wrapped in the WithSeverity.

testApp :: MonadLog (WithSeverity Doc) m => m ()
testApp = do
  logMessage (WithSeverity Informational "Don't mind me")
  logMessage (WithSeverity Error "But do mind me!")

Note that this does not specify where the logs "go", we'll address that when we run the program.

Outputting with LoggingT

Next, we need to run this computation under a MonadLog effect handler. The most flexible handler is LoggingT. LoggingT runs a MonadLog computation by providing it with a Handler, which is a computation that can be in the underlying monad.

For example, we can easily fulfill the MonadLog type class by just using print as our Handler:

>>> runLoggingT testApp print
WithSeverity {msgSeverity = Informational, discardSeverity = "Don't mind me"}
WithSeverity {msgSeverity = Error, discardSeverity = "But do mind me!"}

The log messages are printed according to their Show instances, and - while this works - it is not particularly user friendly. As Handlers are just functions from log messages to monadic actions, we can easily reformat log messages. logging-effect comes with a few "log message transformers" (such as WithSeverity), and each of these message transformers has a canonical way to render in a human-readable format:

>>> runLoggingT testApp (print . renderWithSeverity id)
[Informational] Don't mind me
[Error] But do mind me!

That's looking much more usable - and in fact this approach is probably fine for command line applications.

However, for longer running high performance applications there is a slight problem. Remember that runLoggingT simply interleaves the given Handler whenever logMessage is called. By providing print as a Handler, our application will actually block until the log is complete. This is undesirable for high performance applications, where it's much better to log asynchronously.

logging-effect comes with "batched handlers" for this problem. Batched handlers are handlers that log asynchronously, are flushed periodically, and have maximum memory impact. Batched handlers are created with withBatchedHandler, though if you are just logging to file descriptors you can also use withFDHandler. We'll use this next to log to STDOUT:

main :: IO ()
main =
  withFDHandler defaultBatchingOptions stdout 0.4 80 $ logToStdout ->
  runLoggingT testApp (logToStdout . renderWithSeverity id)

Finally, as Handlers are just functions (we can't stress this enough!) you are free to slice-and-dice your log messages however you want. As our log messages are structured, we can pattern match on the messages and dispatch them to multiple handlers. In this final example of using LoggingT we'll split our log messages between STDOUT and STDERR, and change the formatting of error messages:

main :: IO ()
main = do
  withFDHandler defaultBatchingOptions stderr 0.4 80 $ stderrHandler ->
  withFDHandler defaultBatchingOptions stdout 0.4 80 $ stdoutHandler ->
  runLoggingT m
              (\message ->
                 case msgSeverity message of
                   Error -> stderrHandler (discardSeverity message)
                   _     -> stdoutHandler (renderWithSeverity id message))
>>> main
[Informational] Don't mind me!
BUT DO MIND ME!

Adapting and composing logging

So far we've considered very small applications where all log messages fit nicely into a single type. However, as applications grow and begin to reuse components, it's unlikely that this approach will scale. logging-effect comes with a mapping function - mapLogMessage - which allows us to map log messages from one type to another (just like how we can use map to change elements of a list).

For example, we've already seen the basic testApp computation above that used WithSeverity to add severity information to log messages. Elsewhere we might have some older code that doesn't yet have any severity information:

legacyCode :: MonadLog Doc m => m ()
legacyCode = logMessage "Does anyone even remember writing this function?"

Here legacyCode is only logging Doc, while our testApp is logging WithSeverity Doc. What happens if we compose these programs?

>>> :t testApp >> legacyCode
  Couldn't match type ‘Doc’ with ‘WithSeverity Doc’

Whoops! MonadLog has functional dependencies on the type class which means that there can only be a single way to log per monad. One solution might be to lift one set of logs into the other:

>>> :t testApp >> lift legacyCode
  :: (MonadTrans t, MonadLog Doc m, MonadLog (WithSeverity Doc) (t m)) => t m ()

And indeed, this is a solution, but it's not a particularly nice one.

Instead, we can map both of these computations into a common log format:

>>> :t mapLogMessage Left testApp >> mapLogMessage Right (logMessage "Hello")
  :: (MonadLog (Either (WithSeverity Doc) Doc) m) => m ()

This is a trivial way of combining two different types of log message. In larger applications you will probably want to define a new sum-type that combines all of your log messages, and generally sticking with a single log message type per application.

MonadLog

class Monad m => MonadLog message m | m -> message where Source

The class of monads that support logging.

Methods

logMessage :: message -> m () Source

Append a message to the log for this computation.

Instances

Monad m => MonadLog message (DiscardLoggingT message m) Source

The trivial instance of MonadLog that simply discards all messages logged.

(Monad m, Monoid log) => MonadLog log (PureLoggingT log m) Source

A pure handler of MonadLog that accumulates log messages under the structure of their Monoid instance.

Monad m => MonadLog message (LoggingT message m) Source

The main instance of MonadLog, which replaces calls to logMessage with calls to a Handler.

mapLogMessage :: MonadLog message' m => (message -> message') -> LoggingT message m a -> m a Source

Re-interpret the log messages in one computation. This can be useful to embed a computation with one log type in a larger general computation.

Message transformers

renderPretty :: Float -> Int -> Doc -> SimpleDoc

This is the default pretty printer which is used by show, putDoc and hPutDoc. (renderPretty ribbonfrac width x) renders document x with a page width of width and a ribbon width of (ribbonfrac * width) characters. The ribbon width is the maximal amount of non-indentation characters on a line. The parameter ribbonfrac should be between 0.0 and 1.0. If it is lower or higher, the ribbon width will be 0 or width respectively.

Timestamps

data WithTimestamp a Source

Add a timestamp to log messages.

Note that while most log message transformers are designed to be used at the point of logging, this transformer is best applied within the handler. This is advised as timestamps are generally applied uniformly, so doing it in the handler is fine (no extra information or context of the program is required). The other reason is that logging with a timestamp requires MonadIO - while the rest of your computation is free to use MonadIO, it's best to avoid incurring this constraint as much as possible, as it is generally untestable.

Constructors

WithTimestamp 

Fields

discardTimestamp :: a

Retireve the time a message was logged.

msgTimestamp :: UTCTime

View the underlying message.

timestamp :: MonadIO m => a -> m (WithTimestamp a) Source

Add the current time as a timestamp to a message.

renderWithTimestamp Source

Arguments

:: (UTCTime -> String)

How to format the timestamp.

-> (a -> Doc)

How to render the rest of the message.

-> WithTimestamp a -> Doc 

Given a way to render the underlying message a and a way to format UTCTime, render a message with its timestamp.

>>> renderWithTimestamp (formatTime defaultTimeLocale rfc822DateFormat) id timestamppedLogMessage
[Tue, 19 Jan 2016 11:29:42 UTC] Setting target speed to plaid

Severity

data WithSeverity a Source

Add "Severity" information to a log message. This is often used to convey how significant a log message is.

Constructors

WithSeverity 

Fields

msgSeverity :: Severity

Retrieve the Severity a message.

discardSeverity :: a

View the underlying message.

data Severity Source

Classes of severity for log messages. These have been chosen to match syslog severity levels

Constructors

Emergency

System is unusable. By syslog convention, this level should not be used by applications.

Alert

Should be corrected immediately.

Critical

Critical conditions.

Error

Error conditions.

Warning

May indicate that an error will occur if action is not taken.

Notice

Events that are unusual, but not error conditions.

Informational

Normal operational messages that require no action.

Debug

Information useful to developers for debugging the application.

renderWithSeverity :: (a -> Doc) -> WithSeverity a -> Doc Source

Given a way to render the underlying message a render a message with its timestamp.

>>> renderWithSeverity id Debug (WithSeverity Info "Flux capacitor is functional")
[Info] Flux capacitor is functional

Call stacks

data WithCallStack a Source

Add call stack information to log lines.

This functional requires that you pass around the call stack via implicit parameters. For more information, see the GHC manual (section 9.14.4.5).

withCallStack :: (?stack :: CallStack) => a -> WithCallStack a Source

Construct a WithCallStack log message.

This should normally be preferred over just using WithCallStack as it will append a new entry to the stack - pointing to this exact log line. However, if you are creating a combinator (such as a wrapper that logs and throws an exception), you may be better manually capturing the CallStack and using WithCallStack.

renderWithCallStack :: (a -> Doc) -> WithCallStack a -> Doc Source

Given a way to render the underlying message a render a message with a callstack.

The callstack will be pretty-printed underneith the log message itself.

LoggingT, a general handler

newtype LoggingT message m a Source

LoggingT is a very general handler for the MonadLog effect. Whenever a log entry is emitted, the given Handler is invoked, producing some side-effect (such as writing to stdout, or appending a database table).

Constructors

LoggingT (ReaderT (Handler m message) m a) 

Instances

MonadRWS r w s m => MonadRWS r w s (LoggingT message m) Source 
(Functor f, MonadFree f m) => MonadFree f (LoggingT message m) Source 
MonadBase b m => MonadBase b (LoggingT message m) Source 
MonadBaseControl b m => MonadBaseControl b (LoggingT message m) Source 
MonadError e m => MonadError e (LoggingT message m) Source 
MonadReader r m => MonadReader r (LoggingT message m) Source 
MonadState s m => MonadState s (LoggingT message m) Source 
MonadWriter w m => MonadWriter w (LoggingT message m) Source 
Monad m => MonadLog message (LoggingT message m) Source

The main instance of MonadLog, which replaces calls to logMessage with calls to a Handler.

MonadTrans (LoggingT message) Source 
Monad m => Monad (LoggingT message m) Source 
Functor m => Functor (LoggingT message m) Source 
MonadFix m => MonadFix (LoggingT message m) Source 
Applicative m => Applicative (LoggingT message m) Source 
Alternative m => Alternative (LoggingT message m) Source 
MonadPlus m => MonadPlus (LoggingT message m) Source 
MonadThrow m => MonadThrow (LoggingT message m) Source 
MonadCatch m => MonadCatch (LoggingT message m) Source 
MonadMask m => MonadMask (LoggingT message m) Source 
MonadIO m => MonadIO (LoggingT message m) Source 
MonadCont m => MonadCont (LoggingT message m) Source 
type StM (LoggingT message m) a = StM m a Source 

runLoggingT :: LoggingT message m a -> Handler m message -> m a Source

Given a Handler for a given message, interleave this Handler into the underlying m computation whenever logMessage is called.

mapLoggingT :: (forall x. (Handler m message -> m x) -> Handler n message' -> n x) -> LoggingT message m a -> LoggingT message' n a Source

LoggingT unfortunately does admit an instance of the MFunctor type class, which provides the hoist method to change the monad underneith a monad transformer. However, it is possible to do this with LoggingT provided that you have a way to re-interpret a log handler in the original monad.

LoggingT Handlers

type Handler m message = message -> m () Source

Handlers are mechanisms to interpret the meaning of logging as an action in the underlying monad. They are simply functions from log messages to m-actions.

withFDHandler Source

Arguments

:: (MonadIO io, MonadMask io) 
=> BatchingOptions 
-> Handle

The Handle to write log messages to.

-> Float

The ribbonFrac parameter to renderPretty

-> Int

The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible.

-> (Handler io Doc -> io a) 
-> io a 

withFDHandler creates a new Handler that will append a given file descriptor (or Handle, as it is known in the "base" library). Note that this Handler requires log messages to be of type Text.

These Handlers asynchronously log messages to the given file descriptor, rather than blocking.

Batched handlers

withBatchedHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> ([message] -> IO ()) -> (Handler io message -> io a) -> io a Source

Create a new batched handler. Batched handlers take batches of messages to log at once, which can be more performant than logging each individual message.

A batched handler flushes under three criteria:

  1. The flush interval has elapsed and the queue is not empty.
  2. The queue has become full and needs to be flushed.
  3. The scope of withBatchedHandler is exited.

Batched handlers queue size and flush period can be configured via BatchingOptions.

data BatchingOptions Source

Options that be used to configure withBatchingHandler.

Constructors

BatchingOptions 

Fields

flushMaxDelay :: Int

The maximum amount of time to wait between flushes

flushMaxQueueSize :: Int

The maximum amount of messages to hold in memory between flushes}

blockWhenFull :: Bool

If the Handler becomes full, logMessage will block until the queue is flushed if blockWhenFull is True, otherwise it will drop that message and continue.

Pure logging

newtype PureLoggingT log m a Source

A MonadLog handler optimised for pure usage. Log messages are accumulated strictly, given that messasges form a Monoid.

Constructors

MkPureLoggingT (StateT log m a) 

Instances

MonadRWS r w s m => MonadRWS r w s (PureLoggingT message m) Source 
(Functor f, MonadFree f m) => MonadFree f (PureLoggingT log m) Source 
MonadBase b m => MonadBase b (PureLoggingT message m) Source 
MonadBaseControl b m => MonadBaseControl b (PureLoggingT message m) Source 
MonadError e m => MonadError e (PureLoggingT log m) Source 
MonadReader r m => MonadReader r (PureLoggingT log m) Source 
MonadState s m => MonadState s (PureLoggingT log m) Source 
MonadWriter w m => MonadWriter w (PureLoggingT log m) Source 
(Monad m, Monoid log) => MonadLog log (PureLoggingT log m) Source

A pure handler of MonadLog that accumulates log messages under the structure of their Monoid instance.

MonadTrans (PureLoggingT log) Source 
MonadTransControl (PureLoggingT message) Source 
Monad m => Monad (PureLoggingT log m) Source 
Functor m => Functor (PureLoggingT log m) Source 
MonadFix m => MonadFix (PureLoggingT log m) Source 
Monad m => Applicative (PureLoggingT log m) Source 
MonadPlus m => Alternative (PureLoggingT log m) Source 
MonadPlus m => MonadPlus (PureLoggingT log m) Source 
MonadThrow m => MonadThrow (PureLoggingT log m) Source 
MonadCatch m => MonadCatch (PureLoggingT log m) Source 
MonadMask m => MonadMask (PureLoggingT log m) Source 
MonadIO m => MonadIO (PureLoggingT log m) Source 
MonadCont m => MonadCont (PureLoggingT log m) Source 
type StT (PureLoggingT message) a = StT (StateT message) a Source 
type StM (PureLoggingT message m) a = ComposeSt (PureLoggingT message) m a Source 

runPureLoggingT :: Monoid log => PureLoggingT log m a -> m (a, log) Source

Run a computation with access to logging by accumulating a log under its Monoid instance.

Discarding logs

newtype DiscardLoggingT message m a Source

A MonadLog handler that throws messages away.

The documentation may appear a bit confusing, but note that the full type of discardLogging is:

discardLogging :: DiscardLoggingT messsage m a -> m a

Constructors

DiscardLoggingT 

Fields

discardLogging :: m a

Run a MonadLog computation by throwing away all log requests.

Instances

MonadRWS r w s m => MonadRWS r w s (DiscardLoggingT message m) Source 
(Functor f, MonadFree f m) => MonadFree f (DiscardLoggingT message m) Source 
MonadBase b m => MonadBase b (DiscardLoggingT message m) Source 
MonadBaseControl b m => MonadBaseControl b (DiscardLoggingT message m) Source 
MonadError e m => MonadError e (DiscardLoggingT message m) Source 
MonadReader r m => MonadReader r (DiscardLoggingT message m) Source 
MonadState s m => MonadState s (DiscardLoggingT message m) Source 
MonadWriter w m => MonadWriter w (DiscardLoggingT message m) Source 
Monad m => MonadLog message (DiscardLoggingT message m) Source

The trivial instance of MonadLog that simply discards all messages logged.

MonadTrans (DiscardLoggingT message) Source 
Monad m => Monad (DiscardLoggingT message m) Source 
Functor m => Functor (DiscardLoggingT message m) Source 
MonadFix m => MonadFix (DiscardLoggingT message m) Source 
Applicative m => Applicative (DiscardLoggingT message m) Source 
Alternative m => Alternative (DiscardLoggingT message m) Source 
MonadPlus m => MonadPlus (DiscardLoggingT message m) Source 
MonadThrow m => MonadThrow (DiscardLoggingT message m) Source 
MonadCatch m => MonadCatch (DiscardLoggingT message m) Source 
MonadMask m => MonadMask (DiscardLoggingT message m) Source 
MonadIO m => MonadIO (DiscardLoggingT message m) Source 
MonadCont m => MonadCont (DiscardLoggingT message m) Source 
type StM (DiscardLoggingT message m) a = StM m a Source 

Aside: A mtl refresher

If you are already familiar with the mtl you can skip this section. This is not designed to be an exhaustive introduction to the mtl library, but hopefully via a short example you'll have a basic familarity with the approach.

In this example, we'll write a program with access to state and general IO actions. One way to do this would be to work with monad transformers, stacking StateT on top of IO:

import Control.Monad.Trans.State.Strict (StateT, get, put)
import Control.Monad.Trans.Class (lift)

transformersProgram :: StateT Int IO ()
transformersProgram = do
  stateNow <- get
  lift launchMissles
  put (stateNow + 42)

This is OK, but it's not very flexible. For example, the transformers library actually provides us with two implementations of state monads - strict and a lazy variant. In the above approach we have forced the user into a choice (we chose the strict variant), but this can be undesirable. We could imagine that in the future there may be even more implementations of state monads (for example, a state monad that persists state entirely on a remote machine) - if requirements change we are unable to reuse this program without changing its type.

With the mtl, we instead program to an abstract specification of the effects we require, and we postpone the choice of handler until the point when the computation is ran.

Rewriting the transformersProgram using the mtl, we have the following:

import Control.Monad.State.Class (MonadState(get, put))
import Control.Monad.IO.Class (MonadIO(liftIO))

mtlProgram :: (MonadState Int m, MonadIO m) => m ()
mtlProgram = do
  stateNow <- get
  liftIO launchMissles
  put (stateNow + 42)

Notice that mtlProgram doesn't specify a concrete choice of state monad. The "transformers" library gives us two choices - strict or lazy state monads. We make the choice of a specific monad stack when we run our program:

import Control.Monad.Trans.State.Strict (execStateT)

main :: IO ()
main = execStateT mtlProgram 99

Here we chose the strict variant via execStateT. Using execStateT eliminates the MonadState type class from mtlProgram, so now we only have to fulfill the MonadIO obligation. There is only one way to handle this, and that's by working in the IO monad. Fortunately we're inside the main function, which is in the IO monad, so we're all good.