yet-another-logger-0.3.0: Yet Another Logger

CopyrightCopyright (c) 2014-2015 PivotCloud Inc.
LicenseApache License, Version 2.0
MaintainerLars Kuhtz <lkuhtz@pivotmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

System.Logger.Types

Contents

Description

 

Synopsis

LogLevel

data LogLevel Source #

Constructors

Quiet 
Error 
Warn 
Info 
Debug 

Instances

Bounded LogLevel Source # 
Enum LogLevel Source # 
Eq LogLevel Source # 
Ord LogLevel Source # 
Read LogLevel Source # 
Show LogLevel Source # 
Generic LogLevel Source # 

Associated Types

type Rep LogLevel :: * -> * #

Methods

from :: LogLevel -> Rep LogLevel x #

to :: Rep LogLevel x -> LogLevel #

ToJSON LogLevel Source # 
FromJSON LogLevel Source # 
NFData LogLevel Source # 

Methods

rnf :: LogLevel -> () #

type Rep LogLevel Source # 
type Rep LogLevel = D1 (MetaData "LogLevel" "System.Logger.Types" "yet-another-logger-0.3.0-5rm0jRQNZUUFOUSMQAcGn3" 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))))

pLogLevel_ Source #

Arguments

:: Text

prefix for the command line options.

-> Parser LogLevel 

A version of pLogLevel that takes a prefix for the command line option.

Since: 0.2

LogPolicy

data LogPolicy Source #

Policy that determines how the case of a congested logging pipeline is addressed.

Instances

Bounded LogPolicy Source # 
Enum LogPolicy Source # 
Eq LogPolicy Source # 
Ord LogPolicy Source # 
Read LogPolicy Source # 
Show LogPolicy Source # 
Generic LogPolicy Source # 

Associated Types

type Rep LogPolicy :: * -> * #

ToJSON LogPolicy Source # 
FromJSON LogPolicy Source # 
NFData LogPolicy Source # 

Methods

rnf :: LogPolicy -> () #

type Rep LogPolicy Source # 
type Rep LogPolicy = D1 (MetaData "LogPolicy" "System.Logger.Types" "yet-another-logger-0.3.0-5rm0jRQNZUUFOUSMQAcGn3" False) ((:+:) (C1 (MetaCons "LogPolicyDiscard" PrefixI False) U1) ((:+:) (C1 (MetaCons "LogPolicyRaise" PrefixI False) U1) (C1 (MetaCons "LogPolicyBlock" PrefixI False) U1)))

pLogPolicy_ Source #

Arguments

:: Text

prefix for the command line options.

-> Parser LogPolicy 

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 loggerConfigExceptionLimit times

Since: 0.2

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

  • _logMsg :: !a
     
  • _logMsgLevel :: !LogLevel
     
  • _logMsgScope :: !LogScope

    efficiency of this depends on whether this is shared between log messsages. Usually this should be just a pointer to a shared list.

  • _logMsgTime :: !TimeSpec

    a POSIX timestamp

    UTC seconds elapsed since UNIX Epoch as returned by clock_gettime on the respective system. NOTE that POSIX is ambigious with regard to treatment of leap seconds, and some implementations may actually return TAI.

    Since: 0.2

Instances

Eq a => Eq (LogMessage a) Source # 

Methods

(==) :: LogMessage a -> LogMessage a -> Bool #

(/=) :: LogMessage a -> LogMessage a -> Bool #

Ord a => Ord (LogMessage a) Source # 
Read a => Read (LogMessage a) Source # 
Show a => Show (LogMessage a) Source # 
Generic (LogMessage a) Source # 

Associated Types

type Rep (LogMessage a) :: * -> * #

Methods

from :: LogMessage a -> Rep (LogMessage a) x #

to :: Rep (LogMessage a) x -> LogMessage a #

NFData a => NFData (LogMessage a) Source # 

Methods

rnf :: LogMessage a -> () #

type Rep (LogMessage a) Source # 
type Rep (LogMessage a) = D1 (MetaData "LogMessage" "System.Logger.Types" "yet-another-logger-0.3.0-5rm0jRQNZUUFOUSMQAcGn3" False) (C1 (MetaCons "LogMessage" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_logMsg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Just Symbol "_logMsgLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LogLevel))) ((:*:) (S1 (MetaSel (Just Symbol "_logMsgScope") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LogScope)) (S1 (MetaSel (Just Symbol "_logMsgTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TimeSpec)))))

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.

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

Methods

get :: LoggerCtxT ctx m a #

put :: a -> LoggerCtxT ctx m () #

state :: (a -> (a, a)) -> LoggerCtxT ctx m a #

Monad m => MonadReader ctx (LoggerCtxT ctx m) Source # 

Methods

ask :: LoggerCtxT ctx m ctx #

local :: (ctx -> ctx) -> LoggerCtxT ctx m a -> LoggerCtxT ctx m a #

reader :: (ctx -> a) -> LoggerCtxT ctx m a #

MonadWriter a m => MonadWriter a (LoggerCtxT ctx m) Source # 

Methods

writer :: (a, a) -> LoggerCtxT ctx m a #

tell :: a -> LoggerCtxT ctx m () #

listen :: LoggerCtxT ctx m a -> LoggerCtxT ctx m (a, a) #

pass :: LoggerCtxT ctx m (a, a -> a) -> LoggerCtxT ctx m a #

MonadError a m => MonadError a (LoggerCtxT ctx m) Source # 

Methods

throwError :: a -> LoggerCtxT ctx m a #

catchError :: LoggerCtxT ctx m a -> (a -> LoggerCtxT ctx m a) -> LoggerCtxT ctx m a #

