di-1.0: Typeful hierarchical structured logging using di, mtl and df1.

Safe HaskellNone
LanguageHaskell2010

Di

Contents

Description

This module is a highly opinionated, basic, and yet sufficient choice of a concrete stack of logging solutions belonging to the di logging ecosystem—an otherwise rather general ecosystem, flexible and full of choices.

For most logging scenarios out there, the choices made here should suffice, but if you find these are not sufficient for your particular use case, please refer to other libraries of the di logging ecosystem such as di-core, di-monad, di-handle, or di-df1, and you are likely to find a compatible and composable solution there. For this reason, staring with this package rather than one of the those other lower-level packages is always recommended.

The choices made here are:

  • We encourage a mtl approach through a typeclass called MonadDi, for which all of the monad transformers in transformers and pipes have instances.
  • We provide our own DiT monad transformer which has a MonadDi instance, as well as instances for all the relevant typeclasses in the base, mtl, and exceptions libraries. All of the MonadDi instances exported by this package expect a DiT transformer in the stack somewhere, and defer all work to it.
  • We embrace the df1 hierarchical structured logging format, both at the type-level and when rendering the log lines as text. Most notably, this means that we embrace the df1 importance Levels.
  • We commit logs to the outside world by printing them to stderr.

You will notice that some of the functions in this module mention the types Level, Path and Message, and some other functions talk about level, path and msg type variables. This is because even while our particular set of choices require some monomorphic types, the di logging ecosystem treats these values polymorphically, so they will show up in the types in one way or another, either in concrete or polymorphic form. This can seem a bit noisy, but the good news is that if, for example, want to call a third party library that uses other types for conveying the idea of a “log importance level” or a “log message”, then you can do so if you can convert between these different types. For more information about this, see Di.Monad and Di.Core, but not today.

The intended usage of this module is:

import qualified Di
Synopsis

Documentation

new Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> (Di Level Path Message -> m a)

Within this scope, you can use the obtained Di safely, even concurrently. As soon as m a finishes, new will block until all logs have finished processing, before returning.

WARNING: Even while new commit pure :: m (Di Level Path Message) type-checks, and you can use it to work with the Di outside the intended scope, you will have to remember to call flush yourself before exiting your application. Otherwise, some log messages may be left unprocessed. If possible, use the Di within this function and don't let it escape this scope.

-> m a 

Obtain a Di that will write logs in the df1 format to stderr.

Generally, you will want to call new just once per application, right from your main function. For example:

main :: IO ()
main = do
   new $ \di -> do
      runDiT di $ do
          -- The rest of your program goes here.
          -- You can start logging right away.
          notice "Welcome to my program!"
          -- You can use push to separate different
          -- logging scopes of your program:
          push "initialization" $ do
              -- something something do initialization
              notice "Starting web server"
          push "server" $ do
              -- And you can use attr to add metadata to
              -- messages logged within a particular scope.
              attr "port" "80" $ do
                   info "Listening for new clients"
                   clientAddress <- somehow get a client connection
                   push "handler" $ do
                      attr "client-address" clientAddress $ do
                         info "Connection established"

That program will render something like this to stderr (in colors!):

2018-05-06T19:48:06.194579393Z NOTICE Welcome to my program!
2018-05-06T19:48:06.195041422Z /initialization NOTICE Starting web server
2018-05-06T19:48:06.195052862Z /server port=80 INFO Listening for new clients
2018-05-06T19:48:06.195059084Z /server port=80 /handler client%2daddress=192%2e168%2e0%2e25%3a32528 INFO Connection established

(Unrelated: Notice how df1 escapes pretty much all punctuation characters. This is temporal until df1 is formalized and a more limited set of punctuation characters is reserved.)

data Di level path msg #

Di level path msg allows you to to log messages of type msg, with a particular importance level, under a scope identified by path.

Each msg gets logged together with its level, path and the UTC timestamp stating the instant when the logging request 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).

Undesired messages can be filtered 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.

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", which clearly must have something to do with logging.

Monadic API

class Monad m => MonadDi level path msg (m :: * -> *) | m -> level path msg #

A MonadDi allows interacting with a Di through a mtl-like monadic API, rather than through the “bare” API proposed by Di.Core.

Nevertheless, be aware that these two APIs are compatible, so you may choose to use the monadic API for some parts of your application, the “bare” API for some other parts, and everything will compose and behave as expected. Usually, runDiT is the boundary between these two APIs, although not necessarily.

Semantically, MonadDi m is a “reader monad” that carries as its environment a Di and natural transformation from STM to m.

Minimal complete definition

local

Instances
MonadDi level path msg m => MonadDi level path msg (MaybeT m) 
Instance details

