Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control.Eff.Log
Contents
Description
FilteredLogging via extensible-effects
FilteredLogging consist of two effects:
- Receiving log messages sent by the code using e.g.
logInfo
; this also include deep evaluation and dropping messages not satisfying the currentLogPredicate
. - Writing log message to disk, network, ... etc; this also includes rendering log messages and setting fields like the hostname, timestamp, etc
Example
exampleLogging :: IO () exampleLogging = runLift $ withLogging consoleLogWriter $ do logDebug "test 1.1" logError "test 1.2" censorLogs (prefixLogMessagesWith "NESTED: ") $ do addLogWriter debugTraceLogWriter $ setLogPredicate (\m -> (view lmMessage m) /= "not logged") $ do logInfo "not logged" logMsg "test 2.1" logWarning "test 2.2" logCritical "test 1.3"
Log Message Data Type
A singular logging event is contained in a LogMessage
s value.
The LogMessage
is modelled along RFC-5424.
There is the ToLogMessage
class for converting to LogMessage
.
Although the author is not clear on how to pursue the approach.
Receiving and Filtering
LogMessage
s are sent using logMsg
and friends, see Control.Eff.Log
Log Message Predicates
There is a single global LogPredicate
that can be used to suppress logs before
they are passed to any LogWriter
.
This is done by the logMsg
function.
Also, LogMessage
s are evaluated using deepseq
, after they pass the LogPredicate
,
also inside logMsg
.
See Control.Eff.Log
Writing and Rendering
Writing is done through a LogWriter
; the current LogWriter
value to use is held by the
LogWriterReader
effect.
Log Message Rendering
Message are rendered by LogMessageRenderer
s found in the Control.Eff.Log.MessageRenderer.
LogWriter
s
- FilteredLogging in a
withAsync
spawned thread is done usingwithAsyncLogging
.
Synopsis
- logMsg :: forall e. (HasCallStack, Member Logs e) => LogMessage -> Eff e ()
- logWithSeverity :: forall e. (HasCallStack, Member Logs e) => Severity -> Text -> Eff e ()
- logWithSeverity' :: forall e. (HasCallStack, Member Logs e) => Severity -> String -> Eff e ()
- logEmergency :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logEmergency' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logAlert :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logAlert' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logCritical :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logCritical' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logError :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logError' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logWarning :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logWarning' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logNotice :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logNotice' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logInfo :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logInfo' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logDebug :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e ()
- logDebug' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logCallStack :: forall e. (HasCallStack, Member Logs e) => Severity -> Eff e ()
- logMultiLine :: forall e. (HasCallStack, Member Logs e) => Severity -> [Text] -> Eff e ()
- logMultiLine' :: forall e. (HasCallStack, Member Logs e) => Severity -> [String] -> Eff e ()
- includeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a
- excludeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a
- setLogPredicate :: forall r b. (Member Logs r, HasCallStack) => LogPredicate -> Eff r b -> Eff r b
- modifyLogPredicate :: forall e b. (Member Logs e, HasCallStack) => (LogPredicate -> LogPredicate) -> Eff e b -> Eff e b
- askLogPredicate :: forall e. Member Logs e => Eff e LogPredicate
- setLogWriter :: IoLogging e => LogWriter -> Eff e a -> Eff e a
- addLogWriter :: IoLogging e => LogWriter -> Eff e a -> Eff e a
- modifyLogWriter :: IoLogging e => (LogWriter -> LogWriter) -> Eff e a -> Eff e a
- censorLogs :: IoLogging e => (LogMessage -> LogMessage) -> Eff e a -> Eff e a
- censorLogsIo :: IoLogging e => (LogMessage -> IO LogMessage) -> Eff e a -> Eff e a
- data Logs v
- type FilteredLogging e = (Member Logs e, Member LogWriterReader e)
- type IoLogging e = (FilteredLogging e, Lifted IO e)
- type LoggingAndIo = '[Logs, LogWriterReader, Lift IO]
- withLogging :: Lifted IO e => LogWriter -> Eff (Logs ': (LogWriterReader ': e)) a -> Eff e a
- withoutLogging :: Eff (Logs ': (LogWriterReader ': e)) a -> Eff e a
- runLogs :: forall e b. (Member LogWriterReader (Logs ': e), Lifted IO e) => LogPredicate -> Eff (Logs ': e) b -> Eff e b
- respondToLogMessage :: forall r b. Member Logs r => (LogMessage -> Eff r ()) -> Eff r b -> Eff r b
- interceptLogMessages :: forall r b. Member Logs r => (LogMessage -> Eff r LogMessage) -> Eff r b -> Eff r b
- module Control.Eff.Log.Message
- module Control.Eff.Log.MessageRenderer
- module Control.Eff.Log.Writer
FilteredLogging API
Sending Log Messages
logMsg :: forall e. (HasCallStack, Member Logs e) => LogMessage -> Eff e () Source #
Log a message.
All logging goes through this function.
This function is the only place where the LogPredicate
is applied.
Also, LogMessage
s are evaluated using deepseq
, after they pass the LogPredicate
.
logWithSeverity :: forall e. (HasCallStack, Member Logs e) => Severity -> Text -> Eff e () Source #
Log a Text
as LogMessage
with a given Severity
.
logWithSeverity' :: forall e. (HasCallStack, Member Logs e) => Severity -> String -> Eff e () Source #
Log a Text
as LogMessage
with a given Severity
.
logEmergency :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a String
as emergencySeverity
.
logEmergency' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a String
as emergencySeverity
.
logAlert :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a message with alertSeverity
.
logAlert' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a message with alertSeverity
.
logCritical :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a criticalSeverity
message.
logCritical' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a criticalSeverity
message.
logError :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a errorSeverity
message.
logError' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a errorSeverity
message.
logWarning :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a warningSeverity
message.
logWarning' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a warningSeverity
message.
logNotice :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a noticeSeverity
message.
logNotice' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a noticeSeverity
message.
logInfo :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a informationalSeverity
message.
logInfo' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a informationalSeverity
message.
logDebug :: forall e. (HasCallStack, Member Logs e) => Text -> Eff e () Source #
Log a debugSeverity
message.
logDebug' :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a debugSeverity
message.
logCallStack :: forall e. (HasCallStack, Member Logs e) => Severity -> Eff e () Source #
logMultiLine :: forall e. (HasCallStack, Member Logs e) => Severity -> [Text] -> Eff e () Source #
Issue a log statement for each item in the list prefixed with a line number and a message hash.
When several concurrent processes issue log statements, multi line log statements are often interleaved.
In order to make the logs easier to read, this function will count the items and calculate a unique hash and prefix each message, so a user can grep to get all the lines of an interleaved, multi-line log message.
Since: 0.30.0
logMultiLine' :: forall e. (HasCallStack, Member Logs e) => Severity -> [String] -> Eff e () Source #
Issue a log statement for each item in the list prefixed with a line number and a message hash.
When several concurrent processes issue log statements, multiline log statements are often interleaved.
In order to make the logs easier to read, this function will count the items and calculate a unique hash and prefix each message, so a user can grep to get all the lines of an interleaved, multi-line log message.
This function takes a list of String
s as opposed to logMultiLine
.
Since: 0.30.0
Log Message Pre-Filtering
Ways to change the LogPredicate
are:
The current predicate is retrieved via askLogPredicate
.
Some pre-defined LogPredicate
s can be found here: Control.Eff.Log.Message
includeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a Source #
Include LogMessage
s that match a LogPredicate
.
includeLogMessages p
allows log message to be logged if p m
Although it is enough if the previous predicate holds.
See excludeLogMessages
and modifyLogPredicate
.
See Control.Eff.Log
excludeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a Source #
Exclude LogMessage
s that match a LogPredicate
.
excludeLogMessages p
discards logs if p m
Also the previous predicate must also hold for a
message to be logged.
See excludeLogMessages
and modifyLogPredicate
.
See Control.Eff.Log
setLogPredicate :: forall r b. (Member Logs r, HasCallStack) => LogPredicate -> Eff r b -> Eff r b Source #
Keep only those messages, for which a predicate holds.
E.g. to keep only messages which begin with OMG
:
exampleSetLogWriter :: IO Int exampleSetLogWriter = runLift $ withLogging consoleLogWriter $ do logMsg "test" setLogPredicate (\ msg -> case view lmMessage msg of 'O':'M':'G':_ -> True _ -> False) (do logMsg "this message will not be logged" logMsg "OMG logged" return 42)
In order to also delegate to the previous predicate, use modifyLogPredicate
See Control.Eff.Log
modifyLogPredicate :: forall e b. (Member Logs e, HasCallStack) => (LogPredicate -> LogPredicate) -> Eff e b -> Eff e b Source #
Change the LogPredicate
.
Other than setLogPredicate
this function allows to include the previous predicate, too.
For to discard all messages currently no satisfying the predicate and also all messages that are to long:
modifyLogPredicate (previousPredicate msg -> previousPredicate msg && length (lmMessage msg) < 29 ) (do logMsg "this message will not be logged" logMsg "this message might be logged")
See Control.Eff.Log
askLogPredicate :: forall e. Member Logs e => Eff e LogPredicate Source #
Get the current Logs
filter/transformer function.
See Control.Eff.Log
Log Handling API
Writing Logs
setLogWriter :: IoLogging e => LogWriter -> Eff e a -> Eff e a Source #
Replace the current LogWriter
.
To add an additional log message consumer use addLogWriter
addLogWriter :: IoLogging e => LogWriter -> Eff e a -> Eff e a Source #
Combine the effects of a given LogWriter
and the existing one.
import Data.Text as T import Data.Text.IO as T exampleAddLogWriter :: IO () exampleAddLogWriter = go >>= T.putStrLn where go = fmap (unlines . map renderLogMessageConsoleLog . snd) $ runLift $ runCaptureLogWriter $ withLogging captureLogWriter $ addLogWriter (mappingLogWriter (lmMessage %~ ("CAPTURED "++)) captureLogWriter) $ addLogWriter (filteringLogWriter severeMessages (mappingLogWriter (lmMessage %~ ("TRACED "++)) debugTraceLogWriter)) $ do logEmergency "test emergencySeverity 1" logCritical "test criticalSeverity 2" logAlert "test alertSeverity 3" logError "test errorSeverity 4" logWarning "test warningSeverity 5" logInfo "test informationalSeverity 6" logDebug "test debugSeverity 7" severeMessages = view (lmSeverity . to (<= errorSeverity))
modifyLogWriter :: IoLogging e => (LogWriter -> LogWriter) -> Eff e a -> Eff e a Source #
Change the current LogWriter
.
Log Message Modification
censorLogs :: IoLogging e => (LogMessage -> LogMessage) -> Eff e a -> Eff e a Source #
Modify the the LogMessage
s written in the given sub-expression.
Note: This is equivalent to modifyLogWriter
. mappingLogWriter
censorLogsIo :: IoLogging e => (LogMessage -> IO LogMessage) -> Eff e a -> Eff e a Source #
Modify the the LogMessage
s written in the given sub-expression, as in censorLogs
but with a effectful function.
Note: This is equivalent to modifyLogWriter
. mappingLogWriterIO
Logs
Effect Handling
This effect sends LogMessage
s and is a reader for a LogPredicate
.
Logs are sent via logMsg
;
for more information about log predicates, see Control.Eff.Log
This effect is handled via withLogging
.
Instances
Handle Logs e a (LogPredicate -> k) Source # | |
Defined in Control.Eff.Log.Handler Methods handle :: (Eff e a -> LogPredicate -> k) -> Arrs e v a -> Logs v -> LogPredicate -> k # handle_relay :: (e ~ (Logs ': r'), Relay (LogPredicate -> k) r') => (a -> LogPredicate -> k) -> (Eff e a -> LogPredicate -> k) -> Eff e a -> LogPredicate -> k # respond_relay :: (a -> LogPredicate -> k) -> (Eff e a -> LogPredicate -> k) -> Eff e a -> LogPredicate -> k # | |
(MonadBase m IO, MonadBaseControl IO (Eff e), LiftedBase m e, Lifted IO e, IoLogging (Logs ': e)) => MonadBaseControl m (Eff (Logs ': e)) Source # | This instance allows lifting the |
(LiftedBase m e, MonadThrow (Eff e)) => MonadThrow (Eff (Logs ': e)) Source # | |
(Applicative m, MonadBaseControl IO (Eff e), LiftedBase m e, MonadCatch (Eff e), IoLogging (Logs ': e), Lifted IO e) => MonadCatch (Eff (Logs ': e)) Source # | |
(Applicative m, MonadBaseControl IO (Eff e), LiftedBase m e, MonadMask (Eff e), IoLogging (Logs ': e), Lifted IO e) => MonadMask (Eff (Logs ': e)) Source # | |
Defined in Control.Eff.Log.Handler Methods mask :: ((forall a. Eff (Logs ': e) a -> Eff (Logs ': e) a) -> Eff (Logs ': e) b) -> Eff (Logs ': e) b # uninterruptibleMask :: ((forall a. Eff (Logs ': e) a -> Eff (Logs ': e) a) -> Eff (Logs ': e) b) -> Eff (Logs ': e) b # generalBracket :: Eff (Logs ': e) a -> (a -> ExitCase b -> Eff (Logs ': e) c) -> (a -> Eff (Logs ': e) b) -> Eff (Logs ': e) (b, c) # | |
type StM (Eff (Logs ': e)) a Source # | |
type FilteredLogging e = (Member Logs e, Member LogWriterReader e) Source #
A constraint that requires Logs
and LogWriterReader
,
and hence supports the functions to filter and modify
logs:
- setLogWriter
- addLogWriter
- modifyLogWriter
- censorLogs
Provided by withLogging
, runLogs
, and also
withoutLogging
and runLogsWithoutLogging
.
Since: 0.31.0
type IoLogging e = (FilteredLogging e, Lifted IO e) Source #
A constraint that requires
and Logs
e
.Lifted
IO
e
Provided by withLogging
and runLogs
.
It contains FilteredLogging
and allows in addition:
- censorLogsIo
Don't infect everything with IO
, if you can fall back to
FilteredLogging
.
Since: 0.24.0
type LoggingAndIo = '[Logs, LogWriterReader, Lift IO] Source #
The concrete list of Eff
ects for logging with a
LogWriter
, and a LogWriterReader
.
This also provides both IoLogging
and FilteredLogging
.
withLogging :: Lifted IO e => LogWriter -> Eff (Logs ': (LogWriterReader ': e)) a -> Eff e a Source #
Handle the Logs
and LogWriterReader
effects.
It installs the given LogWriter
, which determines the underlying
LogWriter
type parameter.
Example:
exampleWithLogging :: IO () exampleWithLogging = runLift $ withLogging consoleLogWriter $ logDebug "Oh, hi there"
This provides the IoLogging
and FilteredLogging
effects.
See also runLogs
.
withoutLogging :: Eff (Logs ': (LogWriterReader ': e)) a -> Eff e a Source #
Handles the Logs
and LogWriterReader
effects, while not invoking the LogWriter
at all.
There is no way to get log output when this logger is used.
Example:
exampleWithSomeLogging :: () exampleWithSomeLogging = run $ withoutLogging $ logDebug "Oh, hi there" -- Nothing written
This provides the FilteredLogging
effect.
See also runLogsWithoutLogging
.
Low-Level API for Custom Extensions
Log Message Interception
runLogs :: forall e b. (Member LogWriterReader (Logs ': e), Lifted IO e) => LogPredicate -> Eff (Logs ': e) b -> Eff e b Source #
Raw handling of the Logs
effect.
Exposed for custom extensions, if in doubt use withLogging
.
respondToLogMessage :: forall r b. Member Logs r => (LogMessage -> Eff r ()) -> Eff r b -> Eff r b Source #
Consume log messages.
Exposed for custom extensions, if in doubt use withLogging
.
Respond to all LogMessage
s logged from the given action,
up to any MonadBaseControl
liftings.
Note that all logging is done through logMsg
and that means
only messages passing the LogPredicate
are received.
The LogMessage
s are consumed once they are passed to the
given callback function, previous respondToLogMessage
invocations
further up in the call stack will not get the messages anymore.
Use interceptLogMessages
if the messages shall be passed
any previous handler.
NOTE: The effects of this function are lost when using
MonadBaseControl
, MonadMask
, MonadCatch
and MonadThrow
.
In contrast the functions based on modifying the LogWriter
,
such as addLogWriter
or censorLogs
, are save to use in combination
with the aforementioned liftings.
interceptLogMessages :: forall r b. Member Logs r => (LogMessage -> Eff r LogMessage) -> Eff r b -> Eff r b Source #
Change the LogMessage
s using an effectful function.
Exposed for custom extensions, if in doubt use withLogging
.
This differs from respondToLogMessage
in that the intercepted messages will be
written either way, albeit in altered form.
NOTE: The effects of this function are lost when using
MonadBaseControl
, MonadMask
, MonadCatch
and MonadThrow
.
In contrast the functions based on modifying the LogWriter
,
such as addLogWriter
or censorLogs
, are save to use in combination
with the aforementioned liftings.
Module Re-Exports
The module that contains the LogMessage
and LogPredicate
definitions.
The log message type corresponds roughly to RFC-5424, including structured data.
module Control.Eff.Log.Message
Rendering functions for LogMessage
s
The functions have been seperated from Control.Eff.Log.Message
This module defines the LogWriter
type, which is used to give
callback functions for log messages an explicit type.
module Control.Eff.Log.Writer