| 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 |
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.
- module System.Logger.Types
- data Logger a
- withLogger :: (MonadIO μ, MonadBaseControl IO μ) => LoggerConfig -> LoggerBackend a -> (Logger a -> μ α) -> μ α
- withLogFunction :: (Show a, Typeable a, NFData a, MonadIO μ, MonadBaseControl 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 Int
- loggerConfigThreshold :: Lens' LoggerConfig LogLevel
- loggerConfigScope :: Lens' LoggerConfig LogScope
- defaultLoggerConfig :: LoggerConfig
- validateLoggerConfig :: ConfigValidation LoggerConfig λ
- pLoggerConfig :: 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 .~ levelwithLogFunction :: (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
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
Constructors
| LoggerConfig | |
Fields
| |