| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cli.Extras
Description
|
Synopsis
- type CliLog m = MonadLog Output m
- type CliThrow e m = MonadError e m
- newtype CliT e m a = CliT {}
- runCli :: MonadIO m => CliConfig e -> CliT e m a -> m a
- data CliConfig e
- class Monad m => HasCliConfig e m | m -> e
- getCliConfig :: HasCliConfig e m => m (CliConfig e)
- data Output
- withSpinner :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> m a -> m a
- withSpinnerNoTrail :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> m a -> m a
- withSpinner' :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> Maybe (a -> Text) -> m a -> m a
- class AsUnstructuredError e where
- newCliConfig :: Severity -> Bool -> Bool -> (e -> (Text, ExitCode)) -> IO (CliConfig e)
- getLogLevel :: (MonadIO m, HasCliConfig e m) => m Severity
- putLog :: 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
- data Severity
- class AsProcessFailure e where
- data ProcessFailure = ProcessFailure CmdSpec Int
- data ProcessSpec = ProcessSpec {}
- callCommand :: (MonadIO m, CliLog m) => String -> m ()
- callProcess :: (MonadIO m, CliLog m) => String -> [String] -> m ()
- callProcessAndLogOutput :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) => (Severity, Severity) -> ProcessSpec -> m ()
- createProcess :: (MonadIO m, CliLog m) => ProcessSpec -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- createProcess_ :: (MonadIO m, CliLog m) => String -> ProcessSpec -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- throwExitCode :: (CliThrow e m, AsProcessFailure e) => ProcessSpec -> ExitCode -> m ()
- overCreateProcess :: (CreateProcess -> CreateProcess) -> ProcessSpec -> ProcessSpec
- proc :: FilePath -> [String] -> ProcessSpec
- readCreateProcessWithExitCode :: (MonadIO m, CliLog m) => ProcessSpec -> m (ExitCode, String, String)
- readProcessAndLogOutput :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m) => (Severity, Severity) -> ProcessSpec -> m Text
- readProcessAndLogStderr :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) => Severity -> ProcessSpec -> m Text
- readProcessJSONAndLogStderr :: (FromJSON a, MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) => Severity -> ProcessSpec -> m a
- reconstructCommand :: CmdSpec -> Text
- runProcess_ :: (MonadIO m, CliLog m, CliThrow e m, MonadMask m, AsProcessFailure e) => ProcessSpec -> m ()
- setCwd :: Maybe FilePath -> ProcessSpec -> ProcessSpec
- setDelegateCtlc :: Bool -> ProcessSpec -> ProcessSpec
- setEnvOverride :: (Map String String -> Map String String) -> ProcessSpec -> ProcessSpec
- shell :: String -> ProcessSpec
- waitForProcess :: MonadIO m => ProcessHandle -> m ExitCode
Documentation
type CliThrow e m = MonadError e m Source #
Instances
| MonadIO m => MonadError e (CliT e m) Source # | |
Defined in Cli.Extras.Types | |
| Monad m => MonadLog Output (CliT e m) Source # | |
Defined in Cli.Extras.Types Methods logMessageFree :: (forall n. Monoid n => (Output -> n) -> n) -> CliT e m () # | |
| Monad m => HasCliConfig e (CliT e m) Source # | |
Defined in Cli.Extras.Types Methods getCliConfig :: CliT e m (CliConfig e) Source # | |
| MonadTrans (CliT e) Source # | |
Defined in Cli.Extras.Types | |
| Monad m => MonadReader (CliConfig e) (CliT e m) Source # | |
| Monad m => Monad (CliT e m) Source # | |
| Functor m => Functor (CliT e m) Source # | |
| MonadFail m => MonadFail (CliT e m) Source # | |
Defined in Cli.Extras.Types | |
| Applicative m => Applicative (CliT e m) Source # | |
| MonadIO m => MonadIO (CliT e m) Source # | |
Defined in Cli.Extras.Types | |
| MonadThrow m => MonadThrow (CliT e m) Source # | |
Defined in Cli.Extras.Types | |
| MonadCatch m => MonadCatch (CliT e m) Source # | |
| MonadMask m => MonadMask (CliT e m) Source # | |
Defined in Cli.Extras.Types | |
class Monad m => HasCliConfig e m | m -> e Source #
Minimal complete definition
Instances
| Monad m => HasCliConfig e (CliT e m) Source # | |
Defined in Cli.Extras.Types Methods getCliConfig :: CliT e m (CliConfig e) Source # | |
| HasCliConfig e m => HasCliConfig e (ExceptT e m) Source # | |
Defined in Cli.Extras.Types Methods getCliConfig :: ExceptT e m (CliConfig e) Source # | |
| HasCliConfig e m => HasCliConfig e (StateT s m) Source # | |
Defined in Cli.Extras.Types Methods getCliConfig :: StateT s m (CliConfig e) Source # | |
| (Monoid w, HasCliConfig e m) => HasCliConfig e (WriterT w m) Source # | |
Defined in Cli.Extras.Types Methods getCliConfig :: WriterT w m (CliConfig e) Source # | |
| HasCliConfig e m => HasCliConfig e (ReaderT r m) Source # | |
Defined in Cli.Extras.Types Methods getCliConfig :: ReaderT r m (CliConfig e) Source # | |
getCliConfig :: HasCliConfig e m => m (CliConfig e) Source #
Instances
| Eq Output Source # | |
| Ord Output Source # | |
| Show Output Source # | |
| Monad m => MonadLog Output (CliT e m) Source # | |
Defined in Cli.Extras.Types Methods logMessageFree :: (forall n. Monoid n => (Output -> n) -> n) -> CliT e m () # | |
| Monad m => MonadLog Output (DieT e m) Source # | |
Defined in Cli.Extras.Types Methods logMessageFree :: (forall n. Monoid n => (Output -> n) -> n) -> DieT e m () # | |
withSpinner :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> m a -> m a Source #
Run an action with a CLI spinner.
withSpinnerNoTrail :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) => Text -> m a -> m a Source #
A spinner that leaves no trail after a successful run.
Use if you wish the spinner to be ephemerally visible to the user.
The 'no trail' property automatically carries over to sub-spinners (in that they won't leave a trail either).
Arguments
| :: (MonadIO m, MonadMask m, CliLog m, HasCliConfig e m) | |
| => Text | |
| -> Maybe (a -> Text) | Leave an optional trail with the given message creator |
| -> m a | |
| -> m a |
Advanced version that controls the display and content of the trail message.
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!
Methods
asUnstructuredError :: Prism' e Text Source #
Instances
| AsUnstructuredError Text Source # | |
Defined in Cli.Extras.Logging | |
Arguments
| :: 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.
getLogLevel :: (MonadIO m, HasCliConfig e m) => m Severity 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.
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.
Classes of severity for log messages. These have been chosen to match
syslog severity levels
Constructors
| Emergency | System is unusable. By |
| Alert | Should be corrected immediately. |
| Critical | Critical conditions. |
| Error | Error conditions. |
| Warning | May indicate that an error will occur if action is not taken. |
| Notice | Events that are unusual, but not error conditions. |
| Informational | Normal operational messages that require no action. |
| Debug | Information useful to developers for debugging the application. |
Instances
| Bounded Severity | |
| Enum Severity | |
Defined in Control.Monad.Log | |
| Eq Severity | |
| Ord Severity | |
Defined in Control.Monad.Log | |
| Read Severity | |
| Show Severity | |
| Pretty Severity | |
Defined in Control.Monad.Log | |
class AsProcessFailure e where Source #
Indicates arbitrary process failures form one variant (or conceptual projection) of the error type.
Methods
Instances
| AsProcessFailure ProcessFailure Source # | |
Defined in Cli.Extras.Process Methods asProcessFailure :: Prism' ProcessFailure ProcessFailure Source # | |
data ProcessFailure Source #
Constructors
| ProcessFailure CmdSpec Int |
Instances
| Show ProcessFailure Source # | |
Defined in Cli.Extras.Process Methods showsPrec :: Int -> ProcessFailure -> ShowS # show :: ProcessFailure -> String # showList :: [ProcessFailure] -> ShowS # | |
| AsProcessFailure ProcessFailure Source # | |
Defined in Cli.Extras.Process Methods asProcessFailure :: Prism' ProcessFailure ProcessFailure Source # | |
data ProcessSpec Source #
Constructors
| ProcessSpec | |
Fields | |
callCommand :: (MonadIO m, CliLog m) => String -> m () Source #
Like callCommand, but logging (with Debug
severity) the process which was started.
callProcess :: (MonadIO m, CliLog m) => String -> [String] -> m () Source #
Like callProcess, but logging (with Debug
severity) the process which was started.
callProcessAndLogOutput Source #
Arguments
| :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) | |
| => (Severity, Severity) | This tuple controls the severity of each output stream. Its |
| -> ProcessSpec | |
| -> m () |
Like readProcess, but such that each of the child
processes' standard output streams (stdout and stderr) is logged,
with the corresponding severity.
Usually, this function is called as callProcessAndLogOutput (Debug,
Error). If the child process is known to print diagnostic or
informative messages to stderr, it is advisable to call
callProcessAndLogOutput with a non-Error severity for stderr, for
example callProcessAndLogOutput (Debug, Debug).
createProcess :: (MonadIO m, CliLog m) => ProcessSpec -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
Like createProcess, but logging (with Debug
severity) the process which was started.
createProcess_ :: (MonadIO m, CliLog m) => String -> ProcessSpec -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
Like createProcess_, but logging (with Debug
severity) the process which was started.
throwExitCode :: (CliThrow e m, AsProcessFailure e) => ProcessSpec -> ExitCode -> m () Source #
Aborts the computation (using throwError) when given a
non-ExitSuccess ExitCode.
overCreateProcess :: (CreateProcess -> CreateProcess) -> ProcessSpec -> ProcessSpec Source #
readCreateProcessWithExitCode :: (MonadIO m, CliLog m) => ProcessSpec -> m (ExitCode, String, String) Source #
readProcessAndLogOutput Source #
Arguments
| :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m) | |
| => (Severity, Severity) | This tuple controls the severity of each output stream. Its |
| -> ProcessSpec | |
| -> m Text |
Like readProcess, but such that each of the child
processes' standard output streams (stdout and stderr) is logged,
with the corresponding severity.
Usually, this function is called as readProcessAndLogOutput (Debug,
Error). If the child process is known to print diagnostic or
informative messages to stderr, it is advisable to call
readProcessAndLogOutput with a non-Error severity for stderr, for
example readProcessAndLogOutput (Debug, Debug).
readProcessAndLogStderr :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) => Severity -> ProcessSpec -> m Text Source #
readProcessJSONAndLogStderr :: (FromJSON a, MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadMask m) => Severity -> ProcessSpec -> m a Source #
reconstructCommand :: CmdSpec -> Text Source #
Pretty print a CmdSpec
runProcess_ :: (MonadIO m, CliLog m, CliThrow e m, MonadMask m, AsProcessFailure e) => ProcessSpec -> m () Source #
Runs a process to completion, aborting the computation (using
throwExitCode) in case of a non-ExitSuccess exit status.
setCwd :: Maybe FilePath -> ProcessSpec -> ProcessSpec Source #
setDelegateCtlc :: Bool -> ProcessSpec -> ProcessSpec Source #
setEnvOverride :: (Map String String -> Map String String) -> ProcessSpec -> ProcessSpec Source #
shell :: String -> ProcessSpec Source #
waitForProcess :: MonadIO m => ProcessHandle -> m ExitCode Source #
Wrapper around waitForProcess