log-base-0.7.1.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

Eq UTCTime 

Methods

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

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

Data 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 :: (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 
ToJSON UTCTime 
ToJSONKey UTCTime 
FromJSON UTCTime 
FromJSONKey UTCTime 
NFData UTCTime 

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
ParseTime UTCTime 

class Monad m => MonadTime m where #

Class of monads which carry the notion of the current time.

Minimal complete definition

currentTime

Methods

currentTime :: m UTCTime #

Instances

MonadTime IO

Base instance for IO.

(MonadTime m, MonadTrans t, Monad (t m)) => MonadTime (t m)

Generic, overlapping instance.

Methods

currentTime :: t m UTCTime #

class MonadTime 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.

Minimal complete definition

logMessage, localData, localDomain

Methods

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

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.

Instances

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

Generic, overlapping instance.

Methods

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

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

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

(MonadBase IO m, MonadTime m) => MonadLog (LogT m) Source # 

Methods

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

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

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

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.