| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cli.Extras.Process
Description
Synopsis
- 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
- runProc :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m, MonadMask m) => ProcessSpec -> m ()
- runProcSilently :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m, MonadMask m) => ProcessSpec -> m ()
- readProc :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m) => ProcessSpec -> m Text
Documentation
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
runProc :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m, MonadMask m) => ProcessSpec -> m () Source #
A wrapper for callProcessAndLogOutput with sensible default
verbosities: standard output gets the Notice severity and standard
error gets Error.
runProcSilently :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m, MonadMask m) => ProcessSpec -> m () Source #
readProc :: (MonadIO m, CliLog m, CliThrow e m, AsProcessFailure e, MonadFail m) => ProcessSpec -> m Text Source #
A wrapper for readProcessAndLogOutput with sensible default
verbosities: standard output gets the Debug severity and standard
error gets Error.
The child process' output gets the Debug severity rather than the
Notice severity because it is first and foremost /returned by this
function/, so you can log it afterwards in a reasonable manner.