knit-haskell-0.1.0.0: a minimal Rmarkdown sort-of-thing for haskell, by way of Pandoc

Copyright(c) Adam Conner-Sax 2019
LicenseBSD-3-Clause
Maintaineradam_conner_sax@yahoo.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Knit.Effect.Logger

Contents

Description

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

Logging Types

data LogEntry Source #

A basic LogEntry with a severity and a (Text) message

Constructors

LogEntry 

Effects

data Logger a m r where Source #

The Logger effect

Constructors

Log :: a -> Logger a m () 

data PrefixLog m r Source #

Prefix Effect

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 Semantic '[] a or a Semantic '[ Lift m ] a value, which can be consumed respectively by run 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 String
put :: String -> Semantic r ()

methods.

By also adding a

Member (Error Bool) r

constraint on r, we gain access to the

throw :: Bool -> Semantic r a
catch :: Semantic r a -> (Bool -> Semantic r a) -> Semantic r a

functions as well.

In this sense, a Member (State s) r constraint is analogous to mtl's MonadState s m and should be thought of as such. However, unlike mtl, a Semantic monad may have an arbitrary number of the same effect.

For example, we can write a Semantic program which can output either Ints or Bools:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       )
    => Semantic r ()
foo = do
  output @Int  5
  output True

Notice that we must use -XTypeApplications to specify that we'd like to use the (Output Int) effect.

Instances
Member (Error PandocError :: (Type -> Type) -> Type -> Type) effs => MonadError PandocError (Semantic effs) Source #

Split off the error piece. We will handle directly with the polysemy Error effect

Instance details

Defined in Knit.Effect.PandocMonad

Methods

throwError :: PandocError -> Semantic effs a #

catchError :: Semantic effs a -> (PandocError -> Semantic effs a) -> Semantic effs a #

Monad (Semantic f) 
Instance details

Defined in Polysemy.Internal

Methods

(>>=) :: Semantic f a -> (a -> Semantic f b) -> Semantic f b #

(>>) :: Semantic f a -> Semantic f b -> Semantic f b #

return :: a -> Semantic f a #

fail :: String -> Semantic f a #

Functor (Semantic f) 
Instance details

Defined in Polysemy.Internal

Methods

fmap :: (a -> b) -> Semantic f a -> Semantic f b #

(<$) :: a -> Semantic f b -> Semantic f a #

Member Fixpoint r => MonadFix (Semantic r) 
Instance details

Defined in Polysemy.Internal

Methods

mfix :: (a -> Semantic r a) -> Semantic r a #

Applicative (Semantic f) 
Instance details

Defined in Polysemy.Internal

Methods

pure :: a -> Semantic f a #

(<*>) :: Semantic f (a -> b) -> Semantic f a -> Semantic f b #

liftA2 :: (a -> b -> c) -> Semantic f a -> Semantic f b -> Semantic f c #

(*>) :: Semantic f a -> Semantic f b -> Semantic f b #

(<*) :: Semantic f a -> Semantic f b -> Semantic f a #

Member NonDet r => Alternative (Semantic r) 
Instance details

Defined in Polysemy.Internal

Methods

empty :: Semantic r a #

(<|>) :: Semantic r a -> Semantic r a -> Semantic r a #

some :: Semantic r a -> Semantic r [a] #

many :: Semantic r a -> Semantic r [a] #

Member (Lift IO) r => MonadIO (Semantic r)

This instance will only lift IO actions. If you want to lift into some other MonadIO type, use this instance, and handle it via the runIO interpretation.

Instance details

Defined in Polysemy.Internal

Methods

liftIO :: IO a -> Semantic r a #

PandocEffects effs => PandocMonad (Semantic effs) Source #

PandocMonad instance so that pandoc functions can be run in the polysemy union effect

Instance details

Defined in Knit.Effect.PandocMonad

Member (Random :: (Type -> Type) -> Type -> Type) effs => MonadRandom (Semantic effs) Source #

supply instance of MonadRandom for functions which require it

Instance details

Defined in Knit.Effect.RandomFu

type Member (e :: (Type -> Type) -> Type -> Type) (r :: [(Type -> Type) -> Type -> Type]) = Member' e r #

A proof that the effect e is available somewhere inside of the effect stack r.

type Handler (m :: Type -> Type) message = message -> m () #

Handlers are mechanisms to interpret the meaning of logging as an action in the underlying monad. They are simply functions from log messages to m-actions.