di-0.2: Easy, powerful, structured and typeful logging without monad towers.

Safe HaskellSafe
LanguageHaskell2010

Di

Contents

Description

Import this module as follows:

import Di (Di)
import qualified Di

Synopsis

Usage

First, read the documentation for the Di datatype.

Second, create a base Di value. You will achieve this by using mkDi or, more likely, one of the ready-made mkDiStringStderr, mkDiStringHandle, etc.

At this point, you can start logging messages using log. However, things can be made more interesting.

Your choice of base Di will mandate particular types for the level, path and msg arguments to Di. However, these base types are likely to be very general (e.g., String), so quite likely you'll want to use contralevel, contrapath and contramsg to make those types more specific. For example, you can use a precise datatype like the following for associating each log message with a particular importance level:

data Level = Error | Info | Debug
  deriving (Show)

Now, assuming the your base Di level type is String, you can use contralevel show to convert your Di String path msg to a Di Level path msg. The same approach applies to path and msg as well, through the contrapath and contramsg functions respectively.

Hint: If you are building a library, be sure to export your Level datatype so that users of your library can contralevel your Level datatype as necessary.

data Di level path msg Source #

Di level path msg allows you to to log messages of type msg, with a particular importance level, under a scope identified by path (think of path as a filesystem path that you can use to group together related log messages).

Each msg gets logged together with its level, path and the UTCTime stating the instant when the logging requests was made.

Even though logging is usually associated with rendering text, Di makes no assumption about the types of the msg values being logged, nor the path values that convey their scope, nor the level values that convey their importance. Instead, it delays conversion from these precise types into the ultimately desired raw representation (if any) as much as possible. This makes it possible to log more precise information (for example, logging a datatype of your own without having to convert it to text first), richer scope paths (for example, the scope could be a Map that gets enriched with more information as we push down the path), and importance levels that are never too broad nor too narrow. This improves type safety, as well as the composability of the level, path and msg values. In particular, all of level, path and msg are contravariant values, which in practice means including a precise Di into a more general Di is always possible (see the 'contralevel@, contrapath and contramsg functions).

Messages of undesired importance levels can be muted by using filter.

Contrary to other logging approaches based on monad transformers, a Di is a value that is expected to be passed around explicitly. Of course, if necessary you can always put a Di in some internal monad state or environment and provide a custom API for it. That's a choice you can make.

A Di can be safely used concurrently, and messages are rendered in the absolute order they were submitted for logging.

Di is pronounced as "dee" (not "die" nor "dye" nor "day"). "Di" is the spanish word for an imperative form of the verb "decir", which in english means "to say".

log :: (MonadIO m, Monoid path) => Di level path msg -> level -> msg -> m () Source #

Log a message with the given importance level.

This function returns immediately after queing the message for logging in a different thread. If you want to explicitly wait for the message to be logged, then call flush afterwards.

Note: No exceptions from the underlying logging backend (i.e., the IO action given to mkDi) will be thrown from log. Instead, those will be recorded to stderr and ignored.

flush :: MonadIO m => Di level path msg -> m () Source #

Block until all messages being logged have finished processing.

Mabually calling flush is not usually necessary, but, if at some point you want to ensure that all messages logged until then have properly rendered to the underlying backend, then flush will block until that happens.

push :: Monoid path => path -> Di level path msg -> Di level path msg Source #

Push a new path to the Di.

Identity:

push mempty   ==   id

Composition:

push (a <> b)   ==   push b . push a

filter :: (level -> Bool) -> Di level path msg -> Di level path msg Source #

Returns a new Di on which only messages with a level satisfying the given predicate—in addition to any previous filters—are ever logged.

Identity:

filter (const True)    ==   id

Composition:

filter (liftA2 (&&) f g)   ==   filter f . filter g

Conmutativity:

filter f . filter g    ==    filter g . filter f

contralevel :: (level -> level') -> Di level' path msg -> Di level path msg Source #

A Di is contravariant in its level argument.

This function is used to go from a more general to a less general type of level. For example, data Level = Info | Error is a less general type than data Level' = Info' | Warning' | Error', since the former can only convey two logging levels, whereas the latter can convey three. We can convert from the more general to the less general level type using this contralevel function:

contralevel (\case { Info -> Info'; Error -> Error' }) (di :: Di Level' [String] msg)
    :: Di Level [Int] msg

Identity:

contralevel id   ==   id

Composition:

contralevel (f . g)   ==   contralevel g . contralevel f

contrapath :: (path -> path') -> Di level path' msg -> Di level path msg Source #

A Di is contravariant in its path argument.

This function is used to go from a more general to a less specific type of path. For example, [Int] is a less general type than [String], since the former clearly conveys the idea of a list of numbers, whereas the latter could be a list of anything that is representable as String, such as names of fruits and poems. We can convert from the more general to the less general path type using this contrapath function:

contrapath (map show) (di :: Di level [String] msg)
    :: Di [Int] msg

Identity:

contrapath id   ==   id

Composition:

contrapath (f . g)   ==   contrapath g . contrapath f

contramsg :: (msg -> msg') -> Di level path msg' -> Di level path msg Source #

A Di is contravariant in its msg argument.

This function is used to go from a more general to a less general type of msg. For example, Int is a less general type than String, since the former clearly conveys the idea of a numbers, whereas the latter could be a anything that is representable as String, such as names of painters and colors. We can convert from the more general to the less general msg type using this contramsg function:

contramsg show (di :: Di level path String)
    :: Di level path Int

Identity:

contramsg id   ==   id

Composition:

contramsg (f . g)   ==   contramsg g . contramsg f

Backends

mkDi Source #

Arguments

:: MonadIO m 
=> (UTCTime -> level -> path -> msg -> IO ()) 
-> m (Di level path msg) 

Build a new Di from a logging function.

Note: If the passed in IO function throws a exception, it will be just logged to stderr and then ignored.

Note: There's no need to "release" the obtained Di.

mkDiStringStderr :: MonadIO m => m (Di String String String) Source #

String is written to stderr using the system's locale encoding.

mkDiStringHandle :: MonadIO m => Handle -> m (Di String String String) Source #

Strings are written to Handle using the Handle's locale encoding.