polysemy-log-0.9.0.0: Polysemy effects for logging
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Log

Description

 
Synopsis

Introduction

There are at least two libraries that wrap a logging backend with polysemy interpreters. An author of a library who wants to provide log messages faces the problem that committing to a backend requires the user to translate those messages if their chosen backend differs.

polysemy-log provides an abstraction for this task with interpreter adapters for co-log and di, but the library can be used without those as well.

If you're looking for instructions on how to use polysemy-log with a third-party backend, please visit the haddocks of the adapter libraries:

A program using this library might look like this:

prog :: Member Log r => Sem r ()
prog = do
  Log.debug "starting"
  Log.error "nothing happened"

Arbitrary Data Messages

Logging backends usually don't put any restrictions on the data type that represents a log message, so the adapter effect that faces towards the backend is simply polymorphic in that type.

For complex logging purposes, it would be perfectly valid to use DataLog directly, even though this library focuses on simpler messages:

data ComplexMessage = ComplexMessage { points :: Int, user :: Text }

prog :: Member (DataLog ComplexMessage) r => Sem r ()
prog = do
  dataLog (ComplexMessage 500 "googleson78")

data DataLog a :: Effect where Source #

Structural logs, used as a backend for the simpler Text log effect, Log.

Can also be used on its own, or reinterpreted into an effect like those from co-log or di.

Constructors

DataLog :: a -> DataLog a m ()

Schedule an arbitrary value for logging.

type Logger = DataLog (LogEntry LogMessage) Source #

Alias for the logger with the default message type used by Log.

Interpreters

interpretDataLogStderrWith :: Member (Embed IO) r => (a -> Text) -> InterpreterFor (DataLog a) r Source #

Interpret DataLog by printing to stderr, converting messages to Text with the supplied function.

interpretDataLogStderr :: Show a => Member (Embed IO) r => InterpreterFor (DataLog a) r Source #

Interpret DataLog by printing to stderr, converting messages to Text by using Show.

interpretDataLogStdoutWith :: Member (Embed IO) r => (a -> Text) -> InterpreterFor (DataLog a) r Source #

Interpret DataLog by printing to stdout, converting messages to Text with the supplied function.

interpretDataLogStdout :: Show a => Member (Embed IO) r => InterpreterFor (DataLog a) r Source #

Interpret DataLog by printing to stdout, converting messages to Text by using Show.

interpretDataLogAtomic' :: forall a r. Member (AtomicState [a]) r => InterpreterFor (DataLog a) r Source #

Interpret DataLog by prepending each message to a list in an AtomicState.

interpretDataLogAtomic :: forall a r. Member (Embed IO) r => InterpretersFor [DataLog a, AtomicState [a]] r Source #

Interpret DataLog by prepending each message to a list in an AtomicState, then interpret the AtomicState in a TVar.

interpretDataLog :: forall a r. (a -> Sem r ()) -> InterpreterFor (DataLog a) r Source #

Combinator for building DataLog interpreters that handles Local.

Text Messages with Severity and Metadata

While it would be quite reasonable to handle any kind of complexly structured logging data ergonomically with Polysemy, most authors probably prefer not to burden their users with this task while still appreciating the possibility to easily relay debug information in a standardized way.

The default logging effect uses a simple data structure that annotates the given severity and text message with the source location and timestamp:

data LogMessage Source #

User-specified part of the default logging data, consisting of a severity level like warning, error, debug, and a plain text message.

Constructors

LogMessage !Severity Text 

Instances

Instances details
Show LogMessage Source # 
Instance details

Defined in Polysemy.Log.Data.LogMessage

Eq LogMessage Source # 
Instance details

Defined in Polysemy.Log.Data.LogMessage

data LogEntry a Source #

Metadata wrapper for a log message.

Constructors

LogEntry !a !UTCTime !CallStack 

Instances

Instances details
Show a => Show (LogEntry a) Source # 
Instance details

Defined in Polysemy.Log.Data.LogEntry

Methods

showsPrec :: Int -> LogEntry a -> ShowS #

show :: LogEntry a -> String #

showList :: [LogEntry a] -> ShowS #

data Log :: Effect where Source #

The default high-level effect for simple text messages. To be used with the severity constructors:

import qualified Polysemy.Log as Log

prog = do
  Log.debug "debugging…"
  Log.warn "warning!"

Interpreters should preprocess and relay the message to DataLog.

Constructors

Log :: HasCallStack => LogMessage -> Log m ()

Schedule a message to be logged.

log :: HasCallStack => Member Log r => Severity -> Text -> Sem r () Source #

Log a message with the given severity. Basic Sem constructor.

trace :: HasCallStack => Member Log r => Text -> Sem r () Source #

Log a message with the Trace severity.

debug :: HasCallStack => Member Log r => Text -> Sem r () Source #

Log a message with the Debug severity.

info :: HasCallStack => Member Log r => Text -> Sem r () Source #

Log a message with the Info severity.

warn :: HasCallStack => Member Log r => Text -> Sem r () Source #

Log a message with the Warn severity.

error :: HasCallStack => Member Log r => Text -> Sem r () Source #

Log a message with the Error severity.

crit :: HasCallStack => Member Log r => Text -> Sem r () Source #

Log a message with the Crit severity.

formatLogEntry :: LogEntry LogMessage -> Text Source #

Default formatter for the default message type.

data Severity Source #

A log message's severity, or log level.

