| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Log
Contents
Description
A logging effect.
There is just one log message type: LogMessage and it is written using logMsg and
the functions built on top of it.
The Logs effect is tightly coupled with the LogWriterReader effect.
When using the ControlMonadBaseControl instance, the underlying monad of the LogWriter,
that is expected to be present through the respective LogWriterReader, is
constrained to be the base monad itself, e.g. IO.
The log message type is fixed to LogMessage, and there is a type class for
converting to that, call ToLogMessage.
There is a single global LogPredicate that can be used to suppress logs directly
at the point where they are sent, in the logMsg function.
Note that all logging is eventually done via logMsg; logMsg is the only place where
log filtering should happen.
Also, LogMessages are evaluated using deepseq, after they pass the LogPredicate, also inside logMsg.
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"Asynchronous Logging
Logging in a withAsync spawned thread is done using withAsyncLogging.
LogPredicates
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 ()
- 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 :: forall h e a. LogsTo h e => LogWriter h -> Eff e a -> Eff e a
- addLogWriter :: forall h e a. (HasCallStack, LogsTo h e, Monad h) => LogWriter h -> Eff e a -> Eff e a
- modifyLogWriter :: forall h e a. LogsTo h e => (LogWriter h -> LogWriter h) -> Eff e a -> Eff e a
- censorLogs :: LogsTo h e => (LogMessage -> LogMessage) -> Eff e a -> Eff e a
- censorLogsM :: (LogsTo h e, Monad h) => (LogMessage -> h LogMessage) -> Eff e a -> Eff e a
- data Logs v
- type LogsTo h e = (Member Logs e, HandleLogWriter h, LogWriterEffects h <:: e, SetMember LogWriterReader (LogWriterReader h) e)
- withLogging :: forall h e a. (Applicative h, LogsTo h (Logs ': (LogWriterReader h ': e))) => LogWriter h -> Eff (Logs ': (LogWriterReader h ': e)) a -> Eff e a
- withSomeLogging :: forall h e a. (Applicative h, LogsTo h (Logs ': (LogWriterReader h ': e))) => Eff (Logs ': (LogWriterReader h ': e)) a -> Eff e a
- runLogs :: forall h e b. LogsTo h (Logs ': 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
Logging 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, LogMessages 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.
Log Message Pre-Filtering
includeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a Source #
Include LogMessages that match a LogPredicate.
excludeLogMessages p allows log message to be logged if p m
Although it is enough if the previous predicate holds.
See excludeLogMessages and modifyLogPredicate.
excludeLogMessages :: forall e a. Member Logs e => LogPredicate -> Eff e a -> Eff e a Source #
Exclude LogMessages 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.
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:
exampleLogPredicate :: IO Int
exampleLogPredicate =
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
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")
askLogPredicate :: forall e. Member Logs e => Eff e LogPredicate Source #
Get the current Logs filter/transformer function.
Log Handling API
Writing Logs
setLogWriter :: forall h e a. LogsTo h e => LogWriter h -> Eff e a -> Eff e a Source #
Replace the current LogWriter.
To add an additional log message consumer use addLogWriter
addLogWriter :: forall h e a. (HasCallStack, LogsTo h e, Monad h) => LogWriter h -> 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 :: forall h e a. LogsTo h e => (LogWriter h -> LogWriter h) -> Eff e a -> Eff e a Source #
Change the current LogWriter.
Log Message Modification
censorLogs :: LogsTo h e => (LogMessage -> LogMessage) -> Eff e a -> Eff e a Source #
Modify the the LogMessages written in the given sub-expression.
Note: This is equivalent to modifyLogWriter . mappingLogWriter
censorLogsM :: (LogsTo h e, Monad h) => (LogMessage -> h LogMessage) -> Eff e a -> Eff e a Source #
Modify the the LogMessages written in the given sub-expression, as in censorLogs
but with a effectful function.
Note: This is equivalent to modifyLogWriter . mappingLogWriterM
Logs Effect Handling
This effect sends LogMessages and is a reader for a LogPredicate.
Logs are sent via logMsg;
for more information about log predicates, see Control.Eff.Log.Handler
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 m, LiftedBase m e, LogsTo m (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, LiftedBase m e, MonadCatch (Eff e), LogsTo m (Logs ': e)) => MonadCatch (Eff (Logs ': e)) Source # | |
| (Applicative m, LiftedBase m e, MonadMask (Eff e), LogsTo m (Logs ': 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 LogsTo h e = (Member Logs e, HandleLogWriter h, LogWriterEffects h <:: e, SetMember LogWriterReader (LogWriterReader h) e) Source #
A constraint alias for effects that requires a LogWriterReader, as well as that the
contained LogWriterReader has a HandleLogWriter instance.
The requirements of this constraint are provided by:
withIoLoggingwithLoggingwithSomeLogging
withLogging :: forall h e a. (Applicative h, LogsTo h (Logs ': (LogWriterReader h ': e))) => LogWriter h -> Eff (Logs ': (LogWriterReader h ': 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"withSomeLogging :: forall h e a. (Applicative h, LogsTo h (Logs ': (LogWriterReader h ': e))) => Eff (Logs ': (LogWriterReader h ': e)) a -> Eff e a Source #
Handles the Logs and LogWriterReader effects.
By default it uses the noOpLogWriter, but using setLogWriter the
LogWriter can be replaced.
This is like withLogging applied to noOpLogWriter
Example:
exampleWithSomeLogging :: ()
exampleWithSomeLogging =
run
$ withSomeLogging @PureLogWriter
$ logDebug "Oh, hi there"Low-Level API for Custom Extensions
Log Message Interception
runLogs :: forall h e b. LogsTo h (Logs ': 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 LogMessages 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 LogMessages 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 LogMessages 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 LogMessages
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