Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- logMessage :: MonadLog message m => message -> m ()
- mapLogMessage :: MonadLog message' m => (message -> message') -> LoggingT message m a -> m a
- mapLogMessageM :: MonadLog message' m => (message -> m message') -> LoggingT message m a -> m a
- class Monad m => MonadLog message m | m -> message where
- logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> m ()
- logDebug :: MonadLog (WithSeverity a) m => a -> m ()
- logInfo :: MonadLog (WithSeverity a) m => a -> m ()
- logNotice :: MonadLog (WithSeverity a) m => a -> m ()
- logWarning :: MonadLog (WithSeverity a) m => a -> m ()
- logError :: MonadLog (WithSeverity a) m => a -> m ()
- logCritical :: MonadLog (WithSeverity a) m => a -> m ()
- logAlert :: MonadLog (WithSeverity a) m => a -> m ()
- logEmergency :: MonadLog (WithSeverity a) m => a -> m ()
- layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann
- data WithTimestamp a = WithTimestamp {
- discardTimestamp :: a
- msgTimestamp :: UTCTime
- timestamp :: MonadIO m => a -> m (WithTimestamp a)
- renderWithTimestamp :: (UTCTime -> String) -> (a -> Doc ann) -> WithTimestamp a -> Doc ann
- data WithSeverity a = WithSeverity {
- msgSeverity :: Severity
- discardSeverity :: a
- data Severity
- renderWithSeverity :: (a -> Doc ann) -> WithSeverity a -> Doc ann
- data WithCallStack a = WithCallStack {}
- withCallStack :: (?stack :: CallStack) => a -> WithCallStack a
- renderWithCallStack :: (a -> Doc ann) -> WithCallStack a -> Doc ann
- newtype LoggingT message m a = LoggingT (ReaderT (Handler m message) m a)
- runLoggingT :: LoggingT message m a -> Handler m message -> m a
- mapLoggingT :: (forall x. (Handler m message -> m x) -> Handler n message' -> n x) -> LoggingT message m a -> LoggingT message' n a
- type Handler m message = message -> m ()
- withFDHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> Handle -> Double -> Int -> (Handler io (Doc ann) -> io a) -> io a
- withBatchedHandler :: (MonadIO io, MonadMask io) => BatchingOptions -> (NonEmpty message -> IO ()) -> (Handler io message -> io a) -> io a
- data BatchingOptions = BatchingOptions {}
- defaultBatchingOptions :: BatchingOptions
- newtype PureLoggingT log m a = MkPureLoggingT (StateT log m a)
- runPureLoggingT :: Monoid log => PureLoggingT log m a -> m (a, log)
- newtype DiscardLoggingT message m a = DiscardLoggingT {
- discardLogging :: m a
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 ability 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
ann)) 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 Handler
s 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 Handler
s 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 = dowithFDHandler
defaultBatchingOptions
stderr
0.4 80 $ \stderrHandler ->withFDHandler
defaultBatchingOptions
stdout
0.4 80 $ \stdoutHandler ->runLoggingT
testApp (\message -> casemsgSeverity
message ofError
-> 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
ann) 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 runLoggingT (testApp >> legacyCode) (const (pure ()))
Couldn't match type ‘WithSeverity (Doc ann1)’ with '(Doc ann0)'
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 runLoggingT (testApp >> lift legacyCode) (const (pure ()))
:: MonadLog (Doc ann) m => 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 ann)) (Doc ann)) 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)
Nothing
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 ()
default logMessageFree :: (m ~ t n, MonadTrans t, MonadLog message n) => (forall mon. Monoid mon => (message -> mon) -> mon) -> m () Source #
Instances
MonadLog message m => MonadLog message (CatchT m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> CatchT m () Source # | |
MonadLog message m => MonadLog message (ListT m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ListT m () Source # | |
MonadLog message m => MonadLog message (MaybeT m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> MaybeT m () Source # | |
Monad m => MonadLog message (DiscardLoggingT message m) Source # | The trivial instance of |
Defined in Control.Monad.Log 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 |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (log -> n) -> n) -> PureLoggingT log m () Source # | |
Monad m => MonadLog message (LoggingT message m) Source # | The main instance of |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> LoggingT message m () Source # | |
(Functor f, MonadLog message m) => MonadLog message (FT f m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> FT f m () Source # | |
(Functor f, MonadLog message m) => MonadLog message (FreeT f m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> FreeT f m () Source # | |
(Error e, MonadLog message m) => MonadLog message (ErrorT e m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ErrorT e m () Source # | |
MonadLog message m => MonadLog message (ExceptT e m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ExceptT e m () Source # | |
(Monoid w, MonadLog message m) => MonadLog message (WriterT w m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> WriterT w m () Source # | |
(Monoid w, MonadLog message m) => MonadLog message (WriterT w m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> WriterT w m () Source # | |
MonadLog message m => MonadLog message (StateT s m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> StateT s m () Source # | |
MonadLog message m => MonadLog message (StateT s m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> StateT s m () Source # | |
MonadLog message m => MonadLog message (ReaderT r m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ReaderT r m () Source # | |
MonadLog message m => MonadLog message (IdentityT m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> IdentityT m () Source # | |
MonadLog message m => MonadLog message (ContT r m) Source # | |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> ContT r m () Source # | |
(Monoid w, MonadLog message m) => MonadLog message (RWST r w s m) Source # | |
Defined in Control.Monad.Log 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 # | |
Defined in Control.Monad.Log 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
.
logDebug :: MonadLog (WithSeverity a) m => a -> m () Source #
logInfo :: MonadLog (WithSeverity a) m => a -> m () Source #
logNotice :: MonadLog (WithSeverity a) m => a -> m () Source #
logWarning :: MonadLog (WithSeverity a) m => a -> m () Source #
logError :: MonadLog (WithSeverity a) m => a -> m () Source #
logCritical :: MonadLog (WithSeverity a) m => a -> m () Source #
logAlert :: MonadLog (WithSeverity a) m => a -> m () Source #
logEmergency :: MonadLog (WithSeverity a) m => a -> m () Source #
Message transformers
layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann #
This is the default layout algorithm, and it is used by show
, putDoc
and hPutDoc
.
commits to rendering something in a certain way if the next
element fits the layout constraints; in other words, it has one
layoutPretty
SimpleDocStream
element lookahead when rendering. Consider using the
smarter, but a bit less performant,
algorithm if the results
seem to run off to the right before having lots of line breaks.layoutSmart
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.
WithTimestamp | |
|
Instances
timestamp :: MonadIO m => a -> m (WithTimestamp a) Source #
Add the current time as a timestamp to a message.
:: (UTCTime -> String) | How to format the timestamp. |
-> (a -> Doc ann) | How to render the rest of the message. |
-> WithTimestamp a -> Doc ann |
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.
WithSeverity | |
|
Instances
Classes of severity for log messages. These have been chosen to match
syslog
severity levels
Emergency | System is unusable. By |
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. |
Instances
Bounded Severity Source # | |
Enum Severity Source # | |
Eq Severity Source # | |
Ord Severity Source # | |
Defined in Control.Monad.Log | |
Read Severity Source # | |
Show Severity Source # | |
Pretty Severity Source # | |
Defined in Control.Monad.Log |
renderWithSeverity :: (a -> Doc ann) -> WithSeverity a -> Doc ann 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
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 ann) -> WithCallStack a -> Doc ann 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).
Instances
MonadRWS r w s m => MonadRWS r w s (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
(Functor f, MonadFree f m) => MonadFree f (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
MonadBase b m => MonadBase b (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
MonadBaseControl b m => MonadBaseControl b (LoggingT message m) Source # | |
MonadWriter w m => MonadWriter w (LoggingT message m) Source # | |
MonadState s m => MonadState s (LoggingT message m) Source # | |
MonadReader r m => MonadReader r (LoggingT message m) Source # | |
MonadError e m => MonadError e (LoggingT message m) Source # | |
Defined in Control.Monad.Log throwError :: e -> LoggingT message m a # catchError :: LoggingT message m a -> (e -> LoggingT message m a) -> LoggingT message m a # | |
Monad m => MonadLog message (LoggingT message m) Source # | The main instance of |
Defined in Control.Monad.Log logMessageFree :: (forall n. Monoid n => (message -> n) -> n) -> LoggingT message m () Source # | |
MonadTrans (LoggingT message) Source # | |
Defined in Control.Monad.Log | |
Monad m => Monad (LoggingT message m) Source # | |
Functor m => Functor (LoggingT message m) Source # | |
MonadFix m => MonadFix (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
MonadFail m => MonadFail (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
Applicative m => Applicative (LoggingT message m) Source # | |
Defined in Control.Monad.Log pure :: a -> LoggingT message m a # (<*>) :: LoggingT message m (a -> b) -> LoggingT message m a -> LoggingT message m b # liftA2 :: (a -> b -> c) -> LoggingT message m a -> LoggingT message m b -> LoggingT message m c # (*>) :: 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 # | |
Defined in Control.Monad.Log | |
Alternative m => Alternative (LoggingT message m) Source # | |
MonadPlus m => MonadPlus (LoggingT message m) Source # | |
MonadThrow m => MonadThrow (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
MonadCatch m => MonadCatch (LoggingT message m) Source # | |
MonadMask m => MonadMask (LoggingT message m) Source # | |
Defined in Control.Monad.Log 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 # generalBracket :: LoggingT message m a -> (a -> ExitCase b -> LoggingT message m c) -> (a -> LoggingT message m b) -> LoggingT message m (b, c) # | |
MonadCont m => MonadCont (LoggingT message m) Source # | |
MonadUnliftIO m => MonadUnliftIO (LoggingT message m) Source # | |
Defined in Control.Monad.Log | |
type StM (LoggingT message m) a Source # | |
Defined in Control.Monad.Log |
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
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.
:: (MonadIO io, MonadMask io) | |
=> BatchingOptions | |
-> Handle | The |
-> Double | The |
-> Int | The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible. |
-> (Handler io (Doc ann) -> 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 Handler
s 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:
- The flush interval has elapsed and the queue is not empty.
- The queue has become full and needs to be flushed.
- 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
.
BatchingOptions | |
|
Instances
Eq BatchingOptions Source # | |
Defined in Control.Monad.Log (==) :: BatchingOptions -> BatchingOptions -> Bool # (/=) :: BatchingOptions -> BatchingOptions -> Bool # | |
Ord BatchingOptions Source # | |
Defined in Control.Monad.Log compare :: BatchingOptions -> BatchingOptions -> Ordering # (<) :: BatchingOptions -> BatchingOptions -> Bool # (<=) :: BatchingOptions -> BatchingOptions -> Bool # (>) :: BatchingOptions -> BatchingOptions -> Bool # (>=) :: BatchingOptions -> BatchingOptions -> Bool # max :: BatchingOptions -> BatchingOptions -> BatchingOptions # min :: BatchingOptions -> BatchingOptions -> BatchingOptions # | |
Read BatchingOptions Source # | |
Defined in Control.Monad.Log | |
Show BatchingOptions Source # | |
Defined in Control.Monad.Log showsPrec :: Int -> BatchingOptions -> ShowS # show :: BatchingOptions -> String # showList :: [BatchingOptions] -> ShowS # |
defaultBatchingOptions :: BatchingOptions Source #
Defaults for BatchingOptions
defaultBatchingOptions
=BatchingOptions
{flushMaxDelay
= 1000000 ,flushMaxQueueSize
= 100 ,blockWhenFull
=True
}
Pure logging
newtype PureLoggingT log m a Source #
A MonadLog
handler optimised for pure usage. Log messages are accumulated
strictly, given that messages form a Monoid
.
MkPureLoggingT (StateT log m a) |
Instances
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
message m a -> m a
DiscardLoggingT | |
|
Instances
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
launchMisslesput
(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
launchMisslesput
(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.