| Copyright | (c) The University of Glasgow 2004-2008 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | experimental | 
| Portability | non-portable (requires concurrency) | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
System.Process
Contents
Description
Operations for creating and interacting with sub-processes.
Synopsis
- createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- createProcess_ :: String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- shell :: String -> CreateProcess
- proc :: FilePath -> [String] -> CreateProcess
- data CreateProcess = CreateProcess {- cmdspec :: CmdSpec
- cwd :: Maybe FilePath
- env :: Maybe [(String, String)]
- std_in :: StdStream
- std_out :: StdStream
- std_err :: StdStream
- close_fds :: Bool
- create_group :: Bool
- delegate_ctlc :: Bool
- detach_console :: Bool
- create_new_console :: Bool
- new_session :: Bool
- child_group :: Maybe GroupID
- child_user :: Maybe UserID
- use_process_jobs :: Bool
 
- data CmdSpec
- data StdStream
- data ProcessHandle
- callProcess :: FilePath -> [String] -> IO ()
- callCommand :: String -> IO ()
- spawnProcess :: FilePath -> [String] -> IO ProcessHandle
- spawnCommand :: String -> IO ProcessHandle
- readCreateProcess :: CreateProcess -> String -> IO String
- readProcess :: FilePath -> [String] -> String -> IO String
- readCreateProcessWithExitCode :: CreateProcess -> String -> IO (ExitCode, String, String)
- readProcessWithExitCode :: FilePath -> [String] -> String -> IO (ExitCode, String, String)
- withCreateProcess :: CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a
- cleanupProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO ()
- showCommandForUser :: FilePath -> [String] -> String
- type Pid = CPid
- getPid :: ProcessHandle -> IO (Maybe Pid)
- waitForProcess :: ProcessHandle -> IO ExitCode
- getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode)
- terminateProcess :: ProcessHandle -> IO ()
- interruptProcessGroupOf :: ProcessHandle -> IO ()
- createPipe :: IO (Handle, Handle)
- createPipeFd :: IO (FD, FD)
- runProcess :: FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ProcessHandle
- runCommand :: String -> IO ProcessHandle
- runInteractiveProcess :: FilePath -> [String] -> Maybe FilePath -> Maybe [(String, String)] -> IO (Handle, Handle, Handle, ProcessHandle)
- runInteractiveCommand :: String -> IO (Handle, Handle, Handle, ProcessHandle)
- system :: String -> IO ExitCode
- rawSystem :: String -> [String] -> IO ExitCode
Running sub-processes
createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
This is the most general way to spawn an external process.  The
process can be a command line to be executed by a shell or a raw command
with a list of arguments.  The stdin, stdout, and stderr streams of
the new process may individually be attached to new pipes, to existing
Handles, or just inherited from the parent (the default.)
The details of how to create the process are passed in the
CreateProcess record.  To make it easier to construct a
CreateProcess, the functions proc and shell are supplied that
fill in the fields with default values which can be overriden as
needed.
createProcess returns (mb_stdin_hdl, mb_stdout_hdl, mb_stderr_hdl, ph),
where
- if std_in==CreatePipemb_stdin_hdlwill beJust h, wherehis the write end of the pipe connected to the child process'sstdin.
- otherwise, mb_stdin_hdl == Nothing
Similarly for mb_stdout_hdl and mb_stderr_hdl.
For example, to execute a simple ls command:
r <- createProcess (proc "ls" [])
To create a pipe from which to read the output of ls:
  (_, Just hout, _, _) <-
      createProcess (proc "ls" []){ std_out = CreatePipe }To also set the directory in which to run ls:
  (_, Just hout, _, _) <-
      createProcess (proc "ls" []){ cwd = Just "/home/bob",
                                    std_out = CreatePipe }Note that Handles provided for std_in, std_out, or std_err via the
UseHandle constructor will be closed by calling this function. This is not
always the desired behavior. In cases where you would like to leave the
Handle open after spawning the child process, please use createProcess_
instead. All created Handles are initially in text mode; if you need them
to be in binary mode then use hSetBinaryMode.
Arguments
| :: String | function name (for error messages) | 
| -> CreateProcess | |
| -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) | 
This function is almost identical to
 createProcess. The only differences are:
- Handles provided via- UseHandleare not closed automatically.
- This function takes an extra Stringargument to be used in creating error messages.
- use_process_jobscan be set in CreateProcess since 1.5.0.0 in order to create an I/O completion port to monitor a process tree's progress on Windows.
The function also returns two new handles: * an I/O Completion Port handle on which events will be signaled. * a Job handle which can be used to kill all running processes.
On POSIX platforms these two new handles will always be Nothing
This function has been available from the System.Process.Internals module for some time, and is part of the System.Process module since version 1.2.1.0.
Since: 1.2.1.0
shell :: String -> CreateProcess Source #
Construct a CreateProcess record for passing to createProcess,
 representing a command to be passed to the shell.
