co-log-polysemy-formatting-0.1.1.0: A Polysemy logging effect for high quality (unstructured) logs.
Safe HaskellNone
LanguageHaskell2010

Colog.Polysemy.Formatting

Description

Checklist for use:

  1. Add `co-log-polysemy-formatting` to your `build-depends` in your .cabal file,
  2. Turn on the OverloadedStrings language extension,
  3. `import Colog.Polysemy.Formatting`
  4. (optional) Add the HasCallStack constrain to your main if it calls any logging functions directly,
  5. Create a logging environment with newLogEnv, e.g. like this: logEnvStderr <- newLogEnv stderr
  6. To create log messages from within the Sem monad, add the WithLog r constraint and then call any of the logging functions: logDebug, logInfo, logWarning, logError, or logException. Note that these take a Formatting formatter, not a StringTextetc. But note also that they can still take a string literal, which will be transformed into a formatter using OverloadedStrings.
  7. (optional) When interpreting your program, add a call to filterLogs to e.g. filter out Debug messages for a production build,
  8. call addThreadAndTimeToLog,
  9. call runLogAction, including a call to renderThreadTimeMessage or renderThreadTimeMessageShort with the LogEnv you created in step 4, e.g. like this: runLogAction (logTextStderr & cmap (renderThreadTimeMessage logEnvStderr)).

Example of usage (this is a copy of example/Main.hs, which you can compile and run for yourself):

-- Required for formatting
{-# LANGUAGE OverloadedStrings #-}

-- Required for Polysemy
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}

-- Required for co-log-polysemy-formatting.
-- This should re-export everything you need for logging.
import Colog.Polysemy.Formatting

-- Other imports for this example
import Data.Function ((&))
import Formatting
import Polysemy
import Polysemy.Async
import System.IO (stderr)

-- main needs the 'HasCallStack' constraint for log functions to know where they were called from
main :: HasCallStack => IO ()
main = do
  -- Set up a logging environment, logging to stderr and using the local timezone
  logEnvStderr <- newLogEnv stderr

  (do
    -- This debug message will show up only if 'debugMode' is True
    logDebug "MyApp version 0.1.0.0"

    -- Run our Polysemy program
    program
    )
      -- Set the level of logging we want (for more control see 'filterLogs')
      & setLogLevel Debug

      -- This lets us log the thread id and message timestamp with each log message
      -- It transforms the 'Log Message' effect into a 'Log ThreadTimeMessage' effect.
      & addThreadAndTimeToLog

      -- If you are using the 'Async' effect then interpret it here, after adding the thread and time,
      -- but before running the log action.
      & asyncToIO

      -- Log to stderr, using our logging environment
      & runLogAction (logTextStderr & cmap (renderThreadTimeMessage logEnvStderr))

      & runM

