| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
RIO.Process
Contents
Description
Interacting with external processes.
This module provides a layer on top of System.Process.Typed, with the following additions:
- For efficiency, it will cache PATHlookups.
- For convenience, you can set the working directory and env vars
   overrides in a RIOenvironment instead of on the individual calls to the process.
- Built-in support for logging at the debug level.
In order to switch over to this API, the main idea is:
- Like most of the rio library, you need to create an environment
   value (this time ProcessContext), and include it in yourRIOenvironment. SeemkProcessContext.
- Instead of using the procfunction from System.Process.Typed for creating aProcessConfig, use the locally definedprocfunction, which will handle overriding environment variables, looking up paths, performing logging, etc.
Once you have your ProcessConfig, use the standard functions from
 Typed (reexported here for convenient) for running
 the ProcessConfig.
Since: 0.0.3.0
Synopsis
- data ProcessContext
- class HasProcessContext env where- processContextL :: Lens' env ProcessContext
 
- type EnvVars = Map Text Text
- mkProcessContext :: MonadIO m => EnvVars -> m ProcessContext
- mkDefaultProcessContext :: MonadIO m => m ProcessContext
- modifyEnvVars :: MonadIO m => ProcessContext -> (EnvVars -> EnvVars) -> m ProcessContext
- withModifyEnvVars :: (HasProcessContext env, MonadReader env m, MonadIO m) => (EnvVars -> EnvVars) -> m a -> m a
- lookupEnvFromContext :: (MonadReader env m, HasProcessContext env) => Text -> m (Maybe Text)
- withWorkingDir :: (HasProcessContext env, MonadReader env m, MonadIO m) => FilePath -> m a -> m a
- workingDirL :: HasProcessContext env => Lens' env (Maybe FilePath)
- envVarsL :: HasProcessContext env => SimpleGetter env EnvVars
- envVarsStringsL :: HasProcessContext env => SimpleGetter env [(String, String)]
- exeSearchPathL :: HasProcessContext env => SimpleGetter env [FilePath]
- resetExeCache :: (MonadIO m, MonadReader env m, HasProcessContext env) => m ()
- proc :: (HasProcessContext env, HasLogFunc env, MonadReader env m, MonadIO m, HasCallStack) => FilePath -> [String] -> (ProcessConfig () () () -> m a) -> m a
- withProcess :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcess_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessWait :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessWait_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessTerm :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- withProcessTerm_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a
- exec :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env b
- execSpawn :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env a
- data LoggedProcessContext = LoggedProcessContext ProcessContext LogFunc
- withProcessContextNoLogging :: MonadIO m => RIO LoggedProcessContext a -> m a
- data ProcessException
- doesExecutableExist :: (MonadIO m, MonadReader env m, HasProcessContext env) => String -> m Bool
- findExecutable :: (MonadIO m, MonadReader env m, HasProcessContext env) => String -> m (Either ProcessException FilePath)
- exeExtensions :: (MonadIO m, MonadReader env m, HasProcessContext env) => m [String]
- augmentPath :: [FilePath] -> Maybe Text -> Either ProcessException Text
- augmentPathMap :: [FilePath] -> EnvVars -> Either ProcessException EnvVars
- showProcessArgDebug :: String -> Text
- data ProcessConfig stdin stdout stderr
- data StreamSpec (streamType :: StreamType) a
- data StreamType
- data Process stdin stdout stderr
- setStdin :: StreamSpec STInput stdin -> ProcessConfig stdin0 stdout stderr -> ProcessConfig stdin stdout stderr
- setStdout :: StreamSpec STOutput stdout -> ProcessConfig stdin stdout0 stderr -> ProcessConfig stdin stdout stderr
- setStderr :: StreamSpec STOutput stderr -> ProcessConfig stdin stdout stderr0 -> ProcessConfig stdin stdout stderr
- setCloseFds :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setCreateGroup :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setDelegateCtlc :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setDetachConsole :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setCreateNewConsole :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setNewSession :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildGroup :: GroupID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildUser :: UserID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- mkStreamSpec :: StdStream -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a
- inherit :: StreamSpec anyStreamType ()
- closed :: StreamSpec anyStreamType ()
- byteStringInput :: ByteString -> StreamSpec STInput ()
- byteStringOutput :: StreamSpec STOutput (STM ByteString)
- createPipe :: StreamSpec anyStreamType Handle
- useHandleOpen :: Handle -> StreamSpec anyStreamType ()
- useHandleClose :: Handle -> StreamSpec anyStreamType ()
- startProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m (Process stdin stdout stderr)
- stopProcess :: MonadIO m => Process stdin stdout stderr -> m ()
- readProcess :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ExitCode, ByteString, ByteString)
- readProcess_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ByteString, ByteString)
- runProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m ExitCode
- runProcess_ :: MonadIO m => ProcessConfig stdin stdout stderr -> m ()
- readProcessStdout :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m (ExitCode, ByteString)
- readProcessStdout_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ByteString
- readProcessStderr :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m (ExitCode, ByteString)
- readProcessStderr_ :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m ByteString
- waitExitCode :: MonadIO m => Process stdin stdout stderr -> m ExitCode
- waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode
- getExitCode :: MonadIO m => Process stdin stdout stderr -> m (Maybe ExitCode)
- getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode)
- checkExitCode :: MonadIO m => Process stdin stdout stderr -> m ()
- checkExitCodeSTM :: Process stdin stdout stderr -> STM ()
- getStdin :: Process stdin stdout stderr -> stdin
- getStdout :: Process stdin stdout stderr -> stdout
- getStderr :: Process stdin stdout stderr -> stderr
- data ExitCodeException = ExitCodeException {- eceExitCode :: ExitCode
- eceProcessConfig :: ProcessConfig () () ()
- eceStdout :: ByteString
- eceStderr :: ByteString
 
- data ByteStringOutputException = ByteStringOutputException SomeException (ProcessConfig () () ())
- unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle
Process context
data ProcessContext Source #
Context in which to run processes.
Since: 0.0.3.0
Instances
| HasProcessContext ProcessContext Source # | |
| Defined in RIO.Process Methods processContextL :: Lens' ProcessContext ProcessContext Source # | |
class HasProcessContext env where Source #
Get the ProcessContext from the environment.
Since: 0.0.3.0
Methods
processContextL :: Lens' env ProcessContext Source #
Instances
| HasProcessContext LoggedProcessContext Source # | |
| Defined in RIO.Process | |
| HasProcessContext ProcessContext Source # | |
| Defined in RIO.Process Methods processContextL :: Lens' ProcessContext ProcessContext Source # | |
| HasProcessContext SimpleApp Source # | |
| Defined in RIO.Prelude.Simple Methods | |
mkProcessContext :: MonadIO m => EnvVars -> m ProcessContext Source #
Create a new ProcessContext from the given environment variable map.
Since: 0.0.3.0
mkDefaultProcessContext :: MonadIO m => m ProcessContext Source #
Same as mkProcessContext but uses the system environment (from
 getEnvironment).
Since: 0.0.3.0
modifyEnvVars :: MonadIO m => ProcessContext -> (EnvVars -> EnvVars) -> m ProcessContext Source #
Modify the environment variables of a ProcessContext. This will not
 change the working directory.
Note that this requires MonadIO, as it will create a new IORef
 for the cache.
Since: 0.0.3.0
withModifyEnvVars :: (HasProcessContext env, MonadReader env m, MonadIO m) => (EnvVars -> EnvVars) -> m a -> m a Source #
Use modifyEnvVars to create a new ProcessContext, and then
 use it in the provided action.
Since: 0.0.3.0
lookupEnvFromContext :: (MonadReader env m, HasProcessContext env) => Text -> m (Maybe Text) Source #
Look into the ProcessContext and return the specified environmet variable if one is
 available.
Since: 0.1.14.0
withWorkingDir :: (HasProcessContext env, MonadReader env m, MonadIO m) => FilePath -> m a -> m a Source #
Set the working directory to be used by child processes.
Since: 0.0.3.0
Lenses
workingDirL :: HasProcessContext env => Lens' env (Maybe FilePath) Source #
Override the working directory processes run in. Nothing means
 the current process's working directory.
Since: 0.0.3.0
envVarsL :: HasProcessContext env => SimpleGetter env EnvVars Source #
Get the environment variables. We cannot provide a Lens here,
 since updating the environment variables requires an IO action to
 allocate a new IORef for holding the executable path cache.
Since: 0.0.3.0
envVarsStringsL :: HasProcessContext env => SimpleGetter env [(String, String)] Source #
exeSearchPathL :: HasProcessContext env => SimpleGetter env [FilePath] Source #
Get the list of directories searched for executables (the PATH).
Similar to envVarMapL, this cannot be a full Lens.
Since: 0.0.3.0
Actions
resetExeCache :: (MonadIO m, MonadReader env m, HasProcessContext env) => m () Source #
Reset the executable cache.
Since: 0.0.3.0
Configuring
Arguments
| :: (HasProcessContext env, HasLogFunc env, MonadReader env m, MonadIO m, HasCallStack) | |
| => FilePath | command to run | 
| -> [String] | command line arguments | 
| -> (ProcessConfig () () () -> m a) | |
| -> m a | 
Provide a ProcessConfig based on the ProcessContext in
 scope. Deals with resolving the full path, setting the child
 process's environment variables, setting the working directory, and
 wrapping the call with withProcessTimeLog for debugging output.
This is intended to be analogous to the proc function provided by
 the System.Process.Typed module, but has a different type
 signature to (1) allow it to perform IO actions for looking up
 paths, and (2) allow logging and timing of the running action.
Since: 0.0.3.0
Spawning (run child process)
withProcess :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Deprecated: Please consider using withProcessWait, or instead use withProcessTerm
Same as withProcess, but generalized to MonadUnliftIO.
Since: 0.0.3.0
withProcess_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Deprecated: Please consider using withProcessWait, or instead use withProcessTerm
Same as withProcess_, but generalized to MonadUnliftIO.
Since: 0.0.3.0
withProcessWait :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessWait, but generalized to MonadUnliftIO.
Since: 0.1.10.0
withProcessWait_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessWait_, but generalized to MonadUnliftIO.
Since: 0.1.10.0
withProcessTerm :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessTerm, but generalized to MonadUnliftIO.
Since: 0.1.10.0
withProcessTerm_ :: MonadUnliftIO m => ProcessConfig stdin stdout stderr -> (Process stdin stdout stderr -> m a) -> m a Source #
Same as withProcessTerm_, but generalized to MonadUnliftIO.
Since: 0.1.10.0
Exec (replacing current process)
exec :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env b Source #
Execute a process within the configured environment.
Execution will not return, because either:
1) On non-windows, execution is taken over by execv of the sub-process. This allows signals to be propagated (#527)
2) On windows, an ExitCode exception will be thrown.
Since: 0.0.3.0
execSpawn :: (HasProcessContext env, HasLogFunc env) => String -> [String] -> RIO env a Source #
Like exec, but does not use execv on non-windows. This way,
 there is a sub-process, which is helpful in some cases
 (https://github.com/commercialhaskell/stack/issues/1306).
This function only exits by throwing ExitCode.
Since: 0.0.3.0
Environment helper
data LoggedProcessContext Source #
A convenience environment combining a LogFunc and a ProcessContext
Since: 0.0.3.0
Constructors
| LoggedProcessContext ProcessContext LogFunc | 
Instances
| HasLogFunc LoggedProcessContext Source # | |
| Defined in RIO.Process | |
| HasProcessContext LoggedProcessContext Source # | |
| Defined in RIO.Process | |
withProcessContextNoLogging :: MonadIO m => RIO LoggedProcessContext a -> m a Source #
Run an action using a LoggedProcessContext with default
 settings and no logging.
Since: 0.0.3.0
Exceptions
data ProcessException Source #
Exception type which may be generated in this module.
NOTE Other exceptions may be thrown by underlying libraries!
Since: 0.0.3.0
Constructors
| NoPathFound | |
| ExecutableNotFound String [FilePath] | |
| ExecutableNotFoundAt FilePath | |
| PathsInvalidInPath [FilePath] | 
Instances
| Show ProcessException Source # | |
| Defined in RIO.Process Methods showsPrec :: Int -> ProcessException -> ShowS # show :: ProcessException -> String # showList :: [ProcessException] -> ShowS # | |
| Exception ProcessException Source # | |
| Defined in RIO.Process Methods toException :: ProcessException -> SomeException # | |
Utilities
Arguments
| :: (MonadIO m, MonadReader env m, HasProcessContext env) | |
| => String | Name of executable | 
| -> m Bool | 
Check if the given executable exists on the given PATH.
Since: 0.0.3.0
Arguments
| :: (MonadIO m, MonadReader env m, HasProcessContext env) | |
| => String | Name of executable | 
| -> m (Either ProcessException FilePath) | Full path to that executable on success | 
Find the complete path for the given executable name.
On POSIX systems, filenames that match but are not exectuables are excluded.
On Windows systems, the executable names tried, in turn, are the supplied
 name (only if it has an extension) and that name extended by each of the
 exeExtensions. Also, this function may behave differently from
 findExecutable. The latter excludes as executables filenames
 without a .bat, .cmd, .com or .exe extension (case-insensitive).
Since: 0.0.3.0
exeExtensions :: (MonadIO m, MonadReader env m, HasProcessContext env) => m [String] Source #
Get the filename extensions for executable files, including the dot (if any).
On POSIX systems, this is [""].
On Windows systems, the list is determined by the value of the PATHEXT
 environment variable, if it present in the environment. If the variable is
 absent, this is its default value on a Windows system. This function may,
 therefore, behave differently from exeExtension,
 which returns only ".exe".
Since: 0.1.13.0
augmentPath :: [FilePath] -> Maybe Text -> Either ProcessException Text Source #
Augment the PATH environment variable with the given extra paths.
Since: 0.0.3.0
augmentPathMap :: [FilePath] -> EnvVars -> Either ProcessException EnvVars Source #
Apply augmentPath on the PATH value in the given EnvVars.
Since: 0.0.3.0
showProcessArgDebug :: String -> Text Source #
Show a process arg including speechmarks when necessary. Just for debugging purposes, not functionally important.
Since: 0.0.3.0
Reexports
data ProcessConfig stdin stdout stderr #
An abstract configuration for a process, which can then be
 launched into an actual running Process. Takes three type
 parameters, providing the types of standard input, standard output,
 and standard error, respectively.
There are three ways to construct a value of this type:
- With the procsmart constructor, which takes a command name and a list of arguments.
- With the shellsmart constructor, which takes a shell string
- With the IsStringinstance via OverloadedStrings. If you provide it a string with no spaces (e.g.,"date"), it will treat it as a raw command with no arguments (e.g.,proc "date" []). If it has spaces, it will useshell.
In all cases, the default for all three streams is to inherit the streams from the parent process. For other settings, see the setters below for default values.
Since: typed-process-0.1.0.0
Instances
| Show (ProcessConfig stdin stdout stderr) | |
| Defined in System.Process.Typed Methods showsPrec :: Int -> ProcessConfig stdin stdout stderr -> ShowS # show :: ProcessConfig stdin stdout stderr -> String # showList :: [ProcessConfig stdin stdout stderr] -> ShowS # | |
| (stdin ~ (), stdout ~ (), stderr ~ ()) => IsString (ProcessConfig stdin stdout stderr) | |
| Defined in System.Process.Typed Methods fromString :: String -> ProcessConfig stdin stdout stderr # | |
| Display (ProcessConfig a b c) Source # | Since: 0.1.0.0 | 
| Defined in RIO.Prelude.Display Methods display :: ProcessConfig a b c -> Utf8Builder Source # textDisplay :: ProcessConfig a b c -> Text Source # | |
data StreamSpec (streamType :: StreamType) a #
A specification for how to create one of the three standard child streams. See examples below.
Since: typed-process-0.1.0.0
Instances
| Functor (StreamSpec streamType) | |
| Defined in System.Process.Typed Methods fmap :: (a -> b) -> StreamSpec streamType a -> StreamSpec streamType b # (<$) :: a -> StreamSpec streamType b -> StreamSpec streamType a # | |
| (streamType ~ STInput, res ~ ()) => IsString (StreamSpec streamType res) | This instance uses  Since: typed-process-0.1.0.0 | 
| Defined in System.Process.Typed Methods fromString :: String -> StreamSpec streamType res # | |
data StreamType #
Whether a stream is an input stream or output stream. Note that
 this is from the perspective of the child process, so that a
 child's standard input stream is an STInput, even though the
 parent process will be writing to it.
Since: typed-process-0.1.0.0
data Process stdin stdout stderr #
A running process. The three type parameters provide the type of the standard input, standard output, and standard error streams.
Since: typed-process-0.1.0.0
setStdin :: StreamSpec STInput stdin -> ProcessConfig stdin0 stdout stderr -> ProcessConfig stdin stdout stderr #
Set the child's standard input stream to the given StreamSpec.
Default: inherit
Since: typed-process-0.1.0.0
setStdout :: StreamSpec STOutput stdout -> ProcessConfig stdin stdout0 stderr -> ProcessConfig stdin stdout stderr #
Set the child's standard output stream to the given StreamSpec.
Default: inherit
Since: typed-process-0.1.0.0
setStderr :: StreamSpec STOutput stderr -> ProcessConfig stdin stdout stderr0 -> ProcessConfig stdin stdout stderr #
Set the child's standard error stream to the given StreamSpec.
Default: inherit
Since: typed-process-0.1.0.0
setCloseFds :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
Should we close all file descriptors besides stdin, stdout, and
 stderr? See close_fds for more information.
Default: False
Since: typed-process-0.1.0.0
setCreateGroup :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
Should we create a new process group?
Default: False
Since: typed-process-0.1.0.0
setDelegateCtlc :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
Delegate handling of Ctrl-C to the child. For more information,
 see delegate_ctlc.
Default: False
Since: typed-process-0.1.0.0
setDetachConsole :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
setCreateNewConsole :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
setNewSession :: Bool -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
Set a new session with the POSIX setsid syscall, does nothing
 on non-POSIX. See new_session.
Default: False
Since: typed-process-0.1.0.0
setChildGroup :: GroupID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
Set the child process's group ID with the POSIX setgid syscall,
 does nothing on non-POSIX. See child_group.
Default: False
Since: typed-process-0.1.0.0
setChildUser :: UserID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr #
Set the child process's user ID with the POSIX setuid syscall,
 does nothing on non-POSIX. See child_user.
Default: False
Since: typed-process-0.1.0.0
mkStreamSpec :: StdStream -> (ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a #
Create a new StreamSpec from the given StdStream and a
 helper function. This function:
- Takes as input the raw Maybe Handlereturned by thecreateProcessfunction. This will be determined by theStdStreamargument.
- Returns the actual stream value a, as well as a cleanup
- function to be run when calling stopProcess.
Since: typed-process-0.1.0.0
inherit :: StreamSpec anyStreamType () #
A stream spec which simply inherits the stream of the parent process.
Since: typed-process-0.1.0.0
closed :: StreamSpec anyStreamType () #
A stream spec which will close the stream for the child process.
 You usually do not want to use this, as it will leave the
 corresponding file descriptor unassigned and hence available for
 re-use in the child process.  Prefer nullStream unless you're
 certain you want this behavior.
Since: typed-process-0.1.0.0
byteStringInput :: ByteString -> StreamSpec STInput () #
An input stream spec which sets the input to the given
 ByteString. A separate thread will be forked to write the
 contents to the child process.
Since: typed-process-0.1.0.0
byteStringOutput :: StreamSpec STOutput (STM ByteString) #
Capture the output of a process in a ByteString.
This function will fork a separate thread to consume all input from
 the process, and will only make the results available when the
 underlying Handle is closed. As this is provided as an STM
 action, you can either check if the result is available, or block
 until it's ready.
In the event of any exception occurring when reading from the
 Handle, the STM action will throw a
 ByteStringOutputException.
Since: typed-process-0.1.0.0
createPipe :: StreamSpec anyStreamType Handle #
Create a new pipe between this process and the child, and return
 a Handle to communicate with the child.
Since: typed-process-0.1.0.0
useHandleOpen :: Handle -> StreamSpec anyStreamType () #
Use the provided Handle for the child process, and when the
 process exits, do not close it. This is useful if, for example,
 you want to have multiple processes write to the same log file
 sequentially.
Since: typed-process-0.1.0.0
useHandleClose :: Handle -> StreamSpec anyStreamType () #
Use the provided Handle for the child process, and when the
 process exits, close it. If you have no reason to keep the Handle
 open, you should use this over useHandleOpen.
Since: typed-process-0.1.0.0
startProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m (Process stdin stdout stderr) #
Launch a process based on the given ProcessConfig. You should
 ensure that you close stopProcess on the result. It's usually
 better to use one of the functions in this module which ensures
 stopProcess is called, such as withProcess.
Since: typed-process-0.1.0.0
stopProcess :: MonadIO m => Process stdin stdout stderr -> m () #
Close a process and release any resources acquired. This will
 ensure terminateProcess is called, wait for the process to
 actually exit, and then close out resources allocated for the
 streams. In the event of any cleanup exceptions being thrown this
 will throw an exception.
Since: typed-process-0.1.0.0
readProcess :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ExitCode, ByteString, ByteString) #
Run a process, capture its standard output and error as a
 ByteString, wait for it to complete, and then return its exit
 code, output, and error.
Note that any previously used setStdout or setStderr will be
 overridden.
Since: typed-process-0.1.0.0
readProcess_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ByteString, ByteString) #
Same as readProcess, but instead of returning the ExitCode,
 checks it with checkExitCode.
