Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Di level path msg
- new :: forall m level path msg a. (MonadIO m, MonadMask m) => (Log level path msg -> IO ()) -> (Di level path msg -> m a) -> m a
- log :: MonadIO m => Di level path msg -> level -> msg -> m ()
- log' :: Monad m => (forall x. STM x -> m x) -> Di level path msg -> level -> msg -> m ()
- flush :: MonadIO m => Di level path msg -> m ()
- flush' :: (forall x. STM x -> m x) -> Di level path msg -> m ()
- throw :: (MonadIO m, Exception e) => Di level path msg -> e -> m a
- throw' :: (Monad m, Exception e) => (forall x. STM x -> m x) -> Di level path msg -> e -> m a
- push :: path -> Di level path msg -> Di level path msg
- filter :: (level -> Seq path -> msg -> Bool) -> Di level path msg -> Di level path msg
- onException :: (SomeException -> Maybe (level, Seq path, msg)) -> Di level path msg -> Di level path msg
- contralevel :: (level -> level') -> Di level' path msg -> Di level path msg
- contrapath :: (path -> path') -> Di level path' msg -> Di level path msg
- contramsg :: (msg -> msg') -> Di level path msg' -> Di level path msg
- data Log level path msg = Log {
- log_time :: SystemTime
- log_level :: level
- log_path :: Seq path
- log_message :: msg
- data ExceptionInLoggingWorker = ExceptionInLoggingWorker !SomeException
- data LoggingWorkerNotRunning = LoggingWorkerNotRunning
Documentation
data Di level path msg Source #
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 level
s 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.
:: (MonadIO m, MonadMask m) | |
=> (Log level path msg -> IO ()) | Function that commits For example, if you want to commit your Notice that this function necessarily runs Synchronous exceptions thrown by this function will be silently ignored. If
you want to implement some retry or fallback mechanism, then you need to
do it within this function. Asynchronous exceptions will be propagated to
the thread that called |
-> (Di level path msg -> m a) | Within this scope, you can use the obtained WARNING: Even while |
-> m a |
Obtain a Di
that will use the given function to commit Log
s to the
outside world.
Generally, you will want to call new
just once per application, right from
your main
function. That is:
main ::IO
() main = do commit <- getSomeLogCommittingFunctionSomehownew
commit $ \di -> do -- The rest of your program goes here. -- You can start logging right away.
Using the obtained Di
concurrently is safe.
Note that by default, exceptions thrown through this Di
using throw
won't
be logged. Please use onException
to change this behavior. Morevoer, the
default filter
on this Di
accepts all incoming logs.
:: MonadIO m | |
=> Di level path msg | Where to log to. |
-> level | Log importance level. |
-> msg | Log message. |
-> m () |
Log a message msg
with a particular importance level
.
Notice that function requires a MonadIO
constraint. If you want to log
from other monads that don't satisfy this constraint but are somehow able
to perform or build STM
actions, then use log'
instead.
log
=log'
(liftIO
.atomically
)
Refer to log'
for more documentation.
:: Monad m | |
=> (forall x. STM x -> m x) | Natural transformation from Note that it is not necessary for this natural transofmation to be a
monad morphism as well. That is, using |
-> Di level path msg | Where to log to. |
-> level | Log importance level. |
-> msg | Log message. |
-> m () |
Log a message msg
with a particular importance level
.
This function is like log
, but it doesn't require a MonadIO
constraint. Instead, it asks for a natural transformation that will be
used in order to run STM
actions in m
.
First, this allows you to log from any Monad
that wraps IO
without
necessarily having a MonadIO
instance. For example:
newtype Foo = Foo (IO
a) deriving (Functor
,Applicative
,Monad
)log'
(Foo .atomically
) ::Di
level path msg -> level -> msg -> Foo ()
Second, this log'
function allows m
to be STM
itself:
log'
id
::Di
level path msg -> level -> msg ->STM
()
The semantics of logging from within STM
are those of any other STM
transaction: That is, a log message is commited only once to the outside
world if and when the STM
transaction succeeds. That is, the following
example will only ever commit the log containing ly
and my
, and not
the one containing lx
and mx
.
atomically
(log'
id
di lx mx >>retry
) <|> (log'
id
di ly my)
Furthermore, much like we were able to log from a Foo
that wrapped IO
in the previous example, we are also able to log from any monad wrapping
STM
:
newtype Bar = Bar (STM
a) deriving (Functor
,Applicative
,Monad
)log'
Bar ::Di
level path msg -> level -> msg -> Bar ()
This function returns immediately after queing the message for
asynchronously committing the message in a different thread. If you want
to explicitly wait for the message to be committed, then call flush
afterwards.
Log messages are rendered in FIFO order, and their timestamp records the time
when this log'
function was called, rather than the time when the log
message is committed in the future.
Note regarding exceptions: Any exception thrown by the given
natural transformation will be thrown here. Synchronous exceptions that
happen due to failures in the actual committing of the log message, which
itself is performed in a different thread, are ignored (they should be
handled in the function passed to new
instead). If an asynchronous
exception kills the logging thread, then you will synchronously get
ExceptionInLoggingWorker
here, but by the time that happens, that same
exception will have already already been thrown asynchronously to this same
thread anyway, so unless you did something funny to recover from that
exception, you will have died already.
flush :: MonadIO m => Di level path msg -> m () Source #
Block until all messages being logged have finished processing.
If the MonadIO
constraint can't be satisfied, then use flush'
instead.
Manually calling flush
is not usually necessary because new
does it
already, if at some point you want to ensure that all messages logged
until then have properly commited, then flush
will block until that
happens.
Please see log
to understand how exceptions behave in this function (hint:
they behave unsurprisingly).
:: (forall x. STM x -> m x) | Natural transformation from Note that it is not necessary for this natural transofmation to be a
monad morphism as well. That is, using |
-> Di level path msg | |
-> m () |
Throw an Exception
, but not without logging it first according to the
rendering rules established by onException
, and further restricted by the
filtering rules established by filter
.
This function is like throw'
, but requires a MonadIO
constraint.
throw
==throw'
(liftIO
.atomically
)
If the exception is not logged, then this function behaves as throwIO
.
throw
(onException
(const
False
) di) ==liftIO
.throwIO
:: (Monad m, Exception e) | |
=> (forall x. STM x -> m x) | Natural transformation from Note that it is not necessary for this natural transofmation to be a
monad morphism as well. That is, using WARNING: Note that while this function can be |
-> Di level path msg | |
-> e | |
-> m a |
:: (level -> Seq path -> msg -> Bool) | Whether a particular log entry with the given The given |
-> Di level path msg | |
-> Di level path msg |
Returns a new Di
on which only messages with level
, path
s and
msg
satisfying the given predicate—in addition to any previous
filter
s—are ever logged.
Identity:
filter
(\_ _ _ ->True
) ==id
Composition:
filter
(\l ps m -> f l ps m&&
g l ps m) ==filter
f .filter
g
Notice how filter
can't accept a message already rejected by a previous use
of filter
, yet it can reject a previously accepted one.
Commutativity:
filter
f .filter
g ==filter
g .filter
f
:: (SomeException -> Maybe (level, Seq path, msg)) | |
-> Di level path msg | |
-> Di level path msg |
Modifies a Di
so that exceptions thrown with throw
could be logged as a
msg
with a particular level
if both the passed in function returns
Just
, and filter
so allows it afterwards.
If the given function returns Nothing
, then no logging is performed.
The returned
will extend the Seq
pathpath
at the throw site before
sending the log. The leftmost path
is closest to the root.
Composition:
onException
f .onException
g ==onException
(g e *> f e)
Notice that the level
, path
s and msg
resulting from g
are discarded,
yet its policy regarding whether to log or not is preserved in the same way
as filter
. That is, onException
can't accept an exception already
rejected by a previous use of onException
, but it can reject a previously
accepted one.
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 more specific type
of level
. For example, data Level = Info | Error
is a more specific 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 more specific level
type using this
contralevel
function:
contralevel
(\case { Info -> Info'; Error -> Error' }) (di ::Di
Level'String
msg) ::Di
LevelString
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 more specific type
of path
. For example, Int
is a more specific type than String
,
since the former clearly conveys the idea of a number, whereas the
latter could be anything that is representable as String
, such as
names of fruits and poems. We can convert from the more general to the
more specific path
type using this contrapath
function:
contrapath
show
(di ::Di
levelString
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 more specific type
of msg
. For example, Int
is a more specific type than
, since
the former clearly conveys the idea of a numbers, whereas the latter could be
a anything that is representable as String
String
, such as names of painters and
colors. We can convert from the more general to the more specific msg
type
using this contramsg
function:
contramsg
show
(di ::Di
level pathString
) ::Di
level pathInt
Identity:
contramsg
id
==id
Composition:
contramsg
(f . g) ==contramsg
g .contramsg
f
data Log level path msg Source #
Log | |
|
data ExceptionInLoggingWorker Source #
In
, if new
f gnew'
s internal worker thread unexpectedly dies with
an exception, either synchronous or asynchronous, then that exception will
be wrapped in ExceptionInLoggingWorker
and thrown to g
's thread. Since
this exception will be delivered to g
asynchronously, it will be further
wrapped in SomeAsyncException
.
SomeAsyncException
(ExceptionInLoggingWorker
(culprit ::SomeException
))
If you receive this exception, it means that the thread responsible for
running f
died. This is very unlikely to happen unless an asynchronous
exception killed the worker thread, in which case you should not try to
recover from the situation.
Notice that synchronous exceptions from f
itself are always muted. f
's
author is responsible for handling those if necessary.
Instances
Show ExceptionInLoggingWorker Source # | |
Defined in Di.Core showsPrec :: Int -> ExceptionInLoggingWorker -> ShowS # show :: ExceptionInLoggingWorker -> String # showList :: [ExceptionInLoggingWorker] -> ShowS # | |
Exception ExceptionInLoggingWorker Source # | |
Defined in Di.Core |
data LoggingWorkerNotRunning Source #
This exception is thrown if somebody tries to log or flush a message when the logging worker is not running.
Instances
Show LoggingWorkerNotRunning Source # | |
Defined in Di.Core showsPrec :: Int -> LoggingWorkerNotRunning -> ShowS # show :: LoggingWorkerNotRunning -> String # showList :: [LoggingWorkerNotRunning] -> ShowS # | |
Exception LoggingWorkerNotRunning Source # | |
Defined in Di.Core |