| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Log.Class
Description
The MonadLog type class of monads with logging capabilities.
Synopsis
- data UTCTime
- class Monad m => MonadTime (m :: Type -> Type) where- currentTime :: m UTCTime
 
- class MonadTime m => MonadLog m where- logMessage :: UTCTime -> LogLevel -> Text -> Value -> m ()
- localData :: [Pair] -> m a -> m a
- localDomain :: Text -> m a -> m a
- getLoggerEnv :: m LoggerEnv
 
- logAttention :: (MonadLog m, ToJSON a) => Text -> a -> m ()
- logInfo :: (MonadLog m, ToJSON a) => Text -> a -> m ()
- logTrace :: (MonadLog m, ToJSON a) => Text -> a -> m ()
- logAttention_ :: MonadLog m => Text -> m ()
- logInfo_ :: MonadLog m => Text -> m ()
- logTrace_ :: MonadLog m => Text -> m ()
Documentation
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 | |
| Data UTCTime | |
| 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 :: (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 | |
| Defined in Data.Time.Clock.Internal.UTCTime | |
| ToJSON UTCTime | |
| Defined in Data.Aeson.Types.ToJSON | |
| ToJSONKey UTCTime | |
| Defined in Data.Aeson.Types.ToJSON | |
| FromJSON UTCTime | |
| FromJSONKey UTCTime | |
| Defined in Data.Aeson.Types.FromJSON Methods | |
| NFData UTCTime | |
| Defined in Data.Time.Clock.Internal.UTCTime | |
| FormatTime UTCTime | |
| Defined in Data.Time.Format Methods formatCharacter :: Char -> Maybe (TimeLocale -> Maybe NumericPadOption -> Maybe Int -> UTCTime -> String) # | |
| ParseTime UTCTime | |
| Defined in Data.Time.Format.Parse | |
| Monad m => MonadTime (ReaderT UTCTime m) | This is  Since: monad-time-0.3.0.0 | 
| Defined in Control.Monad.Time Methods currentTime :: ReaderT UTCTime m UTCTime # | |
class Monad m => MonadTime (m :: Type -> Type) where #
Class of monads which carry the notion of the current time.
Methods
currentTime :: m UTCTime #
Instances
| MonadTime IO | Base instance for IO. | 
| Defined in Control.Monad.Time Methods currentTime :: IO UTCTime # | |
| (MonadTime m, MonadTrans t, Monad (t m)) => MonadTime (t m) | Generic, overlapping instance. | 
| Defined in Control.Monad.Time Methods currentTime :: t m UTCTime # | |
| Monad m => MonadTime (ReaderT UTCTime m) | This is  Since: monad-time-0.3.0.0 | 
| Defined in Control.Monad.Time Methods currentTime :: ReaderT UTCTime 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.
Methods
Arguments
| :: UTCTime | Time of the event. | 
| -> 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.
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.