Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides a logging handler that facilitates safe ouputting to terminal using MVar based locking. | Spinner.hs and Process.hs work on this guarantee.
Synopsis
- class AsUnstructuredError e where
- newCliConfig :: Severity -> Bool -> Bool -> (e -> (Text, ExitCode)) -> IO (CliConfig e)
- runCli :: MonadIO m => CliConfig e -> CliT e m a -> m a
- verboseLogLevel :: Severity
- isOverwrite :: Output -> Bool
- getSeverity :: Output -> Maybe Severity
- getLogLevel :: (MonadIO m, HasCliConfig e m) => m Severity
- setLogLevel :: (MonadIO m, HasCliConfig e m) => Severity -> m ()
- putLog :: CliLog m => Severity -> Text -> m ()
- putLogRaw :: CliLog m => Severity -> Text -> m ()
- failWith :: (CliThrow e m, AsUnstructuredError e) => Text -> m a
- errorToWarning :: (HasCliConfig e m, CliLog m) => e -> m ()
- withExitFailMessage :: (CliLog m, MonadCatch m) => Text -> m a -> m a
- writeLog :: MonadIO m => Bool -> Bool -> WithSeverity Text -> m ()
- allowUserToMakeLoggingVerbose :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => String -> Text -> m ()
- getChars :: IO String
- fork :: (HasCliConfig e m, MonadIO m) => CliT e IO () -> m ThreadId
Documentation
class AsUnstructuredError e where Source #
Indicates unstructured errors form one variant (or conceptual projection) of the error type.
Shouldn't really use this, but who has time to clean up that much!
asUnstructuredError :: Prism' e Text Source #
Instances
AsUnstructuredError Text Source # | |
Defined in Cli.Extras.Logging |
:: Severity | The initial log level. Messages below this severity will not be
logged, unless the log level is subsequently altered using
|
-> Bool | Should ANSI terminal formatting be disabled? |
-> Bool | Should spinners be disabled? |
-> (e -> (Text, ExitCode)) | How to display errors, and compute the |
-> IO (CliConfig e) |
Create a new CliConfig
, initialized with the provided values.
isOverwrite :: Output -> Bool Source #
getLogLevel :: (MonadIO m, HasCliConfig e m) => m Severity Source #
setLogLevel :: (MonadIO m, HasCliConfig e m) => Severity -> m () Source #
putLog :: CliLog m => Severity -> Text -> m () Source #
Log a message to the console.
The message is guaranteed to be logged uninterrupted, even if there are ongoing spinners.
putLogRaw :: CliLog m => Severity -> Text -> m () Source #
Like putLog
but without the implicit newline added.
failWith :: (CliThrow e m, AsUnstructuredError e) => Text -> m a Source #
Like `putLog Alert` but also abrupts the program.
errorToWarning :: (HasCliConfig e m, CliLog m) => e -> m () Source #
Log an error as though it were a warning, in a non-fatal way.
withExitFailMessage :: (CliLog m, MonadCatch m) => Text -> m a -> m a Source #
Intercept ExitFailure exceptions and log the given alert before exiting.
This is useful when you want to provide contextual information to a deeper failure.
:: MonadIO m | |
=> Bool | Should a new line be printed after the message? |
-> Bool | Should ANSI terminal formatting be used when printing the message? |
-> WithSeverity Text | The message to print. |
-> m () |
Log a message to standard output.
allowUserToMakeLoggingVerbose Source #
:: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) | |
=> String | The key(s) which should be read to indicate a shift in verbosity. |
-> Text | A description of the key that must be pressed. |
-> m () |
Allows the user to immediately switch to verbose logging when a particular sequence of characters is read from the terminal.
Call this function in a thread, and kill it to turn off keystroke monitoring.