yet-another-logger-0.2.3.1: Yet Another Logger

CopyrightCopyright (c) 2014-2015 PivotCloud, Inc.
LicenseApache License, Version 2.0
MaintainerLars Kuhtz <lkuhtz@pivotmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

System.Logger.Logger.Internal

Contents

Description

This module provides a logger that implements the logger interface that is defined in System.Logger.Types.

If you want to roll your own implementation you may use the code in this module as an example and starting point.

Synopsis

Logger Configuration

data LoggerConfig Source

Logger Configuration

Constructors

LoggerConfig 

Fields

_loggerConfigQueueSize :: !Natural
 
_loggerConfigThreshold :: !LogLevel

initial log threshold, can be changed later on

_loggerConfigScope :: !LogScope

initial stack of log labels, can be extended later on

_loggerConfigPolicy :: !LogPolicy

how to deal with a congested logging pipeline

_loggerConfigExceptionLimit :: !(Maybe Natural)

number of consecutive backend exception that can occur before the logger raises an BackendTooManyExceptions exception. If this is Nothing the logger will discard all exceptions. For instance a value of 1 means that an exception is raised when the second exception occurs. A value of 0 means that an exception is raised for each exception.

@since 0.2

_loggerConfigExceptionWait :: !(Maybe Natural)

number of microseconds to wait after an exception from the backend. If this is Nothing the logger won't wait at all after an exception.

@since 0.2

_loggerConfigExitTimeout :: !(Maybe Natural)

timeout in microseconds for the logger to flush the queue and deliver all remaining log messages on termination. If this is Nothing termination of the logger blogs until all mesages are delivered.

@since 0.2

defaultLoggerConfig :: LoggerConfig Source

Default Logger configuration

The exception limit for backend exceptions is 10 and the wait time between exceptions is 1000. This means that in case of a defunctioned backend the logger will exist by throwing an exception after at least one second. When the logger is terminated it is granted 1 second to flush the queue and deliver all remaining log messages.

pLoggerConfig_ Source

Arguments

:: Text

prefix for this and all subordinate command line options.

-> MParser LoggerConfig 

A version of pLoggerConfig that takes a prefix for the command line option.

@since 0.2

Logger

data Logger a Source

Instances

Generic (Logger a) 
LoggerCtx (Logger a) a 
Typeable (* -> *) Logger 
type Rep (Logger a) 

createLogger :: MonadIO μ => LoggerConfig -> LoggerBackend a -> μ (Logger a) Source

Create a new logger. A logger created with this function must be released with a call to releaseLogger and must not be used after it is released.

The logger calls the backend function exactly once for each log message. If the backend throws an exception, the message is discarded and the exception is dealt with as follows:

  1. The exception is logged. First it is attempt to log to the backend itself. If that fails, due to another exception, the incident is logged to an alternate log sink, usually T.putStrLn or just const (return ()).
  2. The message is discarded. If the backend exception is of type BackendTerminatedException the exception is rethrown by the logger which causes the logger to exit. Otherwise the exception is appended to the exception list.
  3. If the length of the exception list exceeds a configurable threshold a BackendTooManyExceptions exception is thrown (which causes the logger to terminate).
  4. Otherwise the logger waits for a configurable amount of time before proceeding.
  5. The next time the backend returns without throwing an exception the exception list is reset to [].

Backends are expected to implement there own retry logic if required. Backends may base their behavoir on the LogPolicy that is effective for a given message. Please refer to the documentation of LoggerBackend for more details about how to implement and backend.

Backends are called synchronously. Backends authors must thus ensure that a backend returns promptly in accordance with the LogPolicy and the size of the logger queue. For more elaborate failover strategies, such as batching retried messages with the delivery of new messages, backends may implement there only internal queue.

Exceptions of type BlockedIndefinitelyOnSTM and NestedAtomically are rethrown immediately. Those exceptions indicate a bug in the code due to unsafe usage of createLogger. This exceptions shouldn't be possible when withLogger is used to provide the logger and the reference to the logger isn't used outside the scope of the bracket.

createLogger_ Source

Arguments

:: MonadIO μ 
=> (Text -> IO ())

alternate sink for logging exceptions in the logger itself.

-> LoggerConfig 
-> LoggerBackend a 
-> μ (Logger a) 

A version of createLogger that takes as an extra argument a function for logging errors in the logging system.

@since 0.2

releaseLogger :: MonadIO μ => Logger a -> μ () Source

withLogger :: (MonadIO μ, MonadBaseControl IO μ) => LoggerConfig -> LoggerBackend a -> (Logger a -> μ α) -> μ α Source

Provide a computation with a Logger.

Here is an example how this can be used to run a computation with a MonadLog constraint:

withConsoleLogger
    ∷ (MonadIO m, MonadBaseControl IO m)
    ⇒ LogLevel
    → LoggerT T.Text m α
    → m α
withConsoleLogger level inner = do
   withHandleBackend (config ^. logConfigBackend) $ \backend →
       withLogger (config ^. logConfigLogger) backend $ runLoggerT inner
 where
   config = defaultLogConfig
       & logConfigLogger ∘ loggerConfigThreshold .~ level

For detailed information about how backends are executed refer to the documentation of createLogger.

withLogger_ Source

Arguments

:: (MonadIO μ, MonadBaseControl IO μ) 
=> (Text -> IO ())

alternate sink for logging exceptions in the logger itself.

-> LoggerConfig 
-> LoggerBackend a 
-> (Logger a -> μ α) 
-> μ α 

A version of withLogger that takes as an extra argument a function for logging errors in the logging system.

@since 0.2

withLogFunction :: (Show a, Typeable a, NFData a, MonadIO μ, MonadBaseControl IO μ) => LoggerConfig -> LoggerBackend a -> (LogFunctionIO a -> μ α) -> μ α Source

For simple cases, when the logger threshold and the logger scope is constant this function can be used to directly initialize a log function.

withLogFunction_ Source

Arguments

:: (Show a, Typeable a, NFData a, MonadIO μ, MonadBaseControl IO μ) 
=> (Text -> IO ())

alternate sink for logging exceptions in the logger itself.

-> LoggerConfig 
-> LoggerBackend a 
-> (LogFunctionIO a -> μ α) 
-> μ α 

For simple cases, when the logger threshold and the logger scope is constant this function can be used to directly initialize a log function.

@since 0.2

LoggerT Monad Transformer

runLoggerT :: LoggerT a m α -> Logger a -> m α Source

runLogT :: (MonadBaseControl IO m, MonadIO m) => LoggerConfig -> LoggerBackend msg -> LoggerT msg m α -> m α Source

Convenience function that unwraps a MonadLog computation over a newly created Logger