Safe Haskell | None |
---|---|
Language | Haskell2010 |
Checklist for use:
- Add `co-log-polysemy-formatting` to your `build-depends` in your .cabal file,
- Turn on the OverloadedStrings language extension,
- `import Colog.Polysemy.Formatting`
- (optional) Add the
HasCallStack
constrain to yourmain
if it calls any logging functions directly, - Create a logging environment with
newLogEnv
, e.g. like this:logEnvStderr <- newLogEnv stderr
- To create log messages from within the
Sem
monad, add the
constraint and then call any of the logging functions:WithLog
rlogDebug
,logInfo
,logWarning
,logError
, orlogException
. 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. - (optional) When interpreting your program, add a call to
filterLogs
to e.g. filter out Debug messages for a production build, - call
addThreadAndTimeToLog
, - call
runLogAction
, including a call torenderThreadTimeMessage
orrenderThreadTimeMessageShort
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 & 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 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
- type WithLog r = WithLog' (Msg Severity) r
- type WithLog' msg r = (HasCallStack, Member (Log msg) r)
- logDebug :: WithLog r => Format (Sem r ()) a -> a
- logInfo :: WithLog r => Format (Sem r ()) a -> a
- logWarning :: WithLog r => Format (Sem r ()) a -> a
- logError :: WithLog r => Format (Sem r ()) a -> a
- logException :: (WithLog r, Exception e) => e -> Sem r ()
- newLogEnv :: Handle -> IO LogEnv
- ignoreLog :: Sem (Log msg ': r) a -> Sem r a
- filterLogs :: Member (Log msg) r => (msg -> Bool) -> Sem (Log msg ': r) a -> Sem r a
- setLogLevel :: (HasSeverity msg, Member (Log msg) r) => Severity -> Sem (Log msg ': r) a -> Sem r a
- addThreadAndTimeToLog :: Members '[Embed IO, Log ThreadTimeMessage] r => Sem (Log Message ': r) a -> Sem r a
- renderThreadTimeMessage :: LogEnv -> ThreadTimeMessage -> Text
- type HasCallStack = ?callStack :: CallStack
- 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
- logTextStdout :: forall (m :: Type -> Type). MonadIO m => LogAction m Text
- logTextStderr :: forall (m :: Type -> Type). MonadIO m => LogAction m Text
- logTextHandle :: forall (m :: Type -> Type). MonadIO m => Handle -> LogAction m Text
- cmap :: forall a b (m :: Type -> Type). (a -> b) -> LogAction m b -> LogAction m a
- data Severity
- data Msg sev = Msg {
- msgSeverity :: !sev
- msgStack :: !CallStack
- msgText :: !Text
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.
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.
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
then you can use this
action to tell how to io interpret effect LogAction
m msgLog
. However, this is only possible
if you also have
effect because running log action requires access to
monad Lift
mm
.
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:
: interprets therunLogAction
memptyLog
effect by ignoring all messages.
: interpretsrunLogAction
logStringStdout
Log
effect by allowing to logString
tostdout
.
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.
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
.
Severity for the log messages.
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
Bounded Severity | |
Enum Severity | |
Eq Severity | |
Ord Severity | |
Defined in Colog.Core.Severity | |
Read Severity | |
Show Severity | |
Ix Severity | |
Defined in Colog.Core.Severity | |
HasSeverity (Msg Severity) Source # | |
Defined in Colog.Polysemy.Formatting.ThreadTimeMessage |
General logging message data type. Contains the following fields:
- Polymorphic severity. This can be anything you want if you need more flexibility.
- Function
CallStack
. It provides useful information about source code locations where each particular function was called. - Custom text for logging.
Instances
HasSeverity (Msg Severity) Source # | |
Defined in Colog.Polysemy.Formatting.ThreadTimeMessage |