logging-1.2.0: Simplified logging in IO for application writers.

Safe HaskellNone

Control.Logging

Description

Quick example of how to use this module:

import Control.Logging

main = withStdoutLogging $ do
     log This is a log message!
     timedLog This is a timed log message! $ threadDelay 100000

Synopsis

Documentation

log :: MonadLogger m => Text -> m ()Source

Synonym for logInfoN. This module provides a MonadLogger instance for IO, so this function can be used directly in IO. The only requirement is that you must surround the body of your main function with a call to withStdoutLogging or withStderrLogging, to ensure that all logging buffers are properly flushed on exit.

log' :: (MonadLogger m, MonadIO m) => Text -> m ()Source

The apostrophe varients of the logging functions flush the log after each message.

logS :: MonadLogger m => Text -> Text -> m ()Source

logS' :: (MonadLogger m, MonadIO m) => Text -> Text -> m ()Source

warn :: MonadLogger m => Text -> m ()Source

warn' :: (MonadLogger m, MonadIO m) => Text -> m ()Source

warnS :: MonadLogger m => Text -> Text -> m ()Source

warnS' :: (MonadLogger m, MonadIO m) => Text -> Text -> m ()Source

debug :: MonadLogger m => Text -> m ()Source

debug' :: (MonadLogger m, MonadIO m) => Text -> m ()Source

debugS :: MonadLogger m => Text -> Text -> m ()Source

debugS' :: (MonadLogger m, MonadIO m) => Text -> Text -> m ()Source

errorL :: Text -> aSource

A logging variant of error which uses unsafePerformIO to output a log message before calling error.

traceL :: Text -> a -> aSource

traceL' :: Text -> a -> aSource

traceSL :: Text -> Text -> a -> aSource

traceSL' :: Text -> Text -> a -> aSource

traceShowL :: Show a => a -> a1 -> a1Source

traceShowL' :: Show a => a -> a1 -> a1Source

traceShowSL :: Show a => Text -> a -> a1 -> a1Source

traceShowSL' :: Show a => Text -> a -> a1 -> a1Source

timedLog :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> m () -> m ()Source

Output a logging message both before an action begins, and after it ends, reporting the total length of time. If an exception occurred, it is also reported.

timedLog' :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> m () -> m ()Source

timedLogS :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> Text -> m () -> m ()Source

timedLogS' :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> Text -> m () -> m ()Source

timedLogEnd :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> m () -> m ()Source

Like timedLog, except that it does only logs when the action has completed or failed after it is done.

timedDebug :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> m () -> m ()Source

A debug variant of timedLog.

timedDebugS :: (MonadLogger m, MonadBaseControl IO m, MonadIO m) => Text -> Text -> m () -> m ()Source

withStdoutLogging :: (MonadBaseControl IO m, MonadIO m) => m a -> m aSource

This function, or withStderrLogging, must be wrapped around whatever region of your application intends to use logging. Typically it would be wrapped around the body of main.

flushLog :: MonadIO m => m ()Source

Flush all collected logging messages. This is automatically called by withStdoutLogging and withStderrLogging when those blocks are exited by whatever means.

loggingLogger :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> IO ()Source

This function is used to implement monadLoggerLog for the IO instance. You may reuse it if you wish, or it can be passed as an argument to runLoggingT -- in which case you must remember to call flushLog before the program exits.

setDebugLevel :: LogLevel -> IO ()Source

Set the verbosity level. Messages at our higher than this level are displayed. It defaults to LevelDebug.

setLogFormat :: String -> IO ()Source

Set the format used for log timestamps.