| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Di
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
DiTmonad transformer which has aMonadDiinstance, as well as instances for all the relevant typeclasses in the base, mtl, and exceptions libraries. All of theMonadDiinstances exported by this package expect aDiTtransformer 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
- new :: (MonadIO m, MonadMask m) => (Di Level Path Message -> m a) -> m a
- data Di level path msg
- class Monad m => MonadDi level path msg (m :: * -> *) | m -> level path msg
- push :: MonadDi level Path msg m => Segment -> m a -> m a
- data Segment
- segment :: Text -> Segment
- attr :: MonadDi level Path msg m => Key -> Value -> m a -> m a
- data Key
- key :: Text -> Key
- data Value
- value :: Text -> Value
- data Message
- debug :: MonadDi Level path Message m => Message -> m ()
- info :: MonadDi Level path Message m => Message -> m ()
- notice :: MonadDi Level path Message m => Message -> m ()
- warning :: MonadDi Level path Message m => Message -> m ()
- error :: MonadDi Level path Message m => Message -> m ()
- alert :: MonadDi Level path Message m => Message -> m ()
- critical :: MonadDi Level path Message m => Message -> m ()
- emergency :: MonadDi Level path Message m => Message -> m ()
- data DiT level path msg (m :: * -> *) a
- runDiT :: MonadIO m => Di level path msg -> DiT level path msg m a -> m a
- hoistDiT :: (forall x. n x -> m x) -> (forall x. m x -> n x) -> DiT level path msg m a -> DiT level path msg n a
Documentation
Arguments
| :: (MonadIO m, MonadMask m) | |
| => (Di Level Path Message -> m a) | Within this scope, you can use the obtained WARNING: Even while
|
| -> 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 = donew$ \di -> dorunDiTdi $ do -- The rest of your program goes here. -- You can start logging right away.notice"Welcome to my program!" -- You can usepushto separate different -- logging scopes of your program:push"initialization" $ do -- something something do initializationnotice"Starting web server"push"server" $ do -- And you can useattrto add metadata to -- messages logged within a particular scope.attr"port" "80" $ doinfo"Listening for new clients" clientAddress <- somehow get a client connectionpush"handler" $ doattr"client-address" clientAddress $ doinfo"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.)
allows you to to log messages of type Di level path msgmsg,
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, is a “reader monad” that carries as its
environment a MonadDi mDi and natural transformation from STM to m.
Minimal complete definition
Instances
| MonadDi level path msg m => MonadDi level path msg (MaybeT m) | |
| MonadDi level path msg m => MonadDi level path msg (ListT m) | |
| (Monoid w, MonadDi level path msg m) => MonadDi level path msg (WriterT w m) | |
| (Monoid w, MonadDi level path msg m) => MonadDi level path msg (WriterT w m) | |
| MonadDi level path msg m => MonadDi level path msg (StateT s m) | |
| MonadDi level path msg m => MonadDi level path msg (StateT s m) | |
| MonadDi level path msg m => MonadDi level path msg (SelectT r m) | |
| MonadDi level path msg m => MonadDi level path msg (IdentityT m) | |
| MonadDi level path msg m => MonadDi level path msg (ExceptT e m) | |
| (Monoid w, MonadDi level path msg m) => MonadDi level path msg (AccumT w m) | |
| MonadDi level path msg m => MonadDi level path msg (ReaderT r m) | |
| MonadDi level path msg m => MonadDi level path msg (ContT r m) | |
| (Monoid w, MonadDi level path msg m) => MonadDi level path msg (RWST r w s m) | |
| (Monoid w, MonadDi level path msg m) => MonadDi level path msg (RWST r w s m) | |
| Monad m => MonadDi level path msg (DiT level path msg m) | |
| MonadDi level path msg m => MonadDi level path msg (Proxy a' a b' b m) | |
Hierarchy
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.
Metadata
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 "
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 "
Messages
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 "
Basic DiT support
data DiT level path msg (m :: * -> *) a #
A is a “reader monad” that carries as its
environment a DiT level path msg m and natural transformation from Di level path msgSTM to
m.
Instances
| Monad m => MonadDi level path msg (DiT level path msg m) | |
| MonadWriter w m => MonadWriter w (DiT level path msg m) | |
| MonadState s m => MonadState s (DiT level path msg m) | |
| MonadReader r m => MonadReader r (DiT level path msg m) | |
| MonadTrans (DiT level path msg) | |
| Monad m => Monad (DiT level path msg m) | |
| Functor m => Functor (DiT level path msg m) | |
| MonadFix m => MonadFix (DiT level path msg m) | |
| MonadFail m => MonadFail (DiT level path msg m) | |
| Applicative m => Applicative (DiT level path msg m) | |
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) | |
| MonadPlus m => MonadPlus (DiT level path msg m) | |
| MonadZip m => MonadZip (DiT level path msg m) | |
| MonadIO m => MonadIO (DiT level path msg m) | |
| MonadThrow m => MonadThrow (DiT level path msg m) | |
| MonadCatch m => MonadCatch (DiT level path msg m) | |
| MonadMask m => MonadMask (DiT level path msg m) | |
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) | |
Run a DiT.
forall di.runDiTdi (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 to DiT mm.
Arguments
| :: (forall x. n x -> m x) | Natural transformation from |
| -> (forall x. m x -> n x) | Monad morphism from |
| -> DiT level path msg m a | |
| -> DiT level path msg n a |
Lift a monad morphism from m to n to a monad morphism from
to DiT level path msg m.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
. That is:nat :: forall x. n x -> m x
forall nat. such thatnatis a natural transformationhoistDiTnat ==hoist
In practical terms, it means that most times you can “hoist” a DiT
anyway, just not through hoist.