Copyright | (c) Adam Conner-Sax 2019 |
---|---|
License | BSD-3-Clause |
Maintainer | adam_conner_sax@yahoo.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Polysemy logger effect, using pretty-printing and severity based on logging-effect. Adds a Prefixing effect so that it's easy to wrap entire functions, etc. in logging prefixes and thus to distinguish where things are being logged from more easily. Also allows filtering by severity.
Synopsis
- data LogSeverity
- = Diagnostic
- | Info
- | Warning
- | Error
- data LogEntry = LogEntry {
- severity :: LogSeverity
- message :: Text
- data Logger a m r where
- data PrefixLog m r
- log :: Member (Logger a) effs => a -> Semantic effs ()
- logLE :: Member (Logger LogEntry) effs => LogSeverity -> Text -> Semantic effs ()
- wrapPrefix :: Member PrefixLog effs => Text -> Semantic effs a -> Semantic effs a
- filteredLogEntriesToIO :: MonadIO (Semantic effs) => [LogSeverity] -> Semantic (Logger LogEntry ': (PrefixLog ': effs)) x -> Semantic effs x
- logAll :: [LogSeverity]
- nonDiagnostic :: [LogSeverity]
- type LogWithPrefixes a effs = (Member PrefixLog effs, Member (Logger a) effs)
- type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs
- data Semantic (r :: [(Type -> Type) -> Type -> Type]) a
- type Member (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) = Member' e r
- type Handler (m :: Type -> Type) message = message -> m ()
Logging Types
data LogSeverity Source #
Severity of message. Based on monad-logger.
Instances
A basic LogEntry with a severity and a (Text) message
LogEntry | |
|
Effects
Actions
log :: Member (Logger a) effs => a -> Semantic effs () Source #
Add one log entry of arbitrary type. If you want to log with another type besides @LogEntry.
logLE :: Member (Logger LogEntry) effs => LogSeverity -> Text -> Semantic effs () Source #
Add one log-entry of the LogEntry
type.
wrapPrefix :: Member PrefixLog effs => Text -> Semantic effs a -> Semantic effs a Source #
Add a prefix for the block of code.
Interpreters
filteredLogEntriesToIO :: MonadIO (Semantic effs) => [LogSeverity] -> Semantic (Logger LogEntry ': (PrefixLog ': effs)) x -> Semantic effs x Source #
Run the Logger and PrefixLog effects using the preferred handler and filter output in any Polysemy monad with IO in the union.
Subsets for filtering
logAll :: [LogSeverity] Source #
LogSeverity list used in order to output everything.
nonDiagnostic :: [LogSeverity] Source #
LogSeverity
list used to output all but Diagnostic
.
Diagnostic
messages are sometimes useful for debugging but can get noisy depending on how you use it.
Constraints for convenience
type LogWithPrefixes a effs = (Member PrefixLog effs, Member (Logger a) effs) Source #
Constraint helper for logging with prefixes
type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs Source #
Constraint helper for LogEntry
type with prefixes
Re-Exports
data Semantic (r :: [(Type -> Type) -> Type -> Type]) a #
The Semantic
monad handles computations of arbitrary extensible effects.
A value of type Semantic r
describes a program with the capabilities of
r
. For best results, r
should always be kept polymorphic, but you can
add capabilities via the Member
constraint.
The value of the Semantic
monad is that it allows you to write programs
against a set of effects without a predefined meaning, and provide that
meaning later. For example, unlike with mtl, you can decide to interpret an
Error
effect tradtionally as an Either
, or instead
significantly faster as an IO
Exception
. These
interpretations (and others that you might add) may be used interchangably
without needing to write any newtypes or Monad
instances. The only
change needed to swap interpretations is to change a call from
runError
to runErrorInIO
.
The effect stack r
can contain arbitrary other monads inside of it. These
monads are lifted into effects via the Lift
effect. Monadic values can be
lifted into a Semantic
via sendM
.
A Semantic
can be interpreted as a pure value (via run
) or as any
traditional Monad
(via runM
). Each effect E
comes equipped with some
interpreters of the form:
runE ::Semantic
(E ': r) a ->Semantic
r a
which is responsible for removing the effect E
from the effect stack. It
is the order in which you call the interpreters that determines the
monomorphic representation of the r
parameter.
After all of your effects are handled, you'll be left with either
a
or a Semantic
'[] a
value, which can be
consumed respectively by Semantic
'[ Lift
m ] arun
and runM
.
Examples
As an example of keeping r
polymorphic, we can consider the type
Member
(State
String) r =>Semantic
r ()
to be a program with access to
get
::Semantic
r Stringput
:: String ->Semantic
r ()
methods.
By also adding a
Member
(Error
Bool) r
constraint on r
, we gain access to the
throw
:: Bool ->Semantic
r acatch
::Semantic
r a -> (Bool ->Semantic
r a) ->Semantic
r a
functions as well.
In this sense, a
constraint is
analogous to mtl's Member
(State
s) r
and should
be thought of as such. However, unlike mtl, a MonadState
s mSemantic
monad may have
an arbitrary number of the same effect.
For example, we can write a Semantic
program which can output either
Int
s or Bool
s:
foo :: (Member
(Output
Int) r ,Member
(Output
Bool) r ) =>Semantic
r () foo = dooutput
@Int 5output
True
Notice that we must use -XTypeApplications
to specify that we'd like to
use the (Output
Int
) effect.