knit-haskell-0.8.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

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 LogSeverity Source #

Severity/importance of message.

Constructors

Debug Int

Most detailed levels of logging. Int argument can be used adding fine distinctions between debug levels.

Diagnostic

Minimal details about effects and what is being called.

Info

Informational messages about progress of compuation or document knitting.

Warning

Messages intended to alert the user to an issue in the computation or document production.

Error

Likely unrecoverable issue in computation or document production.

Instances

Instances details
Eq LogSeverity Source # 
Instance details

Defined in Knit.Effect.Logger

Data LogSeverity Source # 
Instance details

Defined in Knit.Effect.Logger

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LogSeverity -> c LogSeverity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LogSeverity #

toConstr :: LogSeverity -> Constr #

dataTypeOf :: LogSeverity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LogSeverity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LogSeverity) #

gmapT :: (forall b. Data b => b -> b) -> LogSeverity -> LogSeverity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LogSeverity -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LogSeverity -> r #

gmapQ :: (forall d. Data d => d -> u) -> LogSeverity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LogSeverity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LogSeverity -> m LogSeverity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LogSeverity -> m LogSeverity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LogSeverity -> m LogSeverity #

Ord LogSeverity Source # 
Instance details

Defined in Knit.Effect.Logger

Show LogSeverity Source # 
Instance details

Defined in Knit.Effect.Logger

Pretty LogSeverity Source # 
Instance details

Defined in Knit.Effect.Logger

Methods

pretty :: LogSeverity -> Doc ann #

prettyList :: [LogSeverity] -> Doc ann #

data LogEntry Source #

A basic log entry with a severity and a (Text) message

Constructors

LogEntry 

Effects

data Logger a m r where Source #

The Logger effect (the same as the Output effect).

Constructors

Log :: a -> Logger a m () 

data PrefixLog m r Source #

Prefix Effect

Actions

log :: Member (Logger a) effs => a -> Sem 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 -> Sem effs () Source #

Add one log-entry of the LogEntry type.

wrapPrefix :: Member PrefixLog effs => Text -> Sem effs a -> Sem effs a Source #

Add a prefix for the block of code.

getPrefix :: Member PrefixLog effs => Sem effs Text Source #

Get current prefix

logWithPrefixToIO :: LogWithPrefixIO Source #

This function can be used to log directly to IO, bypassing the effect. It's here to allow logging from within functions that must be run under more limited stacks and then embedded.

Interpreters

filteredLogEntriesToIO :: MonadIO (Sem r) => (LogSeverity -> Bool) -> Sem (Logger LogEntry ': (PrefixLog ': r)) x -> Sem r x Source #

Run the Logger and PrefixLog effects in IO: filtered via the severity of the message and formatted using "prettyprinter".

Subsets for filtering

logAll :: LogSeverity -> Bool Source #

log everything.

logDebug :: Int -> LogSeverity -> Bool Source #

log debug messages with level lower than or equal to the given Int.

logDiagnostic :: LogSeverity -> Bool Source #

log all but Debug messages.

nonDiagnostic :: LogSeverity -> Bool Source #

log everything above Diagnostic.

Type Synonyms and Constraints for convenience

type PrefixedLogEffects a = [PrefixLog, Logger a] Source #

List of Logger effects for a prefixed log of type a

type PrefixedLogEffectsLE = PrefixedLogEffects LogEntry Source #

List of Logger effects for a prefixed log of type LogEntry

type LogWithPrefixes a effs = Members (PrefixedLogEffects a) effs Source #

Constraint helper for logging with prefixes

type LogWithPrefixesLE effs = LogWithPrefixes LogEntry effs Source #

Constraint helper for LogEntry type with prefixes

type LogWithPrefixIO = Text -> LogEntry -> IO () Source #

A synonym for a function to handle direct logging from IO. Used to allow logging from any stack with IO.