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

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

Instances details
Generic (Logger a) Source # 
Instance details

Defined in System.Logger.Logger.Internal

Associated Types

type Rep (Logger a) :: Type -> Type #

Methods

from :: Logger a -> Rep (Logger a) x #

to :: Rep (Logger a) x -> Logger a #

LoggerCtx (Logger a) a Source # 
Instance details

Defined in System.Logger.Logger.Internal

type Rep (Logger a) Source # 
Instance details

Defined in System.Logger.Logger.Internal

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

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

Configuration Types

Logger Configuration

data LoggerConfig Source #

Logger Configuration

Constructors

LoggerConfig 

Fields

Instances

Instances details
Eq LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

Ord LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

Read LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

Show LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

Generic LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

Associated Types

type Rep LoggerConfig :: Type -> Type #

NFData LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

Methods

rnf :: LoggerConfig -> () #

ToJSON LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

FromJSON (LoggerConfig -> LoggerConfig) Source # 
Instance details

Defined in System.Logger.Logger.Internal

type Rep LoggerConfig Source # 
Instance details

Defined in System.Logger.Logger.Internal

type Rep LoggerConfig = D1 ('MetaData "LoggerConfig" "System.Logger.Logger.Internal" "yet-another-logger-0.4.1-J79MEOzaz0waG5wG6Tk1C" 'False) (C1 ('MetaCons "LoggerConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_loggerConfigQueueSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural) :*: (S1 ('MetaSel ('Just "_loggerConfigThreshold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LogLevel) :*: S1 ('MetaSel ('Just "_loggerConfigScope") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LogScope))) :*: ((S1 ('MetaSel ('Just "_loggerConfigPolicy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LogPolicy) :*: S1 ('MetaSel ('Just "_loggerConfigExceptionLimit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Natural))) :*: (S1 ('MetaSel ('Just "_loggerConfigExceptionWait") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "_loggerConfigExitTimeout") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Natural))))))

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