Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Monad m => MonadLog m where
- logMsg :: Exception e => Level -> e -> m ()
- logString_ :: String -> m ()
- logStringLn :: String -> m ()
- data Level
- data LoggingConf = LoggingConf {}
- newtype Logged m a = Logged {
- runLogged :: ReaderT (LoggingConf, Journal) m a
- type LIO = Logged IO
- withLogging :: (MonadIO m, MonadMask m) => LoggingConf -> Logged m a -> m (Either ExitCode a)
- withLogging_ :: (MonadIO m, MonadMask m) => LoggingConf -> Logged m a -> m a
- logOptions :: Parser LoggingConf
- execWithParser :: Parser a -> Maybe Version -> Maybe String -> InfoMod (a, LoggingConf) -> (a -> LIO b) -> IO (Either ExitCode b)
- execWithParser_ :: Parser a -> Maybe Version -> Maybe String -> InfoMod (a, LoggingConf) -> (a -> LIO b) -> IO b
- data PanicCall = PanicCall String
- panic :: MonadIO m => String -> m a
Documentation
class Monad m => MonadLog m where Source #
Monads in which messages can be logged. Any Exception
can be
logged; it is reported and/or collected, but does not abort any
computation.
logMsg :: Exception e => Level -> e -> m () Source #
Logs a message at a given level. Depending on settings, the message may be printed and/or stored.
logString_ :: String -> m () Source #
Updates the progress indicator. The message should not contain line feeds, as it is intended to fit on one line and be overwritten repeatedly.
logStringLn :: String -> m () Source #
Prints a progress indication. The message should persist on the user's terminal.
Severity levels for logging.
Debug | Message only useful for debugging. Typically ignored. |
Info | Purely informative message, e.g. progress reports. Sometimes printed. |
Notice | Something remarkable, but harmless. Sometimes printed, but not collected. |
Warning | Something unexpected, but usually not a problem. Typically printed, but not collected. |
Error | Recoverable error, will normally result in `ExitFailure 1`. Printed and collected. |
data LoggingConf Source #
LoggingConf | |
|
Instances
Show LoggingConf Source # | |
Defined in Control.Monad.Log showsPrec :: Int -> LoggingConf -> ShowS # show :: LoggingConf -> String # showList :: [LoggingConf] -> ShowS # |
Adds logging to any MonadIO
type. Warnings are printed
to stderr immediately, but we remember whether any were emitted. If
so, we exit with an error code. The advantage over WarningT IO
is
that the warnings are tracked even if the computation exits with an
exception. Progress indicators are sent to the controlling terminal,
and dicarded if none exists.
Logged | |
|
Instances
MonadTrans Logged Source # | |
Defined in Control.Monad.Log | |
MonadTransControl Logged Source # | |
MonadBase b m => MonadBase b (Logged m) Source # | |
Defined in Control.Monad.Log | |
MonadBaseControl b m => MonadBaseControl b (Logged m) Source # | |
Monad m => Monad (Logged m) Source # | |
Functor m => Functor (Logged m) Source # | |
Applicative m => Applicative (Logged m) Source # | |
Alternative m => Alternative (Logged m) Source # | |
MonadIO m => MonadIO (Logged m) Source # | |
Defined in Control.Monad.Log | |
MonadThrow m => MonadThrow (Logged m) Source # | |
Defined in Control.Monad.Log | |
MonadCatch m => MonadCatch (Logged m) Source # | |
MonadMask m => MonadMask (Logged m) Source # | |
Defined in Control.Monad.Log | |
PrimMonad m => PrimMonad (Logged m) Source # | |
MonadIO m => MonadLog (Logged m) Source # | |
MFunctor Logged Source # | |
type StT Logged a Source # | |
Defined in Control.Monad.Log | |
type PrimState (Logged m) Source # | |
Defined in Control.Monad.Log | |
type StM (Logged m) a Source # | |
Defined in Control.Monad.Log |
withLogging :: (MonadIO m, MonadMask m) => LoggingConf -> Logged m a -> m (Either ExitCode a) Source #
withLogging_ :: (MonadIO m, MonadMask m) => LoggingConf -> Logged m a -> m a Source #
execWithParser :: Parser a -> Maybe Version -> Maybe String -> InfoMod (a, LoggingConf) -> (a -> LIO b) -> IO (Either ExitCode b) Source #
execWithParser_ :: Parser a -> Maybe Version -> Maybe String -> InfoMod (a, LoggingConf) -> (a -> LIO b) -> IO b Source #
General wrapper around main. Runs a command line parser with added
standard options (logging and usage related), runs the actual main
function, prints collected warnings and caught exceptions, and exits
appropriately: `exitWith (ExitFailure 2)` if an exception was
caught, exitFailure
if there were warnings of sufficient severity,
and exitSuccess
otherwise.
An exception than can be thrown when it doesn't seem warranted to define a custom exception. Transports a message.
Instances
Show PanicCall Source # | |
Exception PanicCall Source # | |
Defined in Control.Monad.Log toException :: PanicCall -> SomeException # fromException :: SomeException -> Maybe PanicCall # displayException :: PanicCall -> String # |