proc :: FilePath -> [String] -> CreateProcess Source #
Construct a CreateProcess record for passing to createProcess,
 representing a raw command with arguments.
See RawCommand for precise semantics of the specified FilePath.
data CreateProcess Source #
Constructors
| CreateProcess | |
| Fields 
 | |
Instances
| Eq CreateProcess Source # | |
| Defined in System.Process.Common Methods (==) :: CreateProcess -> CreateProcess -> Bool # (/=) :: CreateProcess -> CreateProcess -> Bool # | |
| Show CreateProcess Source # | |
| Defined in System.Process.Common Methods showsPrec :: Int -> CreateProcess -> ShowS # show :: CreateProcess -> String # showList :: [CreateProcess] -> ShowS # | |
Constructors
| ShellCommand String | A command line to execute using the shell | 
| RawCommand FilePath [String] | The name of an executable with a list of arguments The  
 | 
Constructors
| 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  | 
data ProcessHandle Source #
Simpler functions for common tasks
callProcess :: FilePath -> [String] -> IO () Source #
Creates a new process to run the specified command with the given arguments, and wait for it to finish. If the command returns a non-zero exit code, an exception is raised.
If an asynchronous exception is thrown to the thread executing
 callProcess, the forked process will be terminated and
 callProcess will wait (block) until the process has been
 terminated.
Since: 1.2.0.0
callCommand :: String -> IO () Source #
Creates a new process to run the specified shell command. If the command returns a non-zero exit code, an exception is raised.
If an asynchronous exception is thrown to the thread executing
 callCommand, the forked process will be terminated and
 callCommand will wait (block) until the process has been
 terminated.
Since: 1.2.0.0
spawnProcess :: FilePath -> [String] -> IO ProcessHandle Source #
Creates a new process to run the specified raw command with the given
 arguments. It does not wait for the program to finish, but returns the
 ProcessHandle.
Since: 1.2.0.0
spawnCommand :: String -> IO ProcessHandle Source #
Creates a new process to run the specified shell command.
 It does not wait for the program to finish, but returns the ProcessHandle.
Since: 1.2.0.0
Arguments
| :: CreateProcess | |
| -> String | standard input | 
| -> IO String | stdout | 
readCreateProcess works exactly like readProcess except that it
 lets you pass CreateProcess giving better flexibility.
 > readCreateProcess ((shell "pwd") { cwd = Just "/etc/" }) ""
 "/etc\n"Note that Handles provided for std_in or std_out via the CreateProcess
 record will be ignored.