Exceptions thrown by this function will include stdout and stderr.
Since: typed-process-0.1.0.0
runProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m ExitCode #
Run the given process, wait for it to exit, and returns its
 ExitCode.
Since: typed-process-0.1.0.0
runProcess_ :: MonadIO m => ProcessConfig stdin stdout stderr -> m () #
Same as runProcess, but instead of returning the
 ExitCode, checks it with checkExitCode.
Since: typed-process-0.1.0.0
readProcessStdout :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m (ExitCode, ByteString) #
Same as readProcess, but only read the stdout of the process. Original settings for stderr remain.
Since: typed-process-0.2.1.0
readProcessStdout_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ByteString #
Same as readProcessStdout, but instead of returning the
 ExitCode, checks it with checkExitCode.
Exceptions thrown by this function will include stdout.
Since: typed-process-0.2.1.0
readProcessStderr :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m (ExitCode, ByteString) #
Same as readProcess, but only read the stderr of the process.
 Original settings for stdout remain.
Since: typed-process-0.2.1.0
readProcessStderr_ :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m ByteString #
Same as readProcessStderr, but instead of returning the
 ExitCode, checks it with checkExitCode.
Exceptions thrown by this function will include stderr.
Since: typed-process-0.2.1.0
waitExitCode :: MonadIO m => Process stdin stdout stderr -> m ExitCode #
Wait for the process to exit and then return its ExitCode.
Since: typed-process-0.1.0.0
waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode #
Same as waitExitCode, but in STM.
Since: typed-process-0.1.0.0
getExitCode :: MonadIO m => Process stdin stdout stderr -> m (Maybe ExitCode) #
Check if a process has exited and, if so, return its ExitCode.
Since: typed-process-0.1.0.0
getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode) #
Same as getExitCode, but in STM.
Since: typed-process-0.1.0.0
checkExitCode :: MonadIO m => Process stdin stdout stderr -> m () #
Wait for a process to exit, and ensure that it exited
 successfully. If not, throws an ExitCodeException.
