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

Safe HaskellNone
LanguageHaskell98

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 :: Text -> IO () Source

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

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

logS :: Text -> Text -> IO () Source

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

warn :: Text -> IO () Source

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

warnS :: Text -> Text -> IO () Source

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

debug :: Text -> IO () Source

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

debugS :: Text -> Text -> IO () Source

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

errorL :: Text -> a Source

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

errorSL :: Text -> Text -> a Source

traceL :: Text -> a -> a Source

traceL' :: Text -> a -> a Source

traceSL :: Text -> Text -> a -> a Source

traceSL' :: Text -> Text -> a -> a Source

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

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

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

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

timedLog :: (MonadBaseControl IO m, MonadIO m) => Text -> m a -> m a 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' :: (MonadBaseControl IO m, MonadIO m) => Text -> m a -> m a Source

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

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

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

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

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

timedLogEndS :: (MonadBaseControl IO m, MonadIO m) => Text -> Text -> m a -> m a Source

timedLogEndS' :: (MonadBaseControl IO m, MonadIO m) => Text -> Text -> m a -> m a Source

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

A debug variant of timedLog.

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

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

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

timedDebugEnd :: (MonadBaseControl IO m, MonadIO m) => Text -> m a -> m a Source

timedDebugEndS :: (MonadBaseControl IO m, MonadIO m) => Text -> Text -> m a -> m a Source

timedDebugEndS' :: (MonadBaseControl IO m, MonadIO m) => Text -> Text -> m a -> m a Source

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

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 => LogLevel -> LogSource -> msg -> IO () Source

setLogLevel :: LogLevel -> IO () Source

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

setLogTimeFormat :: String -> IO () Source

Set the format used for log timestamps.

setDebugSourceRegex :: String -> IO () Source

When printing LevelDebug messages, only display those matching the given regexp applied to the Source parameter. Calls to debug without a source parameter are regarded as having a source of "".