Copyright | Copyright (c) 2016-2018 Lars Kuhtz <lakuhtz@gmail.com> Copyright (c) 2014-2015 PivotCloud Inc. |
---|---|
License | Apache License, Version 2.0 |
Maintainer | Lars Kuhtz <lakuhtz@gmail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data LogLevel
- logLevelText :: IsString a => LogLevel -> a
- readLogLevel :: (MonadError e m, Eq a, Show a, FoldCase a, IsString a, IsString e, Monoid e) => a -> m LogLevel
- pLogLevel :: Parser LogLevel
- pLogLevel_ :: Text -> Parser LogLevel
- data LogPolicy
- logPolicyText :: IsString s => LogPolicy -> s
- readLogPolicy :: (MonadError e m, Eq a, Show a, FoldCase a, IsText a, IsString e, Monoid e) => a -> m LogPolicy
- pLogPolicy :: Parser LogPolicy
- pLogPolicy_ :: Text -> Parser LogPolicy
- type LogLabel = (Text, Text)
- type LogScope = [LogLabel]
- data LoggerException a where
- data LogMessage a = LogMessage {
- _logMsg :: !a
- _logMsgLevel :: !LogLevel
- _logMsgScope :: !LogScope
- _logMsgTime :: !TimeSpec
- logMsg :: Lens (LogMessage a) (LogMessage b) a b
- logMsgLevel :: Lens' (LogMessage a) LogLevel
- logMsgScope :: Lens' (LogMessage a) LogScope
- logMsgTime :: Lens' (LogMessage a) TimeSpec
- type LoggerBackend a = Either (LogMessage Text) (LogMessage a) -> IO ()
- type LogFunction a m = LogLevel -> a -> m ()
- type LogFunctionIO a = LogLevel -> a -> IO ()
- class LoggerCtx ctx msg | ctx -> msg where
- data LoggerCtxT ctx m α
- runLoggerCtxT :: LoggerCtxT ctx m α -> ctx -> m α
- class Monad m => MonadLog a m | m -> a where
- withLabel :: MonadLog a m => LogLabel -> m α -> m α
- clearScope :: MonadLog a m => m α -> m α
- popLabel :: MonadLog a m => m α -> m α
LogLevel
Instances
Bounded LogLevel Source # | |
Enum LogLevel Source # | |
Eq LogLevel Source # | |
Ord LogLevel Source # | |
Defined in System.Logger.Types | |
Read LogLevel Source # | |
Show LogLevel Source # | |
Generic LogLevel Source # | |
NFData LogLevel Source # | |
Defined in System.Logger.Types | |
ToJSON LogLevel Source # | |
Defined in System.Logger.Types | |
FromJSON LogLevel Source # | |
type Rep LogLevel Source # | |
Defined in System.Logger.Types type Rep LogLevel = D1 (MetaData "LogLevel" "System.Logger.Types" "yet-another-logger-0.3.1-9xkv1iYSnq3IJ3TK3FoqRe" False) ((C1 (MetaCons "Quiet" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Error" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Warn" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Info" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Debug" PrefixI False) (U1 :: * -> *)))) |
logLevelText :: IsString a => LogLevel -> a Source #
readLogLevel :: (MonadError e m, Eq a, Show a, FoldCase a, IsString a, IsString e, Monoid e) => a -> m LogLevel Source #
A version of pLogLevel
that takes a prefix for the command line
option.
Since: yet-another-logger-0.2
LogPolicy
Policy that determines how the case of a congested logging pipeline is addressed.
Instances
logPolicyText :: IsString s => LogPolicy -> s Source #
readLogPolicy :: (MonadError e m, Eq a, Show a, FoldCase a, IsText a, IsString e, Monoid e) => a -> m LogPolicy Source #
A version of pLogPolicy
that takes a prefix for the
command line option.
Since: yet-another-logger-0.2
LogLabel
Logger Exception
data LoggerException a where Source #
Exceptions that are thrown by the logger
QueueFullException
- thrown when the queue is full and the logger policy is set to throw exceptions on a full queue
BackendTerminatedException
- a backend can throw this exception to force the logger immediately
BackendTooManyExceptions
- thrown when the backend has thrown unexpected
exceptions more than
loggerConfigExceptionLimit
times
Since: yet-another-logger-0.2
QueueFullException :: LogMessage a -> LoggerException a | |
BackendTerminatedException :: SomeException -> LoggerException Void | |
BackendTooManyExceptions :: [SomeException] -> LoggerException Void |
Instances
Show a => Show (LoggerException a) Source # | |
Defined in System.Logger.Types showsPrec :: Int -> LoggerException a -> ShowS # show :: LoggerException a -> String # showList :: [LoggerException a] -> ShowS # | |
(Typeable a, Show a) => Exception (LoggerException a) Source # | |
Defined in System.Logger.Types toException :: LoggerException a -> SomeException # fromException :: SomeException -> Maybe (LoggerException a) # displayException :: LoggerException a -> String # |
Logger Backend
data LogMessage a Source #
The Internal log message type.
The type parameter a
is expected to provide intances
of Show
, Typeable
, and NFData
.
If we need to support different backends, we may consider including the backend here...
LogMessage | |
|
Instances
logMsg :: Lens (LogMessage a) (LogMessage b) a b Source #
logMsgLevel :: Lens' (LogMessage a) LogLevel Source #
logMsgScope :: Lens' (LogMessage a) LogScope Source #
logMsgTime :: Lens' (LogMessage a) TimeSpec Source #
Since: yet-another-logger-0.2
type LoggerBackend a = Either (LogMessage Text) (LogMessage a) -> IO () Source #
This is given to logger when it is created. It formats and delivers individual log messages synchronously. The backend is called once for each log message (that meets the required log level).
The type parameter a
is expected to provide instances for Show
Typeable
, and NFData
.
The Left
values of the argument allows the generation of log messages that
are independent of the parameter a
. The motivation for this is reporting
issues in Logging system itself, like a full logger queue or providing
statistics about the fill level of the queue. There may be other uses of
this, too.
Backends that can fail are encouraged (but not forced) to take into account
the LogPolicy
that is effective for a message. For instance, a backend may
implement a reasonable retry logic for each message and then raise a
BackendTerminatedException
in case the policy is LogPolicyBlock
or
LogPolicyRaise
(thus causing the logger to exit immediately) and raise
some other exception otherwise (thus discarding the message without causing
the logger to not exit immediately). In addition a backend might retry
harder in case of LogPolicyBlock
.
TODO there may be scenarios where chunked processing is beneficial. While this can be done in a closure of this function, more direct support might be desirable.
Logger Frontend
type LogFunction a m = LogLevel -> a -> m () Source #
type LogFunctionIO a = LogLevel -> a -> IO () Source #
This function is provided by the logger.
LoggerCtx
class LoggerCtx ctx msg | ctx -> msg where Source #
Abstraction of a logger context that can be used without dependening on a specific monadic context.
The loggerFunIO
incorporates a LoggerBackend
. An instance of a LoggerCtx
is free to use a hard coded LoggerBackend
or to be usable with different
LoggerBackend
functions. The latter is recommended but not required.
You don't have to provide an instance of this for your logger. Instead you
may just provide an instance of MonadLog
directly.
If this doesn't fit your needs you may use a newtype wrapper and define your own instances.
loggerFunIO :: (Show msg, Typeable msg, NFData msg) => ctx -> LogFunctionIO msg Source #
setLoggerLevel :: Setter' ctx LogLevel Source #
setLoggerScope :: Setter' ctx LogScope Source #
setLoggerPolicy :: Setter' ctx LogPolicy Source #
withLoggerLevel :: LogLevel -> ctx -> (ctx -> α) -> α Source #
withLoggerLabel :: LogLabel -> ctx -> (ctx -> α) -> α Source #
withLoggerPolicy :: LogPolicy -> ctx -> (ctx -> α) -> α Source #
Instances
LoggerCtx (Logger a) a Source # | |
Defined in System.Logger.Logger.Internal loggerFunIO :: Logger a -> LogFunctionIO a Source # setLoggerLevel :: Setter' (Logger a) LogLevel Source # setLoggerScope :: Setter' (Logger a) LogScope Source # setLoggerPolicy :: Setter' (Logger a) LogPolicy Source # withLoggerLevel :: LogLevel -> Logger a -> (Logger a -> α) -> α Source # withLoggerLabel :: LogLabel -> Logger a -> (Logger a -> α) -> α Source # withLoggerPolicy :: LogPolicy -> Logger a -> (Logger a -> α) -> α Source # |
data LoggerCtxT ctx m α Source #
Instances
runLoggerCtxT :: LoggerCtxT ctx m α -> ctx -> m α Source #
MonadLog
class Monad m => MonadLog a m | m -> a where Source #
logg :: LogFunction a m Source #
Log a message.
withLevel :: LogLevel -> m α -> m α Source #
Run the inner computation with the given LogLevel
withPolicy :: LogPolicy -> m α -> m α Source #
Run the inner computation with the given LogPolicy
.
localScope :: (LogScope -> LogScope) -> m α -> m α Source #
Run the inner computation with a modified LogScope
.
Since: yet-another-logger-0.1
Instances
(Show a, Typeable a, NFData a, MonadIO m, LoggerCtx ctx a) => MonadLog a (LoggerCtxT ctx m) Source # | |
Defined in System.Logger.Types logg :: LogFunction a (LoggerCtxT ctx m) Source # withLevel :: LogLevel -> LoggerCtxT ctx m α -> LoggerCtxT ctx m α Source # withPolicy :: LogPolicy -> LoggerCtxT ctx m α -> LoggerCtxT ctx m α Source # localScope :: (LogScope -> LogScope) -> LoggerCtxT ctx m α -> LoggerCtxT ctx m α Source # | |
MonadLog a m => MonadLog a (StateT σ m) Source # | |
MonadLog a m => MonadLog a (ExceptT ε m) Source # | |
(Monoid σ, MonadLog a m) => MonadLog a (WriterT σ m) Source # | |
clearScope :: MonadLog a m => m α -> m α Source #