simple-logging-0.2.0.0: Logging effect to plug into the simple-effects framework

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Logging

Description

Use this module to add logging to your monad. A log is a structured value that can hold information like severity, log message, timestamp, callstack, etc.

Logging is treated like a stream of logs comming from your application and functions that transform the logs take a stream and output a stream. Functions like logInfo push a new log into the stream and functions like setTimestampToNow take a stream of logs and attach extra info onto each log (current time in this case).

Read the documentation of individual functions to get a feel for what you can do.

Synopsis

Documentation

data Logging Source #

The logging effect.

Constructors

Logging 

newtype Tag Source #

Arbitrary piece of text. Logs contain a list of these.

Constructors

Tag Text 

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Ord Tag Source # 

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

newtype Context Source #

A name for a "layer" of your application. Typically, a log will contain a stack of contexts. Think of it as a call stack specific for your application.

Constructors

Context 

Fields

data Level Source #

The severity of the log.

Constructors

Fatal 
Error 
Warning 
Info 
Debug 

data LogUser Source #

If a notion of a user exists for your application, you can add this information to your logs.

data Crumb Source #

Breadcrumbs are the steps that happened before a log.

data CrumbData Source #

Crumbs come in two varieties. A normal crumb is a list of key-value pairs. There's also a HttpCrumb where you can put more specific information about the processed HTTP request (if your application is a web server).

logEffect :: MonadEffect Logging m => Log -> m () Source #

Send a single log into the stream.

handleLogging :: Functor m => (Log -> m ()) -> EffectHandler Logging m a -> m a Source #

A generic handler for logs. Since it's polymorphic in m you can choose to emit more logs and make it a log transformer instead.

layerLogs :: MonadEffect Logging m => Context -> EffectHandler Logging m a -> m a Source #

Add a new context on top of every log that comes from the given computation.

originContext :: Log -> Maybe Context Source #

Get the bottom-most context if it exists.

logAndError :: (Exception e, MonadEffect Logging m, MonadThrow m, HasCallStack) => Text -> e -> m a Source #

Log an error and then throw the given exception.

logAndThrowsErr :: (MonadEffect Logging m, Throws e m, HasCallStack) => Text -> e -> m a Source #

Log an error and then throw a checked exception. Read about checked exceptions in Signal.

logAndThrowGeneric :: (MonadEffect Logging m, MonadThrow m, HasCallStack) => Text -> m a Source #

Log an error and throw a generic exception containing the text of the error message.

logMessagesToStdout :: MonadIO m => EffectHandler Logging m a -> m a Source #

Log a stripped-down version of the logs to the console. Only contains the message and the severity.

logRawToStdout :: MonadIO m => EffectHandler Logging m a -> m a Source #

Log everything to the console. Uses the Show instance for Log.

muteLogs :: Monad m => EffectHandler Logging m a -> m a Source #

Discard the logs.

witherLogs :: MonadEffect Logging m => (Log -> m (Maybe Log)) -> EffectHandler Logging m a -> m a Source #

Use the given function to transform and possibly discard logs.

filterLogs :: MonadEffect Logging m => (Log -> Bool) -> EffectHandler Logging m a -> m a Source #

Only let through logs that satisfy the given predicate.

mapLogs :: MonadEffect Logging m => (Log -> m Log) -> EffectHandler Logging m a -> m a Source #

Transform logs with the given function.

logIfDepthLessThan :: MonadEffect Logging m => Int -> EffectHandler Logging m a -> m a Source #

Filter out logs that are comming from below a certain depth.

logIfDepth :: MonadEffect Logging m => (Int -> Bool) -> EffectHandler Logging m a -> m a Source #

Filter logs whose depth satisfies the given predicate.

messagesToCrumbs :: (MonadIO m, MonadEffect Logging m) => EffectHandler Logging m a -> m a Source #

For each log, add it's message to the logs breadcrumb list. This is useful so you don't have to manually add crumbs.

collectCrumbs :: MonadEffect Logging m => EffectHandler Logging (StateT [Crumb] m) a -> m a Source #

Each log that passes through will get all of the crumbs of the previous logs added. If, for example, you're writing a web server, you might want to have this handler over the request handler so that if an error occurs you can see all the steps that happened before it, during the handling of that request.

addUserToLogs :: MonadEffect Logging m => LogUser -> EffectHandler Logging m a -> m a Source #

Add a user to every log.

addCrumbToLogs :: MonadEffect Logging m => Crumb -> EffectHandler Logging m a -> m a Source #

Add a crumb to every log.

setDataTo :: MonadEffect Logging m => ByteString -> EffectHandler Logging m a -> m a Source #

Attach an arbitrary ByteString to every log. Typically you want to use this handler on logX functions directly like setDataTo "some data" (logInfo "some info")

setDataToJsonOf :: (MonadEffect Logging m, ToJSON v) => v -> EffectHandler Logging m a -> m a Source #

Attach an arbitrary value to every log using it's ToJSON instance. Typically you want to use this handler on logX functions directly like setDataToJsonOf 123 (logInfo "some info")

setDataToShowOf :: (MonadEffect Logging m, Show v) => v -> EffectHandler Logging m a -> m a Source #

Attach an arbitrary value to every log using it's Show instance. Typically you want to use this handler on logX functions directly like setDataToShowOf 123 (logInfo "some info")

setTimestampToNow :: (MonadEffect Logging m, MonadIO m) => EffectHandler Logging m a -> m a Source #

Add the current time to every log.

prettyPrintSummary :: MonadIO m => Int -> EffectHandler Logging m a -> m a Source #

Print out the logs in rich format. Truncates at the given length. Logs will contain: message, timestamp, data, user and the call stack.