MonadBase a m => MonadBase a (LoggerCtxT ctx m) Source # 

Methods

liftBase :: a α -> LoggerCtxT ctx m α #

MonadBaseControl b m => MonadBaseControl b (LoggerCtxT ctx m) Source # 

Associated Types

type StM (LoggerCtxT ctx m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (LoggerCtxT ctx m) b -> b a) -> LoggerCtxT ctx m a #

restoreM :: StM (LoggerCtxT ctx m) a -> LoggerCtxT ctx m a #

(Show a, Typeable * a, NFData a, MonadIO m, LoggerCtx ctx a) => MonadLog a (LoggerCtxT ctx m) Source # 

Methods

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 #

MonadTrans (LoggerCtxT ctx) Source # 

Methods

lift :: Monad m => m a -> LoggerCtxT ctx m a #

MonadTransControl (LoggerCtxT ctx) Source # 

Associated Types

type StT (LoggerCtxT ctx :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (LoggerCtxT ctx) -> m a) -> LoggerCtxT ctx m a #

restoreT :: Monad m => m (StT (LoggerCtxT ctx) a) -> LoggerCtxT ctx m a #

Monad m => Monad (LoggerCtxT ctx m) Source # 

Methods

(>>=) :: LoggerCtxT ctx m a -> (a -> LoggerCtxT ctx m b) -> LoggerCtxT ctx m b #

(>>) :: LoggerCtxT ctx m a -> LoggerCtxT ctx m b -> LoggerCtxT ctx m b #

return :: a -> LoggerCtxT ctx m a #

fail :: String -> LoggerCtxT ctx m a #

Functor m => Functor (LoggerCtxT ctx m) Source # 

Methods

fmap :: (a -> b) -> LoggerCtxT ctx m a -> LoggerCtxT ctx m b #

(<$) :: a -> LoggerCtxT ctx m b -> LoggerCtxT ctx m a #

Applicative m => Applicative (LoggerCtxT ctx m) Source # 

Methods

pure :: a -> LoggerCtxT ctx m a #

(<*>) :: LoggerCtxT ctx m (a -> b) -> LoggerCtxT ctx m a -> LoggerCtxT ctx m b #

(*>) :: LoggerCtxT ctx m a -> LoggerCtxT ctx m b -> LoggerCtxT ctx m b #

(<*) :: LoggerCtxT ctx m a -> LoggerCtxT ctx m b -> LoggerCtxT ctx m a #

MonadIO m => MonadIO (LoggerCtxT ctx m) Source # 

Methods

liftIO :: IO a -> LoggerCtxT ctx m a #

MonadThrow m => MonadThrow (LoggerCtxT ctx m) Source # 

Methods

throwM :: Exception e => e -> LoggerCtxT ctx m a #

MonadCatch m => MonadCatch (LoggerCtxT ctx m) Source # 

Methods

catch :: Exception e => LoggerCtxT ctx m a -> (e -> LoggerCtxT ctx m a) -> LoggerCtxT ctx m a #

MonadMask m => MonadMask (LoggerCtxT ctx m) Source # 

Methods

mask :: ((forall a. LoggerCtxT ctx m a -> LoggerCtxT ctx m a) -> LoggerCtxT ctx m b) -> LoggerCtxT ctx m b #

uninterruptibleMask :: ((forall a. LoggerCtxT ctx m a -> LoggerCtxT ctx m a) -> LoggerCtxT ctx m b) -> LoggerCtxT ctx m b #

type StT (LoggerCtxT ctx) a Source # 
type StT (LoggerCtxT ctx) a = StT (ReaderT * ctx) a
type StM (LoggerCtxT ctx m) a Source # 
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 #

Minimal complete definition

logg, withLevel, withPolicy, localScope

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

Methods

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 # 

Methods

logg :: LogFunction a (StateT σ m) Source #

withLevel :: LogLevel -> StateT σ m α -> StateT σ m α Source #

withPolicy :: LogPolicy -> StateT σ m α -> StateT σ m α Source #

localScope :: (LogScope -> LogScope) -> StateT σ m α -> StateT σ m α Source #

MonadLog a m => MonadLog a (ExceptT ε m) Source # 

Methods

logg :: LogFunction a (ExceptT ε m) Source #

withLevel :: LogLevel -> ExceptT ε m α -> ExceptT ε m α Source #

withPolicy :: LogPolicy -> ExceptT ε m α -> ExceptT ε m α Source #

localScope :: (LogScope -> LogScope) -> ExceptT ε m α -> ExceptT ε m α Source #

(Monoid σ, MonadLog a m) => MonadLog a (WriterT σ m) Source # 

Methods

logg :: LogFunction a (WriterT σ m) Source #

withLevel :: LogLevel -> WriterT σ m α -> WriterT σ m α Source #

withPolicy :: LogPolicy -> WriterT σ m α -> WriterT σ m α Source #

localScope :: (LogScope -> LogScope) -> WriterT σ m α -> WriterT σ m α Source #

withLabel :: MonadLog a m => LogLabel -> m α -> m α Source #

Append a LogLabel to the current LogScope when executing the inner computation. The LogScope of the outer computation is unchanged.

Since: 0.1

clearScope :: MonadLog a m => m α -> m α Source #

Executing the inner computation with an empty LogScope. The LogScope of the outer computation is unchanged.

Since: 0.1

popLabel :: MonadLog a m => m α -> m α Source #

Remove the last LogLabel from the current LogScope when executing the inner computation. The LogScope of the outer computation is unchanged.

Since: 0.1

Orphan instances

NFData TimeSpec Source # 

Methods

rnf :: TimeSpec -> () #