Safe Haskell | None |
---|---|
Language | Haskell2010 |
The simplest way to get started with this API is to turn on
OverloadedStrings
and call
runProcess
. The following will
write the contents of
/home
to
stdout
and then print the exit
code (on a UNIX system).
{-# LANGUAGE OverloadedStrings #-}
runProcess
"ls -l /home" >>= print
Please see the README.md file for more examples of using this API.
Synopsis
- data ProcessConfig stdin stdout stderr
- data StreamSpec (streamType :: StreamType ) a
- data StreamType
- data Process stdin stdout stderr
- proc :: FilePath -> [ String ] -> ProcessConfig () () ()
- shell :: String -> ProcessConfig () () ()
- 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
- setWorkingDir :: FilePath -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setWorkingDirInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setEnv :: [( String , String )] -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setEnvInherit :: ProcessConfig stdin stdout stderr -> 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
- setChildGroupInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildUser :: UserID -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- setChildUserInherit :: ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout stderr
- inherit :: StreamSpec anyStreamType ()
- nullStream :: 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 ()
- mkStreamSpec :: StdStream -> ( ProcessConfig () () () -> Maybe Handle -> IO (a, IO ())) -> StreamSpec streamType a
- mkPipeStreamSpec :: ( ProcessConfig () () () -> Handle -> IO (a, IO ())) -> StreamSpec streamType a
- runProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m ExitCode
- readProcess :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m ( ExitCode , ByteString , ByteString )
- readProcessStdout :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ( ExitCode , ByteString )
- readProcessStderr :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m ( ExitCode , ByteString )
- readProcessInterleaved :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m ( ExitCode , ByteString )
- 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
- startProcess :: MonadIO m => ProcessConfig stdin stdout stderr -> m ( Process stdin stdout stderr)
- stopProcess :: MonadIO m => Process stdin stdout stderr -> m ()
- runProcess_ :: MonadIO m => ProcessConfig stdin stdout stderr -> m ()
- readProcess_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m ( ByteString , ByteString )
- readProcessStdout_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ByteString
- readProcessStderr_ :: MonadIO m => ProcessConfig stdin stdout stderrIgnored -> m ByteString
- readProcessInterleaved_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m ByteString
- 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
- 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 () () ())
- data ExitCode
-
data
StdStream
- = Inherit
- | UseHandle Handle
- | CreatePipe
- | NoStream
- unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle
- 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
Types
data ProcessConfig stdin stdout stderr Source #
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
proc
smart constructor, which takes a command name and a list of arguments. -
With the
shell
smart constructor, which takes a shell string -
With the
IsString
instance 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.
Once you have a
ProcessConfig
you can launch a process from it
using the functions in the section
Launch a
process
.
Since: 0.1.0.0
Instances
Show ( ProcessConfig stdin stdout stderr) Source # | |
Defined in System.Process.Typed |
|
(stdin ~ (), stdout ~ (), stderr ~ ()) => IsString ( ProcessConfig stdin stdout stderr) Source # | |
Defined in System.Process.Typed fromString :: String -> ProcessConfig stdin stdout stderr Source # |
data StreamSpec (streamType :: StreamType ) a Source #
A specification for how to create one of the three standard child
streams,
stdin
,
stdout
and
stderr
. A
StreamSpec
can be
thought of as containing
-
A type safe version of
StdStream
from System.Process . This determines whether the stream should be inherited from the parent process, piped to or from aHandle
, etc. -
A means of accessing the stream as a value of type
a
- A cleanup action which will be run on the stream once the process terminates
To create a
StreamSpec
see the section
Stream
specs
.
Since: 0.1.0.0
Instances
Functor ( StreamSpec streamType) Source # | |
Defined in System.Process.Typed fmap :: (a -> b) -> StreamSpec streamType a -> StreamSpec streamType b Source # (<$) :: a -> StreamSpec streamType b -> StreamSpec streamType a Source # |
|
(streamType ~ ' STInput , res ~ ()) => IsString ( StreamSpec streamType res) Source # |
This instance uses
Since: 0.1.0.0 |
Defined in System.Process.Typed fromString :: String -> StreamSpec streamType res Source # |
data StreamType Source #
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: 0.1.0.0
data Process stdin stdout stderr Source #
A running process. The three type parameters provide the type of the standard input, standard output, and standard error streams.
To interact with a
Process
use the functions from the section
Interact with a process
.
Since: 0.1.0.0
ProcessConfig
Smart constructors
proc :: FilePath -> [ String ] -> ProcessConfig () () () Source #
Create a
ProcessConfig
from the given command and arguments.
Since: 0.1.0.0
shell :: String -> ProcessConfig () () () Source #
Create a
ProcessConfig
from the given shell command.
Since: 0.1.0.0
Setters
:: StreamSpec ' STInput stdin | |
-> ProcessConfig stdin0 stdout stderr | |
-> ProcessConfig stdin stdout stderr |
:: StreamSpec ' STOutput stdout | |
-> ProcessConfig stdin stdout0 stderr | |
-> ProcessConfig stdin stdout stderr |
:: StreamSpec ' STOutput stderr | |
-> ProcessConfig stdin stdout stderr0 | |
-> ProcessConfig stdin stdout stderr |
:: FilePath | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Set the working directory of the child process.
Default: current process's working directory.
Since: 0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the working directory from the parent process.
Since: 0.2.2.0
:: [( String , String )] | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Set the environment variables of the child process.
Default: current process's environment.
Since: 0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the environment variables from the parent process.
Since: 0.2.2.0
:: 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: 0.1.0.0
:: Bool | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Should we create a new process group?
Default: False
Since: 0.1.0.0
:: 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: 0.1.0.0
:: Bool | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
:: Bool | |
-> ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
:: 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: 0.1.0.0
:: 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: 0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the group from the parent process.
Since: 0.2.2.0
:: 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: 0.1.0.0
:: ProcessConfig stdin stdout stderr | |
-> ProcessConfig stdin stdout stderr |
Inherit the user from the parent process.
Since: 0.2.2.0
Stream specs
Built-in stream specs
inherit :: StreamSpec anyStreamType () Source #
A stream spec which simply inherits the stream of the parent process.
Since: 0.1.0.0
nullStream :: StreamSpec anyStreamType () Source #
A stream spec which is empty when used for for input and discards output. Note this requires your platform's null device to be available when the process is started.
Since: 0.2.5.0
closed :: StreamSpec anyStreamType () Source #
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: 0.1.0.0
byteStringInput :: ByteString -> StreamSpec ' STInput () Source #
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: 0.1.0.0
byteStringOutput :: StreamSpec ' STOutput ( STM ByteString ) Source #
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: 0.1.0.0
createPipe :: StreamSpec anyStreamType Handle Source #
Create a new pipe between this process and the child, and return
a
Handle
to communicate with the child.
Since: 0.1.0.0
useHandleOpen :: Handle -> StreamSpec anyStreamType () Source #
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: 0.1.0.0
useHandleClose :: Handle -> StreamSpec anyStreamType () Source #
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: 0.1.0.0
Create your own stream spec
:: 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 Handle
returned by thecreateProcess
function. The handle will beJust
Handle
if theStdStream
argument isCreatePipe
andNothing
otherwise. SeecreateProcess
for more details. -
Returns the actual stream value
a
, as well as a cleanup function to be run when callingstopProcess
.
If making a
StreamSpec
with
CreatePipe
, prefer
mkPipeStreamSpec
,
which encodes the invariant that a
Handle
is created.
Since: 0.1.0.0
:: ( ProcessConfig () () () -> Handle -> IO (a, IO ())) | |
-> StreamSpec streamType a |
Create a new
CreatePipe
StreamSpec
from the given function.
This function:
-
Takes as input the
Handle
returned by thecreateProcess
function. SeecreateProcess
for more details. -
Returns the actual stream value
a
, as well as a cleanup function to be run when callingstopProcess
.
Since: 0.2.10.0
Launch a process
:: MonadIO m | |
=> ProcessConfig stdin stdout stderr | |
-> m ExitCode |
Run the given process, wait for it to exit, and returns its
ExitCode
.
Since: 0.1.0.0
:: 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: 0.1.0.0
:: 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: 0.2.1.0
:: 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: 0.2.1.0
readProcessInterleaved Source #
:: MonadIO m | |
=> ProcessConfig stdin stdoutIgnored stderrIgnored | |
-> m ( ExitCode , ByteString ) |
Same as
readProcess
, but interleaves stderr with stdout.
Motivation: Use this function if you need stdout interleaved with stderr output (e.g. from an HTTP server) in order to debug failures.
Since: 0.2.4.0
:: MonadUnliftIO m | |
=> ProcessConfig stdin stdout stderr | |
-> ( Process stdin stdout stderr -> m a) | |
-> m a |
Uses the bracket pattern to call
startProcess
. Unlike
withProcessTerm
, this function will wait for the child process to
exit, and only kill it with
stopProcess
in the event that the
inner function throws an exception.
To interact with a
Process
use the functions from the section
Interact with a process
.
Since: 0.2.5.0
:: MonadUnliftIO m | |
=> ProcessConfig stdin stdout stderr | |
-> ( Process stdin stdout stderr -> m a) | |
-> m a |
Uses the bracket pattern to call
startProcess
and ensures that
stopProcess
is called.
This function is usually
not
what you want. You're likely better
off using
withProcessWait
. See
https://github.com/fpco/typed-process/issues/25
.
Since: 0.2.5.0
:: MonadIO m | |
=> ProcessConfig stdin stdout stderr | |
-> m ( Process stdin stdout stderr) |
Launch a process based on the given
ProcessConfig
. You should
ensure that you call
stopProcess
on the result. It's usually
better to use one of the functions in this module which ensures
stopProcess
is called, such as
withProcessWait
.
Since: 0.1.0.0
stopProcess :: MonadIO m => Process stdin stdout stderr -> m () Source #
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: 0.1.0.0
Exception-throwing functions
The functions ending in underbar (
_
) are the same as
their counterparts without underbar but instead of returning
an
ExitCode
they throw
ExitCodeException
on failure.
:: MonadIO m | |
=> ProcessConfig stdin stdout stderr | |
-> m () |
Same as
runProcess
, but instead of returning the
ExitCode
, checks it with
checkExitCode
.
Since: 0.1.0.0
:: 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: 0.1.0.0
:: 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: 0.2.1.0
:: 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: 0.2.1.0
readProcessInterleaved_ Source #
:: MonadIO m | |
=> ProcessConfig stdin stdoutIgnored stderrIgnored | |
-> m ByteString |
Same as
readProcessInterleaved
, but instead of returning the
ExitCode
,
checks it with
checkExitCode
.
Exceptions thrown by this function will include stdout.
Since: 0.2.4.0
:: MonadUnliftIO m | |
=> ProcessConfig stdin stdout stderr | |
-> ( Process stdin stdout stderr -> m a) | |
-> m a |
Same as
withProcessWait
, but also calls
checkExitCode
Since: 0.2.5.0
:: MonadUnliftIO m | |
=> ProcessConfig stdin stdout stderr | |
-> ( Process stdin stdout stderr -> m a) | |
-> m a |
Same as
withProcessTerm
, but also calls
checkExitCode
To interact with a
Process
use the functions from the section
Interact with a process
.
Since: 0.2.5.0
Interact with a process
Process exit code
waitExitCode :: MonadIO m => Process stdin stdout stderr -> m ExitCode Source #
Wait for the process to exit and then return its
ExitCode
.
Since: 0.1.0.0
waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode Source #
Same as
waitExitCode
, but in
STM
.
Since: 0.1.0.0
getExitCode :: MonadIO m => Process stdin stdout stderr -> m ( Maybe ExitCode ) Source #
Check if a process has exited and, if so, return its
ExitCode
.
Since: 0.1.0.0
getExitCodeSTM :: Process stdin stdout stderr -> STM ( Maybe ExitCode ) Source #
Same as
getExitCode
, but in
STM
.
Since: 0.1.0.0
checkExitCode :: MonadIO m => Process stdin stdout stderr -> m () Source #
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: 0.1.0.0
checkExitCodeSTM :: Process stdin stdout stderr -> STM () Source #
Same as
checkExitCode
, but in
STM
.
Since: 0.1.0.0
Process streams
getStdin :: Process stdin stdout stderr -> stdin Source #
Get the child's standard input stream value.
Since: 0.1.0.0
getStdout :: Process stdin stdout stderr -> stdout Source #
Get the child's standard output stream value.
Since: 0.1.0.0
getStderr :: Process stdin stdout stderr -> stderr Source #
Get the child's standard error stream value.
Since: 0.1.0.0
Exceptions
data ExitCodeException Source #
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: 0.1.0.0
ExitCodeException | |
|
Instances
Show ExitCodeException Source # | |
Defined in System.Process.Typed |
|
Exception ExitCodeException Source # | |
Defined in System.Process.Typed |
data ByteStringOutputException Source #
Wrapper for when an exception is thrown when reading from a child
process, used by
byteStringOutput
.
Since: 0.1.0.0
ByteStringOutputException SomeException ( ProcessConfig () () ()) |
Instances
Re-exports
Defines the exit codes that a program can return.
ExitSuccess |
indicates successful termination; |
ExitFailure Int |
indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system). |
Instances
Eq ExitCode | |
Ord ExitCode | |
Defined in GHC.IO.Exception |
|
Read ExitCode | |
Show ExitCode | |
Generic ExitCode | |
Exception ExitCode |
Since: base-4.1.0.0 |
Defined in GHC.IO.Exception toException :: ExitCode -> SomeException Source # fromException :: SomeException -> Maybe ExitCode Source # displayException :: ExitCode -> String Source # |
|
type Rep ExitCode | |
Defined in GHC.IO.Exception
type
Rep
ExitCode
=
D1
('
MetaData
"ExitCode" "GHC.IO.Exception" "base" '
False
) (
C1
('
MetaCons
"ExitSuccess" '
PrefixI
'
False
) (
U1
::
Type
->
Type
)
:+:
C1
('
MetaCons
"ExitFailure" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Int
)))
|
Inherit |
Inherit Handle from parent |
UseHandle Handle |
Use the supplied Handle |
CreatePipe |
Create a new pipe. The returned
|
NoStream |
Close the stream's file descriptor without
passing a Handle. On POSIX systems this may
lead to strange behavior in the child process
because attempting to read or write after the
file has been closed throws an error. This
should only be used with child processes that
don't use the file descriptor at all. If you
wish to ignore the child process's output you
should either create a pipe and drain it
manually or pass a
|
Unsafe functions
unsafeProcessHandle :: Process stdin stdout stderr -> ProcessHandle Source #
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: 0.1.1
Deprecated functions
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
Deprecated synonym for
withProcessTerm
.
Since: 0.1.0.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_
Deprecated synonym for
withProcessTerm_
.
Since: 0.1.0.0