log-base-0.10.0.1: Structured logging solution (base package)
Safe HaskellNone
LanguageHaskell2010

Log.Class

Description

The MonadLog type class of monads with logging capabilities.

Synopsis

Documentation

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Instances details
Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

class Monad m => MonadLog m where Source #

Represents the family of monads with logging capabilities. Each MonadLog carries with it some associated state (the logging environment) that can be modified locally with localData and localDomain.

Methods

logMessage Source #

Arguments

:: LogLevel

Log level.

-> Text

Log message.

-> Value

Additional data associated with the message.

-> m () 

Write a message to the log.

localData :: [Pair] -> m a -> m a Source #

Extend the additional data associated with each log message locally.

localDomain :: Text -> m a -> m a Source #

Extend the current application domain locally.

getLoggerEnv :: m LoggerEnv Source #

Get current LoggerEnv object. Useful for construction of logging functions that work in a different monad, see getLoggerIO as an example.

Instances

Instances details
(MonadLog m, Monad (t m), MonadTransControl t) => MonadLog (t m) Source #

Generic, overlapping instance.

Instance details

Defined in Log.Class

Methods

logMessage :: LogLevel -> Text -> Value -> t m () Source #

localData :: [Pair] -> t m a -> t m a Source #

localDomain :: Text -> t m a -> t m a Source #

getLoggerEnv :: t m LoggerEnv Source #

MonadBase IO m => MonadLog (LogT m) Source # 
Instance details

Defined in Log.Monad

logAttention :: (MonadLog m, ToJSON a) => Text -> a -> m () Source #

Log a message and its associated data using current time as the event time and the LogAttention log level.

logInfo :: (MonadLog m, ToJSON a) => Text -> a -> m () Source #

Log a message and its associated data using current time as the event time and the LogInfo log level.

logTrace :: (MonadLog m, ToJSON a) => Text -> a -> m () Source #

Log a message and its associated data using current time as the event time and the LogTrace log level.

logAttention_ :: MonadLog m => Text -> m () Source #

Like logAttention, but without any additional associated data.

logInfo_ :: MonadLog m => Text -> m () Source #

Like logInfo, but without any additional associated data.

logTrace_ :: MonadLog m => Text -> m () Source #

Like logTrace, but without any additional associated data.