log-warper-1.8.10: Flexible, configurable, monadic and pretty logging

Copyright(c) Serokell 2016
LicenseGPL-3 (see the file LICENSE)
MaintainerSerokell <hi@serokell.io>
Stabilityexperimental
PortabilityPOSIX, GHC
Safe HaskellNone
LanguageHaskell2010

System.Wlog.LoggerConfig

Contents

Description

Logger configuration.

Synopsis

Documentation

data RotationParameters Source #

Parameters for logging rotation.

Constructors

RotationParameters 

Fields

fromScratch :: Monoid m => State m a -> m Source #

Useful lens combinator to be used for logging initialization. Usually should be used with zoomLogger.

isValidRotation :: RotationParameters -> Bool Source #

Checks if logger rotation parameters are valid.

Hierarchical tree of loggers (with lenses)

data HandlerWrap Source #

Wrapper over file handler with additional rounding option.

Constructors

HandlerWrap 

Fields

  • _hwFilePath :: !FilePath

    Path to the file to be handled.

  • _hwRounding :: !(Maybe Int)

    Round timestamps to this power of 10 picoseconds. Just 3 would round to nanoseconds. Just 12 would round to seconds.

data LoggerTree Source #

Stores configuration for hierarchical loggers.

Instances

Show LoggerTree Source # 
Generic LoggerTree Source # 

Associated Types

type Rep LoggerTree :: * -> * #

Semigroup LoggerTree Source # 
Monoid LoggerTree Source # 
ToJSON LoggerTree Source # 
FromJSON LoggerTree Source # 
type Rep LoggerTree Source # 
type Rep LoggerTree = D1 * (MetaData "LoggerTree" "System.Wlog.LoggerConfig" "log-warper-1.8.10-FakDbTTnr7WH8HbjCmkInF" False) (C1 * (MetaCons "LoggerTree" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ltSubloggers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * LoggerMap)) ((:*:) * (S1 * (MetaSel (Just Symbol "_ltFiles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [HandlerWrap])) (S1 * (MetaSel (Just Symbol "_ltSeverity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Severities))))))

Global logger configuration

data LoggerConfig Source #

Logger configuration which keeps RotationParameters and LoggerTree.

Constructors

LoggerConfig 

Fields

Lenses

zoomLogger :: LoggerName -> State LoggerTree () -> State LoggerTree () Source #

Zooming into logger name with putting specific key.

atLogger :: LoggerName -> Traversal' LoggerConfig LoggerTree Source #

Lens to help to change some particular logger properties.

For example if you want to use default configurations, but need to change logger's severity to warningPlus you can do it this way:

launchWithConfig
    ( defaultConfig "myLogger"
    & atLogger "myLogger"
    . ltSeverity ?~ warningPlus )
    "myLogger"
    action

Builders for LoggerConfig

customConsoleActionB :: Maybe (Handle -> Text -> IO ()) -> LoggerConfig Source #

Setup lcConsoleOutput inside LoggerConfig.

logsDirB :: FilePath -> LoggerConfig Source #

Setup lcLogsDirectory inside LoggerConfig to specific prefix.

productionB :: LoggerConfig Source #

Adds sensible predefined set of parameters to logger.