yet-another-logger-0.1.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

Contents

Description

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

All the code of this module is in System.Logger.Logger.Internal.

The definitions in System.Logger.Types are re-exported by this module.

Synopsis

Re-Export Logger Interface

Logger

data Logger a Source

Instances

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

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

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.

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

Configuration Types

Logger Configuration

data LoggerConfig Source

Logger Configuration

Constructors

LoggerConfig 

Fields

_loggerConfigQueueSize :: !Int
 
_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