-- The 'WithLog r' constraint expands to '(HasCallStack, Member (Log Message) r)'
program :: (WithLog r, Members '[Async, Embed IO] r) => Sem r ()
program = do
  -- This concurrency is just here to demonstrate that it is possible.
  -- It isn't required.
  _ <- sequenceConcurrently $
    replicate 10 asyncProg
    <> [logError ("Error message: '" % accessed fst text <> "', number: " % accessed snd int) ("It's all broken!", 17 :: Int)]
    <> replicate 10 asyncProg
  pure ()
  where
    asyncProg = do
      logInfo "Hello, logging!"
      embed $ fprintLn "Hello, logging!"

The above produces this:

Synopsis

Creating log messages

type WithLog r = WithLog' (Msg Severity) r Source #

Add this constraint to a type signature to require the Log effect, with callstack support, using the 'Msg Severity' message type.

type WithLog' msg r = (HasCallStack, Member (Log msg) r) Source #

This constraint allows you to specify a custom message type. Otherwise, use WithLog instead.

logDebug :: WithLog r => Format (Sem r ()) a -> a Source #

Log a debug message in the given format.

logInfo :: WithLog r => Format (Sem r ()) a -> a Source #

Log an info message in the given format.

logWarning :: WithLog r => Format (Sem r ()) a -> a Source #

Log a warning in the given format.

logError :: WithLog r => Format (Sem r ()) a -> a Source #

Log an error in the given format.

logException :: (WithLog r, Exception e) => e -> Sem r () Source #

Log the exception as an error.

Interpreting the log

newLogEnv :: Handle -> IO LogEnv Source #

Create a LogEnv suitable for the given handle. If the output is an interactive terminal which supports color, then the output will be in color. If not then the output will be plain text without color. The timezone used will be that of the current machine.

ignoreLog :: Sem (Log msg ': r) a -> Sem r a Source #

Interpret the Log effect by completely ignoring all log messages.

filterLogs :: Member (Log msg) r => (msg -> Bool) -> Sem (Log msg ': r) a -> Sem r a Source #

Remove any log messages that don't pass the given predicate.

E.g: filterLogs ((<) Info . msgSeverity) will remove any logs that are Debug or Info severity, leaving only Warnings and Errors.

setLogLevel :: (HasSeverity msg, Member (Log msg) r) => Severity -> Sem (Log msg ': r) a -> Sem r a Source #

Only show logs that are this log level or higher (lower according to the Ord instance for Severity).

E.g: setLogLevel Debug will show all logs, whereas setLogLevel Warning will show only warnings and errors.

addThreadAndTimeToLog :: Members '[Embed IO, Log ThreadTimeMessage] r => Sem (Log Message ': r) a -> Sem r a Source #

Add the thread id and a timestamp to messages in the log. This should be called before any use of asyncToIO, otherwise all log messages will have the same thread id. It is best called after any use of filterLogs, otherwise you're needlessly processing messages that will never be logged (TODO: test this assertion is true).

renderThreadTimeMessage :: LogEnv -> ThreadTimeMessage -> Text Source #

Render the message, optionally in color, with green " | " separating fields, and these fields:

  • Severity (e.g. INFO, see fSeverity),
  • Timestamp (e.g. "2020-10-13T16:58:43.982720690+1100", see fIso8601Tz),
  • Thread Id (e.g. "Thread 8", see fThread),
  • Caller (e.g. "MyApp.CLI.cliMain#43", see fCallerLong), and
  • The log message itself.

E.g: "INFO | 2020-10-13T17:06:52.408921221+1100 | Thread 8 | MyApp.CLI.cliMain#43 | MyApp version 0.1.0.0"

The first three columns are fixed-width, which makes visual scanning of the log easier.

Re-exports from other packages

type HasCallStack = ?callStack :: CallStack #

Request a CallStack.

NOTE: The implicit parameter ?callStack :: CallStack is an implementation detail and should not be considered part of the CallStack API, we may decide to change the implementation in the future.

Since: base-4.9.0.0

runLogAction :: forall (m :: Type -> Type) msg (r :: [(Type -> Type) -> Type -> Type]) a. Member (Embed m) r => LogAction m msg -> Sem (Log msg ': r) a -> Sem r a #

Run a Log effect in terms of the given LogAction. The idea behind this function is the following: if you have LogAction m msg then you can use this action to tell how to io interpret effect Log. However, this is only possible if you also have Lift m effect because running log action requires access to monad m.

This function allows to use extensible effects provided by the polysemy library with logging provided by co-log. You can construct LogAction independently and then just pass to this function to tell how to log messages.

Several examples:

  1. runLogAction mempty: interprets the Log effect by ignoring all messages.
  2. runLogAction logStringStdout: interprets Log effect by allowing to log String to stdout.

logTextStdout :: forall (m :: Type -> Type). MonadIO m => LogAction m Text #

Action that prints Text to stdout.

logTextStderr :: forall (m :: Type -> Type). MonadIO m => LogAction m Text #

Action that prints Text to stderr.

logTextHandle :: forall (m :: Type -> Type). MonadIO m => Handle -> LogAction m Text #

Action that prints Text to Handle.

cmap :: forall a b (m :: Type -> Type). (a -> b) -> LogAction m b -> LogAction m a #

This combinator is contramap from contravariant functor. It is useful when you have something like

data LogRecord = LR
    { lrName    :: LoggerName
    , lrMessage :: Text
    }

and you need to provide LogAction which consumes LogRecord

logRecordAction :: LogAction m LogRecord

when you only have action that consumes Text

logTextAction :: LogAction m Text

With cmap you can do the following:

logRecordAction :: LogAction m LogRecord
logRecordAction = cmap lrMesssage logTextAction

This action will print only lrMessage from LogRecord. But if you have formatting function like this:

formatLogRecord :: LogRecord -> Text

you can apply it instead of lrMessage to log formatted LogRecord as Text.

data Severity #

Severity for the log messages.

Constructors

Debug

Information useful for debug purposes.

E.g. output of the function that is important for the internal development, not for users. Like, the result of SQL query.

Info

Normal operational information.

E.g. describing general steps: starting application, finished downloading.

Warning

General warnings, non-critical failures.

E.g. couldn't download icon from some service to display.

Error

General errors/severe errors.

E.g. exceptional situations: couldn't syncronize accounts.

Instances

Instances details
Bounded Severity 
Instance details

Defined in Colog.Core.Severity

Enum Severity 
Instance details

Defined in Colog.Core.Severity

Eq Severity 
Instance details

Defined in Colog.Core.Severity

Ord Severity 
Instance details

Defined in Colog.Core.Severity

Read Severity 
Instance details

Defined in Colog.Core.Severity

Show Severity 
Instance details

Defined in Colog.Core.Severity

Ix Severity 
Instance details

Defined in Colog.Core.Severity

HasSeverity (Msg Severity) Source # 
Instance details

Defined in Colog.Polysemy.Formatting.ThreadTimeMessage

data Msg sev #

General logging message data type. Contains the following fields:

  1. Polymorphic severity. This can be anything you want if you need more flexibility.
  2. Function CallStack. It provides useful information about source code locations where each particular function was called.
  3. Custom text for logging.

Constructors

Msg 

Fields

Instances

Instances details
HasSeverity (Msg Severity) Source # 
Instance details

Defined in Colog.Polysemy.Formatting.ThreadTimeMessage