| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Log.Handler
Contents
Description
A memory efficient, streaming, logging effect with support for efficiently not logging when no logs are required.
Good support for logging to a file or to the network, as well as asynchronous logging in another thread.
Synopsis
- logMsg :: forall e m. (HasCallStack, Member Logs e, ToLogMessage m) => m -> Eff e ()
- logWithSeverity :: forall e. (HasCallStack, Member Logs e) => Severity -> String -> Eff e ()
- logEmergency :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logAlert :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logCritical :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logError :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logWarning :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logNotice :: forall e. (HasCallStack, Member Logs e) => String -> Eff e ()
- logInfo :: forall e. (HasCallStack, Member Logs e) => String -> 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
- data LogWriterReader h v
- 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
- withLogFileAppender :: (Lifted IO e, LogsTo IO e, MonadBaseControl IO (Eff e)) => FilePath -> Eff e b -> Eff e b
- 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
- askLogWriter :: SetMember LogWriterReader (LogWriterReader h) e => Eff e (LogWriter h)
- modifyLogWriter :: forall h e a. LogsTo h e => (LogWriter h -> LogWriter h) -> Eff e a -> Eff e a
- data Logs v
- type LogsTo h e = (Member Logs e, SupportsLogger h e, SetMember LogWriterReader (LogWriterReader h) e)
- withConsoleLogging :: SetMember Lift (Lift IO) e => String -> Facility -> LogPredicate -> Eff (Logs ': (LogWriterReader IO ': e)) a -> Eff e a
- withIoLogging :: SetMember Lift (Lift IO) e => LogWriter IO -> String -> Facility -> LogPredicate -> Eff (Logs ': (LogWriterReader IO ': e)) a -> Eff e a
- 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
- type LoggingAndIo = '[Logs, LogWriterReader IO, Lift IO]
- runLogs :: forall h e b. (LogsTo h (Logs ': e), SupportsLogger 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
- runLogWriterReader :: LogWriter h -> Eff (LogWriterReader h ': e) a -> Eff e a
Logging API
Sending Log Messages
logMsg :: forall e m. (HasCallStack, Member Logs e, ToLogMessage m) => m -> 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 -> String -> Eff e () Source #
Log a String as LogMessage with a given Severity.
logEmergency :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a String as emergencySeverity.
logAlert :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a message with alertSeverity.
logCritical :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a criticalSeverity message.
logError :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a errorSeverity message.
logWarning :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a warningSeverity message.
logNotice :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a noticeSeverity message.
logInfo :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a informationalSeverity message.
logDebug :: forall e. (HasCallStack, Member Logs e) => String -> Eff e () Source #
Log a debugSeverity message.
Log Message Pre-Filtering
Ways to change the LogPredicate are:
The current predicate is retrieved via askLogPredicate.
Some pre-defined LogPredicates can be found here: Control.Eff.Log.Message
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
data LogWriterReader h v Source #
A Reader specialized for LogWriters
The existing Reader couldn't be used together with SetMember, so this
lazy reader was written, specialized to reading LogWriter.
Instances
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.
exampleAddLogWriter :: IO ()
exampleAddLogWriter = go >>= putStrLn
where go = fmap (unlines . map renderLogMessage . snd)
$ runLift
$ runCapturedLogsWriter
$ withLogging listLogWriter
$ addLogWriter (mappingLogWriter (lmMessage %~ ("CAPTURED "++)) listLogWriter)
$ 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))
Log Message Modification
withLogFileAppender :: (Lifted IO e, LogsTo IO e, MonadBaseControl IO (Eff e)) => FilePath -> Eff e b -> Eff e b Source #
Open a file and add the LogWriter in the LogWriterReader tha appends the log messages to it.
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
askLogWriter :: SetMember LogWriterReader (LogWriterReader h) e => Eff e (LogWriter h) Source #
Get the current LogWriter.
modifyLogWriter :: forall h e a. LogsTo h e => (LogWriter h -> LogWriter h) -> Eff e a -> Eff e a Source #
Change the current LogWriter.
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, SupportsLogger m (Logs ': e), SetMember LogWriterReader (LogWriterReader m) (Logs ': e)) => MonadBaseControl m (Eff (Logs ': e)) Source # | This instance allows lifting to the The Otherwise there is no way to preserve to log messages. |
| (LiftedBase m e, MonadThrow (Eff e)) => MonadThrow (Eff (Logs ': e)) Source # | |
| (Applicative m, LiftedBase m e, MonadCatch (Eff e), SupportsLogger m (Logs ': e), SetMember LogWriterReader (LogWriterReader m) (Logs ': e)) => MonadCatch (Eff (Logs ': e)) Source # | |
| (Applicative m, LiftedBase m e, MonadMask (Eff e), SupportsLogger m (Logs ': e), SetMember LogWriterReader (LogWriterReader 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, SupportsLogger 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 SupportsLogger instance.
The requirements of this constraint are provided by:
* withStdOutLogging
* withIoLogging
* withLogging
* withSomeLogging
withConsoleLogging :: SetMember Lift (Lift IO) e => String -> Facility -> LogPredicate -> Eff (Logs ': (LogWriterReader IO ': e)) a -> Eff e a Source #
Enable logging to stdout using the defaultIoLogWriter in combination with
the consoleLogWriter.
Example:
exampleWithConsoleLogging :: IO ()
exampleWithConsoleLogging =
runLift
$ withConsoleLogging "my-app" local7 allLogMessages
$ logInfo "Oh, hi there"To vary the LogWriter use withIoLogging.
withIoLogging :: SetMember Lift (Lift IO) e => LogWriter IO -> String -> Facility -> LogPredicate -> Eff (Logs ': (LogWriterReader IO ': e)) a -> Eff e a Source #
Enable logging to IO using the defaultIoLogWriter.
To log to the console (standard output), one can use withConsoleLogging.
Example:
exampleWithIoLogging :: IO ()
exampleWithIoLogging =
runLift
$ withIoLogging consoleLogWriter"my-app" local7 (lmSeverityIsAtLeast informationalSeverity) > $ logInfo "Oh, hi there"
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"type LoggingAndIo = '[Logs, LogWriterReader IO, Lift IO] Source #
The concrete list of Effects for logging with an IO based LogWriter, and a LogWriterReader.
Low-Level API for Custom Extensions
Log Message Interception
runLogs :: forall h e b. (LogsTo h (Logs ': e), SupportsLogger 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.
LogWriter Handling
runLogWriterReader :: LogWriter h -> Eff (LogWriterReader h ': e) a -> Eff e a Source #
Provide the LogWriter
Exposed for custom extensions, if in doubt use withLogging.