Exceptions thrown by this function will not include stdout or stderr (This prevents unbounded memory usage from reading them into memory).
 However, some callers such as readProcess_ catch the exception, add the stdout and stderr, and rethrow.
Since: typed-process-0.1.0.0
checkExitCodeSTM :: Process stdin stdout stderr -> STM () #
Same as checkExitCode, but in STM.
Since: typed-process-0.1.0.0
getStdin :: Process stdin stdout stderr -> stdin #
Get the child's standard input stream value.
Since: typed-process-0.1.0.0
getStdout :: Process stdin stdout stderr -> stdout #
Get the child's standard output stream value.
Since: typed-process-0.1.0.0
getStderr :: Process stdin stdout stderr -> stderr #
Get the child's standard error stream value.
Since: typed-process-0.1.0.0
data ExitCodeException #
Exception thrown by checkExitCode in the event of a non-success
 exit code. Note that checkExitCode is called by other functions
 as well, like runProcess_ or readProcess_.
Note that several functions that throw an ExitCodeException intentionally do not populate eceStdout or eceStderr.
 This prevents unbounded memory usage for large stdout and stderrs.
Since: typed-process-0.1.0.0
Constructors
| ExitCodeException | |
| Fields 
 | |
Instances
| Show ExitCodeException | |
| Defined in System.Process.Typed Methods showsPrec :: Int -> ExitCodeException -> ShowS # show :: ExitCodeException -> String # showList :: [ExitCodeException] -> ShowS # | |
| Exception ExitCodeException | |
| Defined in System.Process.Typed Methods toException :: ExitCodeException -> SomeException # | |
data ByteStringOutputException #
Wrapper for when an exception is thrown when reading from a child
 process, used by byteStringOutput.
Since: typed-process-0.1.0.0
Constructors
| ByteStringOutputException SomeException (ProcessConfig () () ()) | 
Instances
| Show ByteStringOutputException | |
| Defined in System.Process.Typed Methods showsPrec :: Int -> ByteStringOutputException -> ShowS # show :: ByteStringOutputException -> String # showList :: [ByteStringOutputException] -> ShowS # | |
| Exception ByteStringOutputException | |
| Defined in System.Process.Typed | |
unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle #
Take ProcessHandle out of the Process.
 This method is needed in cases one need to use low level functions
 from the process package. Use cases for this method are:
- Send a special signal to the process.
- Terminate the process group instead of terminating single process.
- Use platform specific API on the underlying process.
This method is considered unsafe because the actions it performs on
 the underlying process may overlap with the functionality that
 typed-process provides. For example the user should not call
 waitForProcess on the process handle as eiter
 waitForProcess or stopProcess will lock.
 Additionally, even if process was terminated by the
 terminateProcess or by sending signal,
 stopProcess should be called either way in order to cleanup resources
 allocated by the typed-process.
Since: typed-process-0.1.1