ContentsIndex
Win32RunProcess
Portability win32
Stability provisional
Maintainer daan@cs.uu.nl
Contents
Process control
Pipes
Data types (IOModeEx)
Description
High level primitives for process spawning on windows.
Synopsis
runProcess :: FilePath -> [String] -> Maybe [(String, String)] -> Maybe FilePath -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ()
runProcessEx :: Bool -> FilePath -> [String] -> Maybe [(String, String)] -> Maybe FilePath -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO Int
createPipe :: IO (Handle, Handle)
createPipeEx :: IOModeEx -> IO (Handle, Handle)
Process control
runProcess
:: FilePath Command
-> [String] Arguments
-> Maybe [(String, String)] Environment (Nothing -> Inherited)
-> Maybe FilePath Working directory (Nothing -> inherited)
-> Maybe Handle stdin (Nothing -> inherited)
-> Maybe Handle stdout (Nothing -> inherited)
-> Maybe Handle stderr (Nothing -> inherited)
-> IO ()

(runProcess cmd args env workdir in out err) runs a command cmd. It searches the application along the current directory, the windows system directories and finally the current PATH. The command is run with the arguments args. The child process runs concurrently with the parent process and a call to runProcess returns immediately.

If the environment env is (Just pairs), the command is executed with the environment specified by pairs of variables and values; otherwise, the command is executed with the current environment.

If workdir is (Just dir), the command is executed with working directory dir and otherwise, the command is executed in the current working directory.

If {in,out,err} is (Just handle), the command is executed with std{in,out,err} attached to the specified handle; otherwise, std{in,out,err} is left unchanged.

 runProcess = runProcessEx False
runProcessEx
:: Bool Wait for termination?
-> FilePath Command
-> [String] Arguments
-> Maybe [(String, String)] Environment (Nothing -> Inherited)
-> Maybe FilePath Working directory (Nothing -> inherited)
-> Maybe Handle stdin (Nothing -> inherited)
-> Maybe Handle stdout (Nothing -> inherited)
-> Maybe Handle stderr (Nothing -> inherited)
-> IO Int The exit code (or 0 if wait is False)

(runProcessEx wait cmd args env workdir in out err) runs a command cmd. It searches the application along the current directory, the windows system directories and finally the current PATH. The command is run with the arguments args. If wait is True, the current process is suspended until the child terminates, otherwise they are run concurrently.

If the environment env is (Just pairs), the command is executed with the environment specified by pairs of variables and values; otherwise, the command is executed with the current environment.

If workdir is (Just dir), the command is executed with working directory dir and otherwise, the command is executed in the current working directory.

If {in,out,err} is (Just handle), the command is executed with std{in,out,err} attached to the specified handle; otherwise, std{in,out,err} is left unchanged.

If wait is True, the call to runProcessEx returns after the child process has terminated with the exit code of the process. If wait is false, the call to runProcessEx returns immediately with an exit code of 0.

Here is a short example of running a command cmd that gets its input from a file foo. The process is run synchronously.

     do{ input    <- openFile "foo" ReadMode
       ; exitcode <- runProcessEx True "cmd" [] Nothing Nothing (Just input) Nothing Nothing
       ; hClose input
       ; ...
Pipes
createPipe :: IO (Handle, Handle)

(createPipe) creates an anonymous pipe and returns a pair of handles, the first for reading and the second for writing. Both pipe ends can be inherited by a child process.

 createPipe  = createPipeEx (BinaryMode AppendMode)   
createPipeEx :: IOModeEx -> IO (Handle, Handle)

(createPipeEx modeEx) creates an anonymous pipe and returns a pair of handles, the first for reading and the second for writing. The pipe mode modeEx can be:

  • TextMode mode -- the pipe is opened in text mode.

  • BinaryMode mode -- the pipe is opened in binary mode.

The mode determines if child processes can inherit the pipe handles:

  • ReadMode -- The read handle of the pipe is private to this process.

  • WriteMode -- The write handle of the pipe is private to this process.

  • ReadWriteMode -- Both handles are private to this process.

  • AppendMode -- Both handles are available (inheritable) to child processes. This mode can be used to append (|) two seperate child processes.

If a broken pipe is read, an end-of-file (EOF) exception is raised. If a broken pipe is written to, an invalid argument exception is raised (InvalidArgument).

Here is a short example that redirects stdin, stdout and stderr of a spawned child process to private handles in the parent process.

 spawn :: String -> IO (Handle,Handle,Handle)
 spawn command 
   = do{ (stdinRead,stdinWrite)   <- createPipeEx (TextMode WriteMode)
       ; (stdoutRead,stdoutWrite) <- createPipeEx (TextMode ReadMode)
       ; (stderrRead,stderrWrite) <- createPipeEx (TextMode ReadMode)
       ; runProcess command [] Nothing Nothing (Just stdinRead) (Just stdoutWrite) (Just stderrWrite)
       ; hClose stdinRead
       ; hClose stdoutWrite
       ; hClose stderrWrite
       ; return (stdinWrite,stdoutRead,stderrRead)
       }
Data types (IOModeEx)
Produced by Haddock version 0.4