Constructors

Trace 
Debug 
Info 
Warn 
Error 
Crit 

setLogLevel :: Member (DataLog (LogEntry LogMessage)) r => Maybe Severity -> Sem r a -> Sem r a Source #

Set the minimum severity for messages to be handled, with Nothing meaning no messages are logged.

setLogLevelWith :: forall msg r a. Member (DataLog msg) r => (msg -> Severity) -> Maybe Severity -> Sem r a -> Sem r a Source #

Set the minimum severity for messages to be handled, with Nothing meaning no messages are logged. This can be used with arbitrary message types, using the ex argument to extract the severity from the message.

Interpreters

interpretLogStderrWith :: Members [Embed IO, GhcTime] r => (LogEntry LogMessage -> Text) -> InterpreterFor Log r Source #

Interpret Log by printing to stderr, converting messages to Text with the supplied function.

interpretLogStderrLevelWith :: Members [Embed IO, GhcTime] r => (LogEntry LogMessage -> Text) -> Maybe Severity -> InterpreterFor Log r Source #

Like interpretLogStderrWith, but setting a log level. Nothing causes no messages to be logged.

interpretLogStderrConc :: Members [Resource, Async, Race, Embed IO] r => InterpreterFor Log r Source #

Like interpretLogStderr, but process messages concurrently.

interpretLogStderr :: Members [Embed IO, GhcTime] r => InterpreterFor Log r Source #

Interpret Log by printing to stderr, using the default formatter.

Since this adds a timestamp, it has a dependency on GhcTime. Use interpretLogStderr' for a variant that interprets GhcTime in-place.

interpretLogStderrLevel :: Members [Embed IO, GhcTime] r => Maybe Severity -> InterpreterFor Log r Source #

Like interpretLogStderr, but setting a log level. Nothing causes no messages to be logged.

interpretLogStderr' :: Member (Embed IO) r => InterpreterFor Log r Source #

Interpret Log by printing to stderr, using the default formatter, then interpreting GhcTime.

interpretLogStdoutWith :: Members [Embed IO, GhcTime] r => (LogEntry LogMessage -> Text) -> InterpreterFor Log r Source #

Interpret Log by printing to stdout, converting messages to Text with the supplied function.

interpretLogStdoutLevelWith :: Members [Embed IO, GhcTime] r => (LogEntry LogMessage -> Text) -> Maybe Severity -> InterpreterFor Log r Source #

Like interpretLogStdoutWith, but setting a log level. Nothing causes no messages to be logged.

interpretLogStdoutConc :: Members [Resource, Async, Race, Embed IO] r => InterpreterFor Log r Source #

Like interpretLogStdout, but process messages concurrently.

interpretLogStdout :: Members [Embed IO, GhcTime] r => InterpreterFor Log r Source #

Interpret Log by printing to stdout, using the default formatter.

Since this adds a timestamp, it has a dependency on GhcTime. Use interpretLogStdout' for a variant that interprets GhcTime in-place.

interpretLogStdoutLevel :: Members [Embed IO, GhcTime] r => Maybe Severity -> InterpreterFor Log r Source #

Like interpretLogStdout, but setting a log level. Nothing causes no messages to be logged.

interpretLogStdout' :: Member (Embed IO) r => InterpreterFor Log r Source #

Interpret Log by printing to stdout, using the default formatter, then interpreting GhcTime.

interpretLogDataLog :: Members [DataLog (LogEntry LogMessage), GhcTime] r => InterpreterFor Log r Source #

Interpret Log into DataLog, adding metadata information and wrapping with LogEntry.

Since this adds a timestamp, it has a dependency on GhcTime. Use interpretLogDataLog' for a variant that interprets GhcTime in-place.

interpretLogDataLog' :: Members [DataLog (LogEntry LogMessage), Embed IO] r => InterpretersFor [Log, LogMetadata LogMessage, GhcTime] r Source #

Interpret Log into DataLog, adding metadata information and wrapping with LogEntry.

interpretLogNull :: InterpreterFor Log r Source #

Interpret Log by discarding all messages.

interpretLogAtomic :: Member (Embed IO) r => InterpretersFor [Log, AtomicState [LogMessage]] r Source #

Interpret Log by prepending each message to a list in an AtomicState, then interpret the AtomicState in a TVar.

interpretLogAtomic' :: Member (AtomicState [LogMessage]) r => InterpreterFor Log r Source #

Interpret Log by prepending each message to a list in an AtomicState.

Concurrent Logging

interceptDataLogConc Source #

Arguments

:: forall msg r a. Members [DataLog msg, Resource, Async, Race, Embed IO] r 
=> Int

Queue size. When the queue fills up, the interceptor will block.

-> Sem r a 
-> Sem r a 

Intercept DataLog for concurrent processing. Creates a queue and starts a worker thread. All log messages received by the interceptor in interceptDataLogConcWithLocal are written to the queue and sent to the next DataLog interpreter when the thread reads from the queue.

Since this is an interceptor, it will not remove the effect from the stack, but relay it to another interpreter:

interpretDataLogAtomic (interceptDataLogConc 64 (DataLog.dataLog "message"))

interpretLogDataLogConc :: Members [DataLog (LogEntry LogMessage), Resource, Async, Race, Embed IO] r => Int -> InterpreterFor Log r Source #

Interpret Log into DataLog concurrently, adding metadata information and wrapping with LogEntry.