Copyright | Copyright (c) 2014-2015 PivotCloud, Inc. |
---|---|
License | Apache License, Version 2.0 |
Maintainer | Lars Kuhtz <lkuhtz@pivotmail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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.
- module System.Logger.Types
- data Logger a
- withLogger :: (MonadIO μ, MonadBaseControl IO μ) => LoggerConfig -> LoggerBackend a -> (Logger a -> μ α) -> μ α
- withLogger_ :: (MonadIO μ, MonadBaseControl IO μ) => (Text -> IO ()) -> LoggerConfig -> LoggerBackend a -> (Logger a -> μ α) -> μ α
- withLogFunction :: (Show a, Typeable a, NFData a, MonadIO μ, MonadBaseControl IO μ) => LoggerConfig -> LoggerBackend a -> (LogFunctionIO a -> μ α) -> μ α
- withLogFunction_ :: (Show a, Typeable a, NFData a, MonadIO μ, MonadBaseControl IO μ) => (Text -> IO ()) -> LoggerConfig -> LoggerBackend a -> (LogFunctionIO a -> μ α) -> μ α
- type LoggerT a = LoggerCtxT (Logger a)
- runLoggerT :: LoggerT a m α -> Logger a -> m α
- runLogT :: (MonadBaseControl IO m, MonadIO m) => LoggerConfig -> LoggerBackend msg -> LoggerT msg m α -> m α
- data LoggerConfig = LoggerConfig {}
- loggerConfigQueueSize :: Lens' LoggerConfig Natural
- loggerConfigThreshold :: Lens' LoggerConfig LogLevel
- loggerConfigScope :: Lens' LoggerConfig LogScope
- loggerConfigPolicy :: Lens' LoggerConfig LogPolicy
- loggerConfigExceptionLimit :: Lens' LoggerConfig (Maybe Natural)
- loggerConfigExceptionWait :: Lens' LoggerConfig (Maybe Natural)
- loggerConfigExitTimeout :: Lens' LoggerConfig (Maybe Natural)
- defaultLoggerConfig :: LoggerConfig
- validateLoggerConfig :: ConfigValidation LoggerConfig λ
- pLoggerConfig :: MParser LoggerConfig
- pLoggerConfig_ :: Text -> MParser LoggerConfig
Re-Export Logger Interface
module System.Logger.Types
Logger
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
.
:: (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.
:: (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
type LoggerT a = LoggerCtxT (Logger a) Source
runLoggerT :: LoggerT a m α -> Logger a -> m α Source
runLogT :: (MonadBaseControl IO m, MonadIO m) => LoggerConfig -> LoggerBackend msg -> LoggerT msg m α -> m α Source
Configuration Types
Logger Configuration
data LoggerConfig Source
Logger Configuration
LoggerConfig | |
|
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.
:: 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