logging-effect-extra-handler-2.0.1: Handy logging handler combinators

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Log.Extra.Handler

Contents

Synopsis

Getting Started

logging-effect-extra-handle supplements logging-effect with convenience handler combinators.

In the quickstart examples, please assume the following is in scope:

app :: MonadLog (WithSeverity (Doc ann)) m => m ()
app = logWarning "Cargo number 2331 has commandeered the vessel"

Quickstart using stdout handler

main :: IO ()
main = withStdoutHandler $ stdoutHandler ->
  runLoggingT app (stdoutHandler . renderWithSeverity id)

Quickstart using a timestamp handler

main :: IO ()
main = withStdoutHandler $ stdoutHandler ->
  runLoggingT app (iso8601Handler stdoutHandler . renderWithSeverity id)

Quickstart using routing handler

main :: IO ()
main =
  withStdoutHandler $ stdoutHandler ->
  withStderrHandler $ stderrHandler ->
  runLoggingT app (routeHandler stdoutHandler stderrHandler id)

Quickstart using routing handler with timestamps

main :: IO ()
main =
  withStdoutHandler $ stdoutHandler ->
  withStderrHandler $ stderrHandler ->
  runLoggingT app (routeHandler (iso8601Handler stdoutHandler) (iso8601Handler stderrHandler) id)

Convenience handler combinators

logging-effect-extra-handler provides combinators for:

  • producing timestamping handlers from existing handlers
  • convenience handlers for stdout and stderr
  • dispatching handler to route messages to non-error and error handlers

Timestamp handlers

iso8601Handler :: (MonadIO m, MonadMask m) => Handler m (Doc ann) -> Handler m (Doc ann) Source #

Converts an existing handler into a handler that renders an ISO8601 (i.e. YYYY-MM-DDTHH:MM:SS) timestamp on every log message.

iso8601PlusHandler :: (MonadIO m, MonadMask m) => Handler m (Doc ann) -> Handler m (Doc ann) Source #

Converts an existing handler into a handler that renders an ISO8601 (i.e. YYYY-MM-DDTHH:MM:SS with decimal point and fraction of second) timestamp on every log message.

rfc822Handler :: (MonadIO m, MonadMask m) => Handler m (Doc ann) -> Handler m (Doc ann) Source #

Converts an existing handler into a handler that renders an RFC822 timestamp on every log message.

Routing handlers

routeHandler Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> Handler m (Doc ann)

The handler for non-error messages (i.e. stdout handler)

-> Handler m (Doc ann)

The handler for error messages (i.e. stderr handler)

-> (a -> Doc ann)

How to render

-> Handler m (WithSeverity a) 

Basic dispatch handler that routes Warning, Notice, Informational, and Debug messages to the first input handler and routes Emergency, Alert, Critical, and Error messages to the second input handler.

dispatchHandler Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> Handler m (Doc ann)

The handler for non-error messages (i.e. stdout handler)

-> Handler m (Doc ann)

The handler for error messages (i.e. stderr handler)

-> Handler m (WithSeverity (Doc ann)) 

Deprecated: dispatchHandler is deprecated in favor of routeHandler.

Basic dispatch handler that routes Warning, Notice, Informational, and Debug messages to the first input handler and routes Emergency, Alert, Critical, and Error messages to the second input handler. This function is limiting as it assumes incoming messages are WithSeverity Doc instead of the more general WithSeverity a.

Shortcuts for stdout/stderr handlers

withStdoutHandler :: (MonadIO m, MonadMask m) => (Handler m (Doc ann) -> m a) -> m a Source #

Convenience wrapper around withFDHandler for stdout with somewhat sensible defaults.

withStderrHandler :: (MonadIO m, MonadMask m) => (Handler m (Doc ann) -> m a) -> m a Source #

Convenience wrapper around withFDHandler for stderr with somewhat sensible defaults.

withCustomStdoutHandler Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> BatchingOptions 
-> Double

The ribbonFrac parameter to renderPretty

-> Int

The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible.

-> (Handler m (Doc ann) -> m a) 
-> m a 

Convenience wrapper around withFDHandler for stdout.

withCustomStderrHandler Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> BatchingOptions 
-> Double

The ribbonFrac parameter to renderPretty

-> Int

The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible.

-> (Handler m (Doc ann) -> m a) 
-> m a 

Convenience wrapper around withFDHandler for stderr.

Utilities

customTimestampHandler :: (MonadIO m, MonadMask m) => (UTCTime -> String) -> Handler m (Doc ann) -> Handler m (Doc ann) Source #

Converts an existing handler into a handler that renders a timestamp on every log message. The timestamp is formatted via the input function.

withCustomHandler Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> Handle 
-> BatchingOptions 
-> Double

The ribbonFrac parameter to renderPretty

-> Int

The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible.

-> (Handler m (Doc ann) -> m a) 
-> m a 

Convenience wrapper around withFDHandler that enables partially applying the Handle as the first parameter.