logging-effect-1.1.2: 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: An 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 a Doc that is wrapped in 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

logMessage :: MonadLog message m => message -> m () Source #

Append a message to the log for this computation.

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.

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

Monadic version of mapLogMessage. This can be used to annotate a message with something that can only be computed in a monad. See e.g. timestamp.

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

The class of monads that support logging.

Laws:

Monoid homomorphism:

logMessageFree a *> logMessageFree b = logMessageFree (a <> b)

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> m () Source #

Fold log messages into this computation. Looking to just log a message? You probably want logMessage.

The perhaps strange type here allows us to construct a monoid out of any type of log message. You can think of this as the simpler type:

logMessageFree :: [message] -> m ()

logMessageFree :: (m ~ t n, MonadTrans t, MonadLog message n) => (forall mon. Monoid mon => (message -> mon) -> mon) -> m () Source #

Fold log messages into this computation. Looking to just log a message? You probably want logMessage.

The perhaps strange type here allows us to construct a monoid out of any type of log message. You can think of this as the simpler type:

logMessageFree :: [message] -> m ()

Instances

MonadLog message m => MonadLog message (CatchT m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> CatchT m () Source #

MonadLog message m => MonadLog message (ListT m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ListT m () Source #

MonadLog message m => MonadLog message (MaybeT m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> MaybeT m () Source #

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

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

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> DiscardLoggingT message 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.

Methods

logMessageFree :: (forall n. Monoid n => (log -> n) -> n) -> PureLoggingT log 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.

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> LoggingT message m () Source #

(Functor f, MonadLog message m) => MonadLog message (FT f m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> FT f m () Source #

(Functor f, MonadLog message m) => MonadLog message (FreeT f m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> FreeT f m () Source #

(Error e, MonadLog message m) => MonadLog message (ErrorT e m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ErrorT e m () Source #

MonadLog message m => MonadLog message (ExceptT e m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ExceptT e m () Source #

(Monoid w, MonadLog message m) => MonadLog message (WriterT w m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> WriterT w m () Source #

(Monoid w, MonadLog message m) => MonadLog message (WriterT w m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> WriterT w m () Source #

MonadLog message m => MonadLog message (StateT s m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> StateT s m () Source #

MonadLog message m => MonadLog message (StateT s m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> StateT s m () Source #

MonadLog message m => MonadLog message (IdentityT * m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> IdentityT * m () Source #

MonadLog message m => MonadLog message (ContT * r m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ContT * r m () Source #

MonadLog message m => MonadLog message (ReaderT * r m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ReaderT * r m () Source #

(Monoid w, MonadLog message m) => MonadLog message (RWST r w s m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> RWST r w s m () Source #

(Monoid w, MonadLog message m) => MonadLog message (RWST r w s m) Source # 

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> RWST r w s m () Source #

Convenience logging combinators

While logging-effect tries to be as general as possible, there is a fairly common case of logging, namely basic messages with an indication of severity. These combinators assume that you will be using WithSeverity at the outer-most level of your log message stack, though no make no assumptions at what is inside your log messages. There is a logX combinator for each level in Severity.

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

Instances

Functor WithTimestamp Source # 

Methods

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

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

Foldable WithTimestamp Source # 

Methods

fold :: Monoid m => WithTimestamp m -> m #

foldMap :: Monoid m => (a -> m) -> WithTimestamp a -> m #

foldr :: (a -> b -> b) -> b -> WithTimestamp a -> b #

foldr' :: (a -> b -> b) -> b -> WithTimestamp a -> b #

foldl :: (b -> a -> b) -> b -> WithTimestamp a -> b #

foldl' :: (b -> a -> b) -> b -> WithTimestamp a -> b #

foldr1 :: (a -> a -> a) -> WithTimestamp a -> a #

foldl1 :: (a -> a -> a) -> WithTimestamp a -> a #

toList :: WithTimestamp a -> [a] #

null :: WithTimestamp a -> Bool #

length :: WithTimestamp a -> Int #

elem :: Eq a => a -> WithTimestamp a -> Bool #

maximum :: Ord a => WithTimestamp a -> a #

minimum :: Ord a => WithTimestamp a -> a #

sum :: Num a => WithTimestamp a -> a #

product :: Num a => WithTimestamp a -> a #

Traversable WithTimestamp Source # 

Methods

traverse :: Applicative f => (a -> f b) -> WithTimestamp a -> f (WithTimestamp b) #

sequenceA :: Applicative f => WithTimestamp (f a) -> f (WithTimestamp a) #

mapM :: Monad m => (a -> m b) -> WithTimestamp a -> m (WithTimestamp b) #

sequence :: Monad m => WithTimestamp (m a) -> m (WithTimestamp a) #

Eq a => Eq (WithTimestamp a) Source # 
Ord a => Ord (WithTimestamp a) Source # 
Read a => Read (WithTimestamp a) Source # 
Show a => Show (WithTimestamp a) Source # 

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

Instances

Functor WithSeverity Source # 

Methods

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

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

Foldable WithSeverity Source # 

Methods

fold :: Monoid m => WithSeverity m -> m #

foldMap :: Monoid m => (a -> m) -> WithSeverity a -> m #

foldr :: (a -> b -> b) -> b -> WithSeverity a -> b #

foldr' :: (a -> b -> b) -> b -> WithSeverity a -> b #

foldl :: (b -> a -> b) -> b -> WithSeverity a -> b #

foldl' :: (b -> a -> b) -> b -> WithSeverity a -> b #

foldr1 :: (a -> a -> a) -> WithSeverity a -> a #

foldl1 :: (a -> a -> a) -> WithSeverity a -> a #

toList :: WithSeverity a -> [a] #

null :: WithSeverity a -> Bool #

length :: WithSeverity a -> Int #

elem :: Eq a => a -> WithSeverity a -> Bool #

maximum :: Ord a => WithSeverity a -> a #

minimum :: Ord a => WithSeverity a -> a #

sum :: Num a => WithSeverity a -> a #

product :: Num a => WithSeverity a -> a #

Traversable WithSeverity Source # 

Methods

traverse :: Applicative f => (a -> f b) -> WithSeverity a -> f (WithSeverity b) #

sequenceA :: Applicative f => WithSeverity (f a) -> f (WithSeverity a) #

mapM :: Monad m => (a -> m b) -> WithSeverity a -> m (WithSeverity b) #

sequence :: Monad m => WithSeverity (m a) -> m (WithSeverity a) #

Eq a => Eq (WithSeverity a) Source # 
Ord a => Ord (WithSeverity a) Source # 
Read a => Read (WithSeverity a) Source # 
Show a => Show (WithSeverity a) Source # 

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 severity.

>>> renderWithSeverity id (WithSeverity Informational "Flux capacitor is functional")
[Informational] 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).

Instances

Functor WithCallStack Source # 

Methods

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

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

Foldable WithCallStack Source # 

Methods

fold :: Monoid m => WithCallStack m -> m #

foldMap :: Monoid m => (a -> m) -> WithCallStack a -> m #

foldr :: (a -> b -> b) -> b -> WithCallStack a -> b #

foldr' :: (a -> b -> b) -> b -> WithCallStack a -> b #

foldl :: (b -> a -> b) -> b -> WithCallStack a -> b #

foldl' :: (b -> a -> b) -> b -> WithCallStack a -> b #

foldr1 :: (a -> a -> a) -> WithCallStack a -> a #

foldl1 :: (a -> a -> a) -> WithCallStack a -> a #

toList :: WithCallStack a -> [a] #

null :: WithCallStack a -> Bool #

length :: WithCallStack a -> Int #

elem :: Eq a => a -> WithCallStack a -> Bool #

maximum :: Ord a => WithCallStack a -> a #

minimum :: Ord a => WithCallStack a -> a #

sum :: Num a => WithCallStack a -> a #

product :: Num a => WithCallStack a -> a #

Traversable WithCallStack Source # 

Methods

traverse :: Applicative f => (a -> f b) -> WithCallStack a -> f (WithCallStack b) #

sequenceA :: Applicative f => WithCallStack (f a) -> f (WithCallStack a) #

mapM :: Monad m => (a -> m b) -> WithCallStack a -> m (WithCallStack b) #

sequence :: Monad m => WithCallStack (m a) -> m (WithCallStack a) #

Show a => Show (WithCallStack a) Source # 

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 underneath 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 # 

Methods

wrap :: f (LoggingT message m a) -> LoggingT message m a #

MonadBase b m => MonadBase b (LoggingT message m) Source # 

Methods

liftBase :: b α -> LoggingT message m α #

MonadBaseControl b m => MonadBaseControl b (LoggingT message m) Source # 

Associated Types

type StM (LoggingT message m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (LoggingT message m) b -> b a) -> LoggingT message m a #

restoreM :: StM (LoggingT message m) a -> LoggingT message m a #

MonadError e m => MonadError e (LoggingT message m) Source # 

Methods

throwError :: e -> LoggingT message m a #

catchError :: LoggingT message m a -> (e -> LoggingT message m a) -> LoggingT message m a #

MonadReader r m => MonadReader r (LoggingT message m) Source # 

Methods

ask :: LoggingT message m r #

local :: (r -> r) -> LoggingT message m a -> LoggingT message m a #

reader :: (r -> a) -> LoggingT message m a #

MonadState s m => MonadState s (LoggingT message m) Source # 

Methods

get :: LoggingT message m s #

put :: s -> LoggingT message m () #

state :: (s -> (a, s)) -> LoggingT message m a #

MonadWriter w m => MonadWriter w (LoggingT message m) Source # 

Methods

writer :: (a, w) -> LoggingT message m a #

tell :: w -> LoggingT message m () #

listen :: LoggingT message m a -> LoggingT message m (a, w) #

pass :: LoggingT message m (a, w -> w) -> LoggingT message m a #

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

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

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> LoggingT message m () Source #

MonadTrans (LoggingT message) Source # 

Methods

lift :: Monad m => m a -> LoggingT message m a #

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

Methods

(>>=) :: LoggingT message m a -> (a -> LoggingT message m b) -> LoggingT message m b #

(>>) :: LoggingT message m a -> LoggingT message m b -> LoggingT message m b #

return :: a -> LoggingT message m a #

fail :: String -> LoggingT message m a #

Functor m => Functor (LoggingT message m) Source # 

Methods

fmap :: (a -> b) -> LoggingT message m a -> LoggingT message m b #

(<$) :: a -> LoggingT message m b -> LoggingT message m a #

MonadFix m => MonadFix (LoggingT message m) Source # 

Methods

mfix :: (a -> LoggingT message m a) -> LoggingT message m a #

Applicative m => Applicative (LoggingT message m) Source # 

Methods

pure :: a -> LoggingT message m a #

(<*>) :: LoggingT message m (a -> b) -> LoggingT message m a -> LoggingT message m b #

(*>) :: LoggingT message m a -> LoggingT message m b -> LoggingT message m b #

(<*) :: LoggingT message m a -> LoggingT message m b -> LoggingT message m a #

MonadIO m => MonadIO (LoggingT message m) Source # 

Methods

liftIO :: IO a -> LoggingT message m a #

Alternative m => Alternative (LoggingT message m) Source # 

Methods

empty :: LoggingT message m a #

(<|>) :: LoggingT message m a -> LoggingT message m a -> LoggingT message m a #

some :: LoggingT message m a -> LoggingT message m [a] #

many :: LoggingT message m a -> LoggingT message m [a] #

MonadPlus m => MonadPlus (LoggingT message m) Source # 

Methods

mzero :: LoggingT message m a #

mplus :: LoggingT message m a -> LoggingT message m a -> LoggingT message m a #

MonadThrow m => MonadThrow (LoggingT message m) Source # 

Methods

throwM :: Exception e => e -> LoggingT message m a #

MonadCatch m => MonadCatch (LoggingT message m) Source # 

Methods

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

MonadMask m => MonadMask (LoggingT message m) Source # 

Methods

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

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

MonadCont m => MonadCont (LoggingT message m) Source # 

Methods

callCC :: ((a -> LoggingT message m b) -> LoggingT message m a) -> LoggingT message m a #

type StM (LoggingT message m) a Source # 
type StM (LoggingT message m) a = StM m a

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 underneath 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 Doc. This abstractly specifies a pretty-printing for log lines. The two arguments two withFDHandler determine how this pretty-printing should be realised when outputting log lines.

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

Batched handlers

withBatchedHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> (NonEmpty 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

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 # 

Methods

wrap :: f (PureLoggingT log m a) -> PureLoggingT log m a #

MonadBase b m => MonadBase b (PureLoggingT message m) Source # 

Methods

liftBase :: b α -> PureLoggingT message m α #

MonadBaseControl b m => MonadBaseControl b (PureLoggingT message m) Source # 

Associated Types

type StM (PureLoggingT message m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (PureLoggingT message m) b -> b a) -> PureLoggingT message m a #

restoreM :: StM (PureLoggingT message m) a -> PureLoggingT message m a #

MonadError e m => MonadError e (PureLoggingT log m) Source # 

Methods

throwError :: e -> PureLoggingT log m a #

catchError :: PureLoggingT log m a -> (e -> PureLoggingT log m a) -> PureLoggingT log m a #

MonadReader r m => MonadReader r (PureLoggingT log m) Source # 

Methods

ask :: PureLoggingT log m r #

local :: (r -> r) -> PureLoggingT log m a -> PureLoggingT log m a #

reader :: (r -> a) -> PureLoggingT log m a #

MonadState s m => MonadState s (PureLoggingT log m) Source # 

Methods

get :: PureLoggingT log m s #

put :: s -> PureLoggingT log m () #

state :: (s -> (a, s)) -> PureLoggingT log m a #

MonadWriter w m => MonadWriter w (PureLoggingT log m) Source # 

Methods

writer :: (a, w) -> PureLoggingT log m a #

tell :: w -> PureLoggingT log m () #

listen :: PureLoggingT log m a -> PureLoggingT log m (a, w) #

pass :: PureLoggingT log m (a, w -> w) -> PureLoggingT log m a #

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

Methods

logMessageFree :: (forall n. Monoid n => (log -> n) -> n) -> PureLoggingT log m () Source #

MonadTrans (PureLoggingT log) Source # 

Methods

lift :: Monad m => m a -> PureLoggingT log m a #

MonadTransControl (PureLoggingT message) Source # 

Associated Types

type StT (PureLoggingT message :: (* -> *) -> * -> *) a :: * #

Methods

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

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

Monad m => Monad (PureLoggingT log m) Source # 

Methods

(>>=) :: PureLoggingT log m a -> (a -> PureLoggingT log m b) -> PureLoggingT log m b #

(>>) :: PureLoggingT log m a -> PureLoggingT log m b -> PureLoggingT log m b #

return :: a -> PureLoggingT log m a #

fail :: String -> PureLoggingT log m a #

Functor m => Functor (PureLoggingT log m) Source # 

Methods

fmap :: (a -> b) -> PureLoggingT log m a -> PureLoggingT log m b #

(<$) :: a -> PureLoggingT log m b -> PureLoggingT log m a #

MonadFix m => MonadFix (PureLoggingT log m) Source # 

Methods

mfix :: (a -> PureLoggingT log m a) -> PureLoggingT log m a #

Monad m => Applicative (PureLoggingT log m) Source # 

Methods

pure :: a -> PureLoggingT log m a #

(<*>) :: PureLoggingT log m (a -> b) -> PureLoggingT log m a -> PureLoggingT log m b #

(*>) :: PureLoggingT log m a -> PureLoggingT log m b -> PureLoggingT log m b #

(<*) :: PureLoggingT log m a -> PureLoggingT log m b -> PureLoggingT log m a #

MonadIO m => MonadIO (PureLoggingT log m) Source # 

Methods

liftIO :: IO a -> PureLoggingT log m a #

MonadPlus m => Alternative (PureLoggingT log m) Source # 

Methods

empty :: PureLoggingT log m a #

(<|>) :: PureLoggingT log m a -> PureLoggingT log m a -> PureLoggingT log m a #

some :: PureLoggingT log m a -> PureLoggingT log m [a] #

many :: PureLoggingT log m a -> PureLoggingT log m [a] #

MonadPlus m => MonadPlus (PureLoggingT log m) Source # 

Methods

mzero :: PureLoggingT log m a #

mplus :: PureLoggingT log m a -> PureLoggingT log m a -> PureLoggingT log m a #

MonadThrow m => MonadThrow (PureLoggingT log m) Source # 

Methods

throwM :: Exception e => e -> PureLoggingT log m a #

MonadCatch m => MonadCatch (PureLoggingT log m) Source # 

Methods

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

MonadMask m => MonadMask (PureLoggingT log m) Source # 

Methods

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

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

MonadCont m => MonadCont (PureLoggingT log m) Source # 

Methods

callCC :: ((a -> PureLoggingT log m b) -> PureLoggingT log m a) -> PureLoggingT log m a #

type StT (PureLoggingT message) a Source # 
type StT (PureLoggingT message) a = StT (StateT message) a
type StM (PureLoggingT message m) a Source # 
type StM (PureLoggingT message m) a = ComposeSt (PureLoggingT message) m a

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

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 # 

Methods

wrap :: f (DiscardLoggingT message m a) -> DiscardLoggingT message m a #

MonadBase b m => MonadBase b (DiscardLoggingT message m) Source # 

Methods

liftBase :: b α -> DiscardLoggingT message m α #

MonadBaseControl b m => MonadBaseControl b (DiscardLoggingT message m) Source # 

Associated Types

type StM (DiscardLoggingT message m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (DiscardLoggingT message m) b -> b a) -> DiscardLoggingT message m a #

restoreM :: StM (DiscardLoggingT message m) a -> DiscardLoggingT message m a #

MonadError e m => MonadError e (DiscardLoggingT message m) Source # 

Methods

throwError :: e -> DiscardLoggingT message m a #

catchError :: DiscardLoggingT message m a -> (e -> DiscardLoggingT message m a) -> DiscardLoggingT message m a #

MonadReader r m => MonadReader r (DiscardLoggingT message m) Source # 

Methods

ask :: DiscardLoggingT message m r #

local :: (r -> r) -> DiscardLoggingT message m a -> DiscardLoggingT message m a #

reader :: (r -> a) -> DiscardLoggingT message m a #

MonadState s m => MonadState s (DiscardLoggingT message m) Source # 

Methods

get :: DiscardLoggingT message m s #

put :: s -> DiscardLoggingT message m () #

state :: (s -> (a, s)) -> DiscardLoggingT message m a #

MonadWriter w m => MonadWriter w (DiscardLoggingT message m) Source # 

Methods

writer :: (a, w) -> DiscardLoggingT message m a #

tell :: w -> DiscardLoggingT message m () #

listen :: DiscardLoggingT message m a -> DiscardLoggingT message m (a, w) #

pass :: DiscardLoggingT message m (a, w -> w) -> DiscardLoggingT message m a #

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

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

Methods

logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> DiscardLoggingT message m () Source #

MonadTrans (DiscardLoggingT message) Source # 

Methods

lift :: Monad m => m a -> DiscardLoggingT message m a #

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

Methods

(>>=) :: DiscardLoggingT message m a -> (a -> DiscardLoggingT message m b) -> DiscardLoggingT message m b #

(>>) :: DiscardLoggingT message m a -> DiscardLoggingT message m b -> DiscardLoggingT message m b #

return :: a -> DiscardLoggingT message m a #

fail :: String -> DiscardLoggingT message m a #

Functor m => Functor (DiscardLoggingT message m) Source # 

Methods

fmap :: (a -> b) -> DiscardLoggingT message m a -> DiscardLoggingT message m b #

(<$) :: a -> DiscardLoggingT message m b -> DiscardLoggingT message m a #

MonadFix m => MonadFix (DiscardLoggingT message m) Source # 

Methods

mfix :: (a -> DiscardLoggingT message m a) -> DiscardLoggingT message m a #

Applicative m => Applicative (DiscardLoggingT message m) Source # 

Methods

pure :: a -> DiscardLoggingT message m a #

(<*>) :: DiscardLoggingT message m (a -> b) -> DiscardLoggingT message m a -> DiscardLoggingT message m b #

(*>) :: DiscardLoggingT message m a -> DiscardLoggingT message m b -> DiscardLoggingT message m b #

(<*) :: DiscardLoggingT message m a -> DiscardLoggingT message m b -> DiscardLoggingT message m a #

MonadIO m => MonadIO (DiscardLoggingT message m) Source # 

Methods

liftIO :: IO a -> DiscardLoggingT message m a #

Alternative m => Alternative (DiscardLoggingT message m) Source # 

Methods

empty :: DiscardLoggingT message m a #

(<|>) :: DiscardLoggingT message m a -> DiscardLoggingT message m a -> DiscardLoggingT message m a #

some :: DiscardLoggingT message m a -> DiscardLoggingT message m [a] #

many :: DiscardLoggingT message m a -> DiscardLoggingT message m [a] #

MonadPlus m => MonadPlus (DiscardLoggingT message m) Source # 

Methods

mzero :: DiscardLoggingT message m a #

mplus :: DiscardLoggingT message m a -> DiscardLoggingT message m a -> DiscardLoggingT message m a #

MonadThrow m => MonadThrow (DiscardLoggingT message m) Source # 

Methods

throwM :: Exception e => e -> DiscardLoggingT message m a #

MonadCatch m => MonadCatch (DiscardLoggingT message m) Source # 

Methods

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

MonadMask m => MonadMask (DiscardLoggingT message m) Source # 

Methods

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

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

MonadCont m => MonadCont (DiscardLoggingT message m) Source # 

Methods

callCC :: ((a -> DiscardLoggingT message m b) -> DiscardLoggingT message m a) -> DiscardLoggingT message m a #

type StM (DiscardLoggingT message m) a Source # 
type StM (DiscardLoggingT message m) a = StM m a

Aside: An 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.