| Copyright | Copyright (c) 2014-2015 PivotCloud, Inc. | 
|---|---|
| License | Apache License, Version 2.0 | 
| Maintainer | Lars Kuhtz <lkuhtz@pivotmail.com> | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
System.Logger.Types
Description
- 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- loggerFunIO :: (Show msg, Typeable msg, NFData msg) => ctx -> LogFunctionIO msg
- setLoggerLevel :: Setter' ctx LogLevel
- setLoggerScope :: Setter' ctx LogScope
- setLoggerPolicy :: Setter' ctx LogPolicy
- withLoggerLevel :: LogLevel -> ctx -> (ctx -> α) -> α
- withLoggerLabel :: LogLabel -> ctx -> (ctx -> α) -> α
- withLoggerPolicy :: LogPolicy -> ctx -> (ctx -> α) -> α
 
- data LoggerCtxT ctx m α
- runLoggerCtxT :: LoggerCtxT ctx m α -> ctx -> m α
- class Monad m => MonadLog a m | m -> a where- logg :: LogFunction a m
- withLevel :: LogLevel -> m α -> m α
- withPolicy :: LogPolicy -> m α -> m α
- localScope :: (LogScope -> LogScope) -> m α -> m α
 
- withLabel :: MonadLog a m => LogLabel -> m α -> m α
- clearScope :: MonadLog a m => m α -> m α
- popLabel :: MonadLog a m => m α -> m α
LogLevel
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 0.2
LogPolicy
Policy that determines how the case of a congested logging pipeline is addressed.
Constructors
| LogPolicyDiscard | |
| LogPolicyRaise | |
| LogPolicyBlock | 
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
pLogPolicy :: Parser LogPolicy Source
A version of pLogPolicy that takes a prefix for the
 command line option.
@since 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 loggerConfigExceptionLimittimes
@since 0.2
Constructors
| QueueFullException :: LogMessage a -> LoggerException a | |
| BackendTerminatedException :: SomeException -> LoggerException Void | |
| BackendTooManyExceptions :: [SomeException] -> LoggerException Void | 
Instances
| Show a => Show (LoggerException a) | |
| (Typeable * a, Show a) => Exception (LoggerException a) | |
| Typeable (* -> *) LoggerException | 
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...
Constructors
| LogMessage | |
| Fields 
 | |
Instances
| Eq a => Eq (LogMessage a) | |
| Ord a => Ord (LogMessage a) | |
| Read a => Read (LogMessage a) | |
| Show a => Show (LogMessage a) | |
| Generic (LogMessage a) | |
| NFData a => NFData (LogMessage a) | |
| Typeable (* -> *) LogMessage | |
| type Rep (LogMessage a) | 
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 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.
Minimal complete definition
loggerFunIO, setLoggerLevel, setLoggerScope, setLoggerPolicy
Methods
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
data LoggerCtxT ctx m α Source
Instances
| MonadState a m => MonadState a (LoggerCtxT ctx m) | |
| Monad m => MonadReader ctx (LoggerCtxT ctx m) | |
| MonadWriter a m => MonadWriter a (LoggerCtxT ctx m) | |
| MonadError a m => MonadError a (LoggerCtxT ctx m) | |
| MonadBase a m => MonadBase a (LoggerCtxT ctx m) | |
| MonadBaseControl b m => MonadBaseControl b (LoggerCtxT ctx m) | |
| MonadTrace t m => MonadTrace t (LoggerCtxT ctx m) | |
| (Show a, Typeable * a, NFData a, MonadIO m, LoggerCtx ctx a) => MonadLog a (LoggerCtxT ctx m) | |
| MonadTrans (LoggerCtxT ctx) | |
| MonadTransControl (LoggerCtxT ctx) | |
| Monad m => Monad (LoggerCtxT ctx m) | |
| Functor m => Functor (LoggerCtxT ctx m) | |
| Applicative m => Applicative (LoggerCtxT ctx m) | |
| MonadIO m => MonadIO (LoggerCtxT ctx m) | |
| type StT (LoggerCtxT ctx) a = StT (ReaderT ctx) a | |
| type StM (LoggerCtxT ctx m) a = ComposeSt (LoggerCtxT ctx) m a | 
runLoggerCtxT :: LoggerCtxT ctx m α -> ctx -> m α Source
MonadLog
class Monad m => MonadLog a m | m -> a where Source
Methods
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 0.1
Instances
| (Show a, Typeable * a, NFData a, MonadIO m, LoggerCtx ctx a) => MonadLog a (LoggerCtxT ctx m) | |
| MonadLog a m => MonadLog a (EitherT σ m) | |
| MonadLog a m => MonadLog a (StateT σ m) | |
| MonadLog a m => MonadLog a (ExceptT ε m) | |
| (Monoid σ, MonadLog a m) => MonadLog a (WriterT σ m) | |
| MonadLog a m => MonadLog a (TraceT t e m) | 
clearScope :: MonadLog a m => m α -> m α Source