Since: 1.2.3.0
Arguments
| :: FilePath | Filename of the executable (see  | 
| -> [String] | any arguments | 
| -> String | standard input | 
| -> IO String | stdout | 
readProcess forks an external process, reads its standard output
 strictly, blocking until the process terminates, and returns the output
 string. The external process inherits the standard error.
If an asynchronous exception is thrown to the thread executing
 readProcess, the forked process will be terminated and readProcess will
 wait (block) until the process has been terminated.
Output is returned strictly, so this is not suitable for launching processes that require interaction over the standard file streams.
This function throws an IOError if the process ExitCode is
 anything other than ExitSuccess. If instead you want to get the
 ExitCode then use readProcessWithExitCode.
Users of this function should compile with -threaded if they
 want other Haskell threads to keep running while waiting on
 the result of readProcess.
> readProcess "date" [] [] "Thu Feb 7 10:03:39 PST 2008\n"
The arguments are:
- The command to run, which must be in the $PATH, or an absolute or relative path
- A list of separate command line arguments to the program
- A string to pass on standard input to the forked process.
readCreateProcessWithExitCode Source #
Arguments
| :: CreateProcess | |
| -> String | standard input | 
| -> IO (ExitCode, String, String) | exitcode, stdout, stderr | 
readCreateProcessWithExitCode works exactly like readProcessWithExitCode except that it
 lets you pass CreateProcess giving better flexibility.
Note that Handles provided for std_in, std_out, or std_err via the CreateProcess
 record will be ignored.
Since: 1.2.3.0
readProcessWithExitCode Source #
Arguments
| :: FilePath | Filename of the executable (see  | 
| -> [String] | any arguments | 
| -> String | standard input | 
| -> IO (ExitCode, String, String) | exitcode, stdout, stderr | 
readProcessWithExitCode is like readProcess but with two differences:
- it returns the ExitCodeof the process, and does not throw any exception if the code is notExitSuccess.
- it reads and returns the output from process' standard error handle, rather than the process inheriting the standard error handle.
On Unix systems, see waitForProcess for the meaning of exit codes
 when the process died as the result of a signal.
withCreateProcess :: CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a Source #
A bracket-style resource handler for createProcess.
Does automatic cleanup when the action finishes. If there is an exception
 in the body then it ensures that the process gets terminated and any
 CreatePipe Handles are closed. In particular this means that if the
 Haskell thread is killed (e.g. killThread), that the external process is
 also terminated.
e.g.
withCreateProcess (proc cmd args) { ... }  $ \stdin stdout stderr ph -> do
  ...Since: 1.4.3.0
cleanupProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO () Source #
Cleans up the process.
This function is meant to be invoked from any application level cleanup 
 handler. It terminates the process, and closes any CreatePipe handles.
Since: 1.6.4.0
Related utilities
showCommandForUser :: FilePath -> [String] -> String Source #
Given a program p and arguments args,
   showCommandForUser p args returns a string suitable for pasting
   into /bin/sh (on Unix systems) or CMD.EXE (on Windows).
The platform specific type for a process identifier.
This is always an integral type. Width and signedness are platform specific.
Since: 1.6.3.0
getPid :: ProcessHandle -> IO (Maybe Pid) Source #
Returns the PID (process ID) of a subprocess.
Nothing is returned if the handle was already closed. Otherwise a
 PID is returned that remains valid as long as the handle is open.
 The operating system may reuse the PID as soon as the last handle to
 the process is closed.
Since: 1.6.3.0
Control-C handling on Unix
When running an interactive console process (such as a shell, console-based
 text editor or ghci), we typically want that process to be allowed to handle
 Ctl-C keyboard interrupts how it sees fit. For example, while most programs
 simply quit on a Ctl-C, some handle it specially. To allow this to happen,
 use the delegate_ctlc = TrueCreateProcess options.
The gory details:
By default Ctl-C will generate a SIGINT signal, causing a UserInterrupt
 exception to be sent to the main Haskell thread of your program, which if
 not specially handled will terminate the program. Normally, this is exactly
 what is wanted: an orderly shutdown of the program in response to Ctl-C.
Of course when running another interactive program in the console then we
 want to let that program handle Ctl-C. Under Unix however, Ctl-C sends
 SIGINT to every process using the console. The standard solution is that
 while running an interactive program, ignore SIGINT in the parent, and let
 it be handled in the child process. If that process then terminates due to
 the SIGINT signal, then at that point treat it as if we had recieved the
 SIGINT ourselves and begin an orderly shutdown.
This behaviour is implemented by createProcess (and
 waitForProcess / getProcessExitCode) when the delegate_ctlc = TrueSIGINT signal will be ignored until
 waitForProcess returns (or getProcessExitCode returns a non-Nothing
 result), so it becomes especially important to use waitForProcess for every
 processes created.
In addition, in delegate_ctlc mode, waitForProcess and
 getProcessExitCode will throw a UserInterrupt exception if the process
 terminated with ExitFailure (-SIGINT)UserInterrupt exception is thrown
 synchronously in the thread that calls waitForProcess, whereas normally
 SIGINT causes the exception to be thrown asynchronously to the main
 thread.
For even more detail on this topic, see "Proper handling of SIGINT/SIGQUIT".
Process completion
Notes about exec on Windows
Note that processes which use the POSIX exec system call (e.g. gcc)
 require special care on Windows. Specifically, the msvcrt C runtime used
 frequently on Windows emulates exec in a non-POSIX compliant manner, where
 the caller will be terminated (with exit code 0) and execution will continue
 in a new process. As a result, on Windows it will appear as though a child
 process which has called exec has terminated despite the fact that the
 process would still be running on a POSIX-compliant platform.
Since many programs do use exec, the process library exposes the
 use_process_jobs flag to make it possible to reliably detect when such a
 process completes. When this flag is set a ProcessHandle will not be
 deemed to be "finished" until all processes spawned by it have
 terminated (except those spawned by the child with the
 CREATE_BREAKAWAY_FROM_JOB CreateProcess flag).
Note, however, that, because of platform limitations, the exit code returned
 by waitForProcess and getProcessExitCode cannot not be relied upon when
 the child uses exec, even when use_process_jobs is used. Specifically,
 these functions will return the exit code of the *original child* (which
 always exits with code 0, since it called exec), not the exit code of the
 process which carried on with execution after exec. This is different from
 the behavior prescribed by POSIX but is the best approximation that can be
 realised under the restrictions of the Windows process model.
waitForProcess :: ProcessHandle -> IO ExitCode Source #
Waits for the specified process to terminate, and returns its exit code.
GHC Note: in order to call waitForProcess without blocking all the
other threads in the system, you must compile the program with
-threaded.
(Since: 1.2.0.0) On Unix systems, a negative value ExitFailure -signumsignum.
The signal numbers are platform-specific, so to test for a specific signal use
the constants provided by System.Posix.Signals in the unix package.
Note: core dumps are not reported, use System.Posix.Process if you need this
detail.
getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode) Source #
This is a non-blocking version of waitForProcess.  If the process is
still running, Nothing is returned.  If the process has exited, then
Just ee is the exit code of the process.
On Unix systems, see waitForProcess for the meaning of exit codes
when the process died as the result of a signal.
terminateProcess :: ProcessHandle -> IO () Source #
Attempts to terminate the specified process.  This function should
 not be used under normal circumstances - no guarantees are given regarding
 how cleanly the process is terminated.  To check whether the process
 has indeed terminated, use getProcessExitCode.
On Unix systems, terminateProcess sends the process the SIGTERM signal.
 On Windows systems, if use_process_jobs is True then the Win32 TerminateJobObject
 function is called to kill all processes associated with the job and passing the
 exit code of 1 to each of them. Otherwise if use_process_jobs is False then the
 Win32 TerminateProcess function is called, passing an exit code of 1.
Note: on Windows, if the process was a shell command created by
 createProcess with shell, or created by runCommand or
 runInteractiveCommand, then terminateProcess will only
 terminate the shell, not the command itself.  On Unix systems, both
 processes are in a process group and will be terminated together.
interruptProcessGroupOf Source #
Arguments
| :: ProcessHandle | A process in the process group | 
| -> IO () | 
Sends an interrupt signal to the process group of the given process.
On Unix systems, it sends the group the SIGINT signal.
On Windows systems, it generates a CTRL_BREAK_EVENT and will only work for
 processes created using createProcess and setting the create_group flag
Interprocess communication
createPipe :: IO (Handle, Handle) Source #
Create a pipe for interprocess communication and return a
 (readEnd, writeEnd) Handle pair.
Since: 1.2.1.0
createPipeFd :: IO (FD, FD) Source #
Create a pipe for interprocess communication and return a
 (readEnd, writeEnd) FD pair.
Since: 1.4.2.0
Old deprecated functions
These functions pre-date createProcess which is much more
 flexible.
Arguments
| :: FilePath | Filename of the executable (see  | 
| -> [String] | Arguments to pass to the executable | 
| -> Maybe FilePath | Optional path to the working directory | 
| -> Maybe [(String, String)] | Optional environment (otherwise inherit) | 
| -> Maybe Handle | Handle to use for  | 
| -> Maybe Handle | Handle to use for  | 
| -> Maybe Handle | Handle to use for  | 
| -> IO ProcessHandle | 
Runs a raw command, optionally specifying Handles from which to
     take the stdin, stdout and stderr channels for the new
     process (otherwise these handles are inherited from the current
     process).
Any Handles passed to runProcess are placed immediately in the
     closed state.
Note: consider using the more general createProcess instead of
     runProcess.
runCommand :: String -> IO ProcessHandle Source #
Runs a command using the shell.
runInteractiveProcess Source #
Arguments
| :: FilePath | Filename of the executable (see  | 
| -> [String] | Arguments to pass to the executable | 
| -> Maybe FilePath | Optional path to the working directory | 
| -> Maybe [(String, String)] | Optional environment (otherwise inherit) | 
| -> IO (Handle, Handle, Handle, ProcessHandle) | 
Runs a raw command, and returns Handles that may be used to communicate
     with the process via its stdin, stdout and stderr respectively.
For example, to start a process and feed a string to its stdin:
(inp,out,err,pid) <- runInteractiveProcess "..." forkIO (hPutStr inp str)
runInteractiveCommand :: String -> IO (Handle, Handle, Handle, ProcessHandle) Source #
Runs a command using the shell, and returns Handles that may
     be used to communicate with the process via its stdin, stdout,
     and stderr respectively.
system :: String -> IO ExitCode Source #
Computation system cmd returns the exit code produced when the
operating system runs the shell command cmd.
This computation may fail with one of the following
IOErrorType exceptions:
- PermissionDenied
- The process has insufficient privileges to perform the operation.
- ResourceExhausted
- Insufficient resources are available to perform the operation.
- UnsupportedOperation
- The implementation does not support system calls.
On Windows, system passes the command to the Windows command
interpreter (CMD.EXE or COMMAND.COM), hence Unixy shell tricks
will not work.
On Unix systems, see waitForProcess for the meaning of exit codes
when the process died as the result of a signal.
rawSystem :: String -> [String] -> IO ExitCode Source #
The computation rawSystem cmd argscmd in such a way that it receives as arguments the args strings
exactly as given, with no funny escaping or shell meta-syntax expansion.
It will therefore behave more portably between operating systems than system.
The return codes and possible failures are the same as for system.