Methods

ask :: MaybeT m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> MaybeT m a -> MaybeT m a #

natSTM :: STM a -> MaybeT m a #

MonadDi level path msg m => MonadDi level path msg (ListT m) 
Instance details

Methods

ask :: ListT m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> ListT m a -> ListT m a #

natSTM :: STM a -> ListT m a #

(Monoid w, MonadDi level path msg m) => MonadDi level path msg (WriterT w m) 
Instance details

Methods

ask :: WriterT w m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> WriterT w m a -> WriterT w m a #

natSTM :: STM a -> WriterT w m a #

(Monoid w, MonadDi level path msg m) => MonadDi level path msg (WriterT w m) 
Instance details

Methods

ask :: WriterT w m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> WriterT w m a -> WriterT w m a #

natSTM :: STM a -> WriterT w m a #

MonadDi level path msg m => MonadDi level path msg (StateT s m) 
Instance details

Methods

ask :: StateT s m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> StateT s m a -> StateT s m a #

natSTM :: STM a -> StateT s m a #

MonadDi level path msg m => MonadDi level path msg (StateT s m) 
Instance details

Methods

ask :: StateT s m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> StateT s m a -> StateT s m a #

natSTM :: STM a -> StateT s m a #

MonadDi level path msg m => MonadDi level path msg (SelectT r m) 
Instance details

Methods

ask :: SelectT r m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> SelectT r m a -> SelectT r m a #

natSTM :: STM a -> SelectT r m a #

MonadDi level path msg m => MonadDi level path msg (IdentityT m) 
Instance details

Methods

ask :: IdentityT m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> IdentityT m a -> IdentityT m a #

natSTM :: STM a -> IdentityT m a #

MonadDi level path msg m => MonadDi level path msg (ExceptT e m) 
Instance details

Methods

ask :: ExceptT e m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> ExceptT e m a -> ExceptT e m a #

natSTM :: STM a -> ExceptT e m a #

(Monoid w, MonadDi level path msg m) => MonadDi level path msg (AccumT w m) 
Instance details

Methods

ask :: AccumT w m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> AccumT w m a -> AccumT w m a #

natSTM :: STM a -> AccumT w m a #

MonadDi level path msg m => MonadDi level path msg (ReaderT r m) 
Instance details

Methods

ask :: ReaderT r m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> ReaderT r m a -> ReaderT r m a #

natSTM :: STM a -> ReaderT r m a #

MonadDi level path msg m => MonadDi level path msg (ContT r m) 
Instance details

Methods

ask :: ContT r m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> ContT r m a -> ContT r m a #

natSTM :: STM a -> ContT r m a #

(Monoid w, MonadDi level path msg m) => MonadDi level path msg (RWST r w s m) 
Instance details

Methods

ask :: RWST r w s m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> RWST r w s m a -> RWST r w s m a #

natSTM :: STM a -> RWST r w s m a #

(Monoid w, MonadDi level path msg m) => MonadDi level path msg (RWST r w s m) 
Instance details

Methods

ask :: RWST r w s m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> RWST r w s m a -> RWST r w s m a #

natSTM :: STM a -> RWST r w s m a #

Monad m => MonadDi level path msg (DiT level path msg m) 
Instance details

Methods

ask :: DiT level path msg m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> DiT level path msg m a -> DiT level path msg m a #

natSTM :: STM a -> DiT level path msg m a #

MonadDi level path msg m => MonadDi level path msg (Proxy a' a b' b m) 
Instance details

Methods

ask :: Proxy a' a b' b m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> Proxy a' a b' b m a0 -> Proxy a' a b' b m a0 #

natSTM :: STM a0 -> Proxy a' a b' b m a0 #

Hierarchy

push #

Arguments

:: MonadDi level Path msg m 
=> Segment 
-> m a 
-> m a 

Push a new Segment to the MonadDi.

data Segment #

A path segment.

If you have the OverloadedStrings GHC extension enabled, you can build a Segment using a string literal:

"foo" :: Segment

Otherwise, you can use fromString or the Segment constructor directly.

Instances
Eq Segment 
Instance details

Methods

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

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

Show Segment 
Instance details
IsString Segment 
Instance details

Methods

fromString :: String -> Segment #

Semigroup Segment 
Instance details
Monoid Segment 
Instance details

Metadata

attr #

Arguments

:: MonadDi level Path msg m 
=> Key 
-> Value 
-> m a 
-> m a 

Push a new attribute Key and Value to the MonadDi.

data Key #

An attribute key (see Attr).

If you have the OverloadedStrings GHC extension enabled, you can build a Key using a string literal:

"foo" :: Key

Otherwise, you can use fromString or the key function.

Please keep in mind that Key will always strip surrounding whitespace. That is:

"x" :: Key  ==  " x"  == "x " == " x "
Instances
Eq Key 
Instance details

Methods

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

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

Show Key 
Instance details

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key 
Instance details

Methods

fromString :: String -> Key #

Semigroup Key 
Instance details

Methods

(<>) :: Key -> Key -> Key #

sconcat :: NonEmpty Key -> Key #

stimes :: Integral b => b -> Key -> Key #

Monoid Key 
Instance details

Methods

mempty :: Key #

mappend :: Key -> Key -> Key #

mconcat :: [Key] -> Key #

key :: Text -> Key #

data Value #

An attribute value (see Attr).

If you have the OverloadedStrings GHC extension enabled, you can build a Value using a string literal:

"foo" :: Value

Otherwise, you can use fromString or the value function.

Please keep in mind that value will always strip surrounding whitespace. That is:

"x" :: Value  ==  " x"  == "x " == " x "
Instances
Eq Value 
Instance details

Methods

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

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

Show Value 
Instance details

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value 
Instance details

Methods

fromString :: String -> Value #

Semigroup Value 
Instance details

Methods

(<>) :: Value -> Value -> Value #

sconcat :: NonEmpty Value -> Value #

stimes :: Integral b => b -> Value -> Value #

Monoid Value 
Instance details

Methods

mempty :: Value #

mappend :: Value -> Value -> Value #

mconcat :: [Value] -> Value #

Messages

data Message #

A message text.

If you have the OverloadedStrings GHC extension enabled, you can build a Message using a string literal:

"foo" :: Message

Please keep in mind that Message will always strip surrounding whitespace. That is:

"x" :: Message  ==  " x"  == "x " == " x "
Instances
Eq Message 
Instance details

Methods

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

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

Show Message 
Instance details
IsString Message 
Instance details

Methods

fromString :: String -> Message #

Semigroup Message 
Instance details
Monoid Message 
Instance details

debug #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log a message intended to be useful only when deliberately debugging a program.

debug == log Debug

info #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log an informational message.

info == log Info

notice #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log a condition that is not an error, but should possibly be handled specially.

notice == log Notice

warning #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log a warning condition, such as an exception being gracefully handled or some missing configuration setting being assigned a default value.

warning == log Warning

error #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log an error condition, such as an unhandled exception.

error == log Error

alert #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log a condition that should be corrected immediately, such as a corrupted database.

alert == log Alert

critical #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log a critical condition that could result in system failure, such as a disk running out of space.

critical == log Critical @

emergency #

Arguments

:: MonadDi Level path Message m 
=> Message 
-> m () 

Log a message stating that the system is unusable.

emergency == log Emergency

Basic DiT support

data DiT level path msg (m :: * -> *) a #

A DiT level path msg m is a “reader monad” that carries as its environment a Di level path msg and natural transformation from STM to m.

The most primitive way to build a DiT is through diT.

The most primitive way to run a DiT is through runDiT'.

Instances
Monad m => MonadDi level path msg (DiT level path msg m) 
Instance details

Methods

ask :: DiT level path msg m (Di level path msg) #

local :: (Di level path msg -> Di level path msg) -> DiT level path msg m a -> DiT level path msg m a #

natSTM :: STM a -> DiT level path msg m a #

MonadWriter w m => MonadWriter w (DiT level path msg m) 
Instance details

Methods

writer :: (a, w) -> DiT level path msg m a #

tell :: w -> DiT level path msg m () #

listen :: DiT level path msg m a -> DiT level path msg m (a, w) #

pass :: DiT level path msg m (a, w -> w) -> DiT level path msg m a #

MonadState s m => MonadState s (DiT level path msg m) 
Instance details

Methods

get :: DiT level path msg m s #

put :: s -> DiT level path msg m () #

state :: (s -> (a, s)) -> DiT level path msg m a #

MonadReader r m => MonadReader r (DiT level path msg m) 
Instance details

Methods

ask :: DiT level path msg m r #

local :: (r -> r) -> DiT level path msg m a -> DiT level path msg m a #

reader :: (r -> a) -> DiT level path msg m a #

MonadTrans (DiT level path msg) 
Instance details

Methods

lift :: Monad m => m a -> DiT level path msg m a #

Monad m => Monad (DiT level path msg m) 
Instance details

Methods

(>>=) :: DiT level path msg m a -> (a -> DiT level path msg m b) -> DiT level path msg m b #

(>>) :: DiT level path msg m a -> DiT level path msg m b -> DiT level path msg m b #

return :: a -> DiT level path msg m a #

fail :: String -> DiT level path msg m a #

Functor m => Functor (DiT level path msg m) 
Instance details

Methods

fmap :: (a -> b) -> DiT level path msg m a -> DiT level path msg m b #

(<$) :: a -> DiT level path msg m b -> DiT level path msg m a #

MonadFix m => MonadFix (DiT level path msg m) 
Instance details

Methods

mfix :: (a -> DiT level path msg m a) -> DiT level path msg m a #

MonadFail m => MonadFail (DiT level path msg m) 
Instance details

Methods

fail :: String -> DiT level path msg m a #

Applicative m => Applicative (DiT level path msg m) 
Instance details

Methods

pure :: a -> DiT level path msg m a #

(<*>) :: DiT level path msg m (a -> b) -> DiT level path msg m a -> DiT level path msg m b #

liftA2 :: (a -> b -> c) -> DiT level path msg m a -> DiT level path msg m b -> DiT level path msg m c #

(*>) :: DiT level path msg m a -> DiT level path msg m b -> DiT level path msg m b #

(<*) :: DiT level path msg m a -> DiT level path msg m b -> DiT level path msg m a #

Alternative m => Alternative (DiT level path msg m) 
Instance details

Methods

empty :: DiT level path msg m a #

(<|>) :: DiT level path msg m a -> DiT level path msg m a -> DiT level path msg m a #

some :: DiT level path msg m a -> DiT level path msg m [a] #

many :: DiT level path msg m a -> DiT level path msg m [a] #

MonadPlus m => MonadPlus (DiT level path msg m) 
Instance details

Methods

mzero :: DiT level path msg m a #

mplus :: DiT level path msg m a -> DiT level path msg m a -> DiT level path msg m a #

MonadZip m => MonadZip (DiT level path msg m) 
Instance details

Methods

mzip :: DiT level path msg m a -> DiT level path msg m b -> DiT level path msg m (a, b) #

mzipWith :: (a -> b -> c) -> DiT level path msg m a -> DiT level path msg m b -> DiT level path msg m c #

munzip :: DiT level path msg m (a, b) -> (DiT level path msg m a, DiT level path msg m b) #

MonadIO m => MonadIO (DiT level path msg m) 
Instance details

Methods

liftIO :: IO a -> DiT level path msg m a #

MonadThrow m => MonadThrow (DiT level path msg m) 
Instance details

Methods

throwM :: Exception e => e -> DiT level path msg m a #

MonadCatch m => MonadCatch (DiT level path msg m) 
Instance details

Methods

catch :: Exception e => DiT level path msg m a -> (e -> DiT level path msg m a) -> DiT level path msg m a #

MonadMask m => MonadMask (DiT level path msg m) 
Instance details

Methods

mask :: ((forall a. DiT level path msg m a -> DiT level path msg m a) -> DiT level path msg m b) -> DiT level path msg m b #

uninterruptibleMask :: ((forall a. DiT level path msg m a -> DiT level path msg m a) -> DiT level path msg m b) -> DiT level path msg m b #

generalBracket :: DiT level path msg m a -> (a -> ExitCase b -> DiT level path msg m c) -> (a -> DiT level path msg m b) -> DiT level path msg m (b, c) #

MonadCont m => MonadCont (DiT level path msg m) 
Instance details

Methods

callCC :: ((a -> DiT level path msg m b) -> DiT level path msg m a) -> DiT level path msg m a #

runDiT #

Arguments

:: MonadIO m 
=> Di level path msg 
-> DiT level path msg m a 
-> m a 

Run a DiT.

forall di.
   runDiT di (diT (\nat' di' -> pure (nat', di')))
       == pure (natSTM, di)

This is like runDiT', but specialized to run with an underlying MonadIO.

runDiT  ==  runDiT' (liftIO . atomically)

Please notice that runDiT doesn't perform a flush on the given Di before returning. You are responsible for doing that (or, more likely, new will do it for you).

Also, notice that runDiT is a monad morphism from DiT m to m.

hoistDiT #

Arguments

:: (forall x. n x -> m x)

Natural transformation from n to m.

-> (forall x. m x -> n x)

Monad morphism from m to n.

-> DiT level path msg m a

Monad morphism from DiT m to DiT n.

-> DiT level path msg n a 

Lift a monad morphism from m to n to a monad morphism from DiT level path msg m to DiT n.

Notice that DiT itself is not a functor in the category of monads, so it can't be an instance of MFunctor from the mmorph package. However, it becomes one if you pair it with a natural transformation nat :: forall x. n x -> m x. That is:

forall nat.  such that nat is a natural transformation
   hoistDiT nat  ==  hoist

In practical terms, it means that most times you can “hoist” a DiT anyway, just not through hoist.