| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Log.Extra.Handler
Contents
- iso8601Handler :: (MonadIO m, MonadMask m) => Handler m Doc -> Handler m Doc
- iso8601PlusHandler :: (MonadIO m, MonadMask m) => Handler m Doc -> Handler m Doc
- rfc822Handler :: (MonadIO m, MonadMask m) => Handler m Doc -> Handler m Doc
- routeHandler :: (MonadIO m, MonadMask m) => Handler m Doc -> Handler m Doc -> (a -> Doc) -> Handler m (WithSeverity a)
- dispatchHandler :: (MonadIO m, MonadMask m) => Handler m Doc -> Handler m Doc -> Handler m (WithSeverity Doc)
- withStdoutHandler :: (MonadIO m, MonadMask m) => (Handler m Doc -> m a) -> m a
- withStderrHandler :: (MonadIO m, MonadMask m) => (Handler m Doc -> m a) -> m a
- withCustomStdoutHandler :: (MonadIO m, MonadMask m) => BatchingOptions -> Float -> Int -> (Handler m Doc -> m a) -> m a
- withCustomStderrHandler :: (MonadIO m, MonadMask m) => BatchingOptions -> Float -> Int -> (Handler m Doc -> m a) -> m a
- customTimestampHandler :: (MonadIO m, MonadMask m) => (UTCTime -> String) -> Handler m Doc -> Handler m Doc
- withCustomHandler :: (MonadIO m, MonadMask m) => Handle -> BatchingOptions -> Float -> Int -> (Handler m Doc -> m a) -> m a
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(WithSeverityDoc) m => m () app =logWarning"Cargo number 2331 has commandeered the vessel"
Quickstart using stdout handler
main :: IO () main =withStdoutHandler$ stdoutHandler ->runLoggingTapp (stdoutHandler .renderWithSeverityid)
Quickstart using a timestamp handler
main :: IO () main =withStdoutHandler$ stdoutHandler ->runLoggingTapp (iso8601HandlerstdoutHandler .renderWithSeverityid)
Quickstart using routing handler
main :: IO () main =withStdoutHandler$ stdoutHandler ->withStderrHandler$ stderrHandler ->runLoggingTapp (routeHandlerstdoutHandler stderrHandlerid)
Quickstart using routing handler with timestamps
main :: IO () main =withStdoutHandler$ stdoutHandler ->withStderrHandler$ stderrHandler ->runLoggingTapp (routeHandler(iso8601HandlerstdoutHandler) (iso8601HandlerstderrHandler)id)
Convenience handler combinators
logging-effect-extra-handler provides combinators for:
Timestamp handlers
iso8601Handler :: (MonadIO m, MonadMask m) => Handler m Doc -> Handler m Doc 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 -> Handler m Doc 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 -> Handler m Doc Source #
Converts an existing handler into a handler that renders an RFC822 timestamp on every log message.
Routing handlers
Arguments
| :: (MonadIO m, MonadMask m) | |
| => Handler m Doc | The handler for non-error messages (i.e. stdout handler) |
| -> Handler m Doc | The handler for error messages (i.e. stderr handler) |
| -> Handler m (WithSeverity Doc) |
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 -> m a) -> m a Source #
Convenience wrapper around withFDHandler for stdout with somewhat sensible defaults.
withStderrHandler :: (MonadIO m, MonadMask m) => (Handler m Doc -> m a) -> m a Source #
Convenience wrapper around withFDHandler for stderr with somewhat sensible defaults.
withCustomStdoutHandler Source #
Arguments
| :: (MonadIO m, MonadMask m) | |
| => BatchingOptions | |
| -> Float | The |
| -> Int | The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible. |
| -> (Handler m Doc -> m a) | |
| -> m a |
Convenience wrapper around withFDHandler for stdout.
withCustomStderrHandler Source #
Arguments
| :: (MonadIO m, MonadMask m) | |
| => BatchingOptions | |
| -> Float | The |
| -> Int | The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible. |
| -> (Handler m Doc -> m a) | |
| -> m a |
Convenience wrapper around withFDHandler for stderr.
Utilities
customTimestampHandler :: (MonadIO m, MonadMask m) => (UTCTime -> String) -> Handler m Doc -> Handler m Doc Source #
Converts an existing handler into a handler that renders a timestamp on every log message. The timestamp is formatted via the input function.
Arguments
| :: (MonadIO m, MonadMask m) | |
| => Handle | |
| -> BatchingOptions | |
| -> Float | The |
| -> Int | The amount of characters per line. Lines longer than this will be pretty-printed across multiple lines if possible. |
| -> (Handler m Doc -> m a) | |
| -> m a |
Convenience wrapper around withFDHandler that enables partially
applying the Handle as the first parameter.