{-# LANGUAGE CPP, ForeignFunctionInterface #-} #if __GLASGOW_HASKELL__ >= 709 {-# LANGUAGE Safe #-} #else {-# LANGUAGE Trustworthy #-} #endif {-# LANGUAGE InterruptibleFFI #-} #include <ghcplatform.h> #if defined(javascript_HOST_ARCH) {-# LANGUAGE JavaScriptFFI #-} #endif ------------------------------------------------------------------------------- |-- Module : System.Process-- 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)---- Operations for creating and interacting with sub-processes.--------------------------------------------------------------------------------- TODO:-- * Flag to control whether exiting the parent also kills the child.moduleSystem.Process(-- * Running sub-processescreateProcess ,createProcess_ ,shell ,proc ,CreateProcess (..),CmdSpec (..),StdStream (..),ProcessHandle ,-- ** Simpler functions for common taskscallProcess ,callCommand ,spawnProcess ,spawnCommand ,readCreateProcess ,readProcess ,readCreateProcessWithExitCode ,readProcessWithExitCode ,withCreateProcess ,cleanupProcess ,-- ** Related utilitiesshowCommandForUser ,Pid ,getPid ,getCurrentPid ,-- ** Control-C handling on Unix-- $ctlc-handling-- * Process completion-- ** Notes about @exec@ on Windows-- $exec-on-windowswaitForProcess ,getProcessExitCode ,terminateProcess ,interruptProcessGroupOf ,-- * Interprocess communicationcreatePipe ,createPipeFd ,-- * Old deprecated functions-- | These functions pre-date 'createProcess' which is much more-- flexible.runProcess ,runCommand ,runInteractiveProcess ,runInteractiveCommand ,system ,rawSystem ,)whereimportPreludehiding(mapM)importSystem.Process.Internals importControl.ConcurrentimportControl.DeepSeq(rnf)importControl.Exception( #if !defined(javascript_HOST_ARCH) allowInterrupt, #endif bracket)importqualifiedControl.ExceptionasCimportControl.MonadimportData.MaybeimportForeignimportForeign.CimportSystem.Exit(ExitCode(..))importSystem.IOimportSystem.IO.Error(mkIOError,ioeSetErrorString) #if defined(javascript_HOST_ARCH) importSystem.Process.JavaScript(getProcessId,getCurrentProcessId) #elif defined(mingw32_HOST_OS) importSystem.Win32.Process(getProcessId,getCurrentProcessId,ProcessId) #else importSystem.Posix.Process(getProcessID)importSystem.Posix.Types(CPid(..)) #endif importGHC.IO.Exception(ioException,IOErrorType(..)) #if defined(wasm32_HOST_ARCH) importGHC.IO.Exception(unsupportedOperation)importSystem.IO.Error #endif -- | 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 #if defined(javascript_HOST_ARCH) typePid=Int #elif defined(mingw32_HOST_OS) typePid=ProcessId #else typePid =CPid #endif -- ------------------------------------------------------------------------------ createProcess-- | Construct a 'CreateProcess' record for passing to 'createProcess',-- representing a raw command with arguments.---- See 'RawCommand' for precise semantics of the specified @FilePath@.proc ::FilePath->[String]->CreateProcess proc :: String -> [String] -> CreateProcess proc String cmd [String] args =CreateProcess {cmdspec :: CmdSpec cmdspec =String -> [String] -> CmdSpec RawCommand String cmd [String] args ,cwd :: Maybe String cwd =Maybe String forall a. Maybe a Nothing,env :: Maybe [(String, String)] env =Maybe [(String, String)] forall a. Maybe a Nothing,std_in :: StdStream std_in =StdStream Inherit ,std_out :: StdStream std_out =StdStream Inherit ,std_err :: StdStream std_err =StdStream Inherit ,close_fds :: Bool close_fds =Bool False,create_group :: Bool create_group =Bool False,delegate_ctlc :: Bool delegate_ctlc =Bool False,detach_console :: Bool detach_console =Bool False,create_new_console :: Bool create_new_console =Bool False,new_session :: Bool new_session =Bool False,child_group :: Maybe GroupID child_group =Maybe GroupID forall a. Maybe a Nothing,child_user :: Maybe UserID child_user =Maybe UserID forall a. Maybe a Nothing,use_process_jobs :: Bool use_process_jobs =Bool False}-- | Construct a 'CreateProcess' record for passing to 'createProcess',-- representing a command to be passed to the shell.shell ::String->CreateProcess shell :: String -> CreateProcess shell String str =CreateProcess {cmdspec :: CmdSpec cmdspec =String -> CmdSpec ShellCommand String str ,cwd :: Maybe String cwd =Maybe String forall a. Maybe a Nothing,env :: Maybe [(String, String)] env =Maybe [(String, String)] forall a. Maybe a Nothing,std_in :: StdStream std_in =StdStream Inherit ,std_out :: StdStream std_out =StdStream Inherit ,std_err :: StdStream std_err =StdStream Inherit ,close_fds :: Bool close_fds =Bool False,create_group :: Bool create_group =Bool False,delegate_ctlc :: Bool delegate_ctlc =Bool False,detach_console :: Bool detach_console =Bool False,create_new_console :: Bool create_new_console =Bool False,new_session :: Bool new_session =Bool False,child_group :: Maybe GroupID child_group =Maybe GroupID forall a. Maybe a Nothing,child_user :: Maybe UserID child_user =Maybe UserID forall a. Maybe a Nothing,use_process_jobs :: Bool use_process_jobs =Bool False}{- | 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 'Handle's, 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' == 'CreatePipe'@, then @/mb_stdin_hdl/@ will be @Just /h/@, where @/h/@ is the write end of the pipe connected to the child process's @stdin@. * 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 @Handle@s 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 @Handle@s are initially in text mode; if you need them to be in binary mode then use 'hSetBinaryMode'. @/ph/@ contains a handle to the running process. On Windows 'use_process_jobs' can be set in CreateProcess in order to create a Win32 Job object to monitor a process tree's progress. If it is set then that job is also returned inside @/ph/@. @/ph/@ can be used to kill all running sub-processes. This feature has been available since 1.5.0.0. -}createProcess ::CreateProcess ->IO(MaybeHandle,MaybeHandle,MaybeHandle,ProcessHandle )createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess CreateProcess cp =do(Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) r <-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "createProcess"CreateProcess cp StdStream -> IO () maybeCloseStd (CreateProcess -> StdStream std_in CreateProcess cp )StdStream -> IO () maybeCloseStd (CreateProcess -> StdStream std_out CreateProcess cp )StdStream -> IO () maybeCloseStd (CreateProcess -> StdStream std_err CreateProcess cp )(Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) r wheremaybeCloseStd ::StdStream ->IO()maybeCloseStd :: StdStream -> IO () maybeCloseStd (UseHandle Handle hdl )|Handle hdl Handle -> Handle -> Bool forall a. Eq a => a -> a -> Bool /=Handle stdinBool -> Bool -> Bool &&Handle hdl Handle -> Handle -> Bool forall a. Eq a => a -> a -> Bool /=Handle stdoutBool -> Bool -> Bool &&Handle hdl Handle -> Handle -> Bool forall a. Eq a => a -> a -> Bool /=Handle stderr=Handle -> IO () hCloseHandle hdl maybeCloseStd StdStream _=() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()-- | A 'C.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' 'Handle's 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.0withCreateProcess ::CreateProcess ->(MaybeHandle->MaybeHandle->MaybeHandle->ProcessHandle ->IOa )->IOa withCreateProcess :: forall a. CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess CreateProcess c Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a action =IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO ()) -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a) -> IO a forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c C.bracket(CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess CreateProcess c )(Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO () cleanupProcess (\(Maybe Handle m_in ,Maybe Handle m_out ,Maybe Handle m_err ,ProcessHandle ph )->Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a action Maybe Handle m_in Maybe Handle m_out Maybe Handle m_err ProcessHandle ph )-- wrapper so we can get exceptions with the appropriate function name.withCreateProcess_ ::String->CreateProcess ->(MaybeHandle->MaybeHandle->MaybeHandle->ProcessHandle ->IOa )->IOa withCreateProcess_ :: forall a. String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess_ String fun CreateProcess c Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a action =IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO ()) -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a) -> IO a forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c C.bracketOnError(String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String fun CreateProcess c )(Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO () cleanupProcess (\(Maybe Handle m_in ,Maybe Handle m_out ,Maybe Handle m_err ,ProcessHandle ph )->Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a action Maybe Handle m_in Maybe Handle m_out Maybe Handle m_err ProcessHandle ph )-- | 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' 'handle's.---- @since 1.6.4.0cleanupProcess ::(MaybeHandle,MaybeHandle,MaybeHandle,ProcessHandle )->IO()cleanupProcess :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO () cleanupProcess (Maybe Handle mb_stdin ,Maybe Handle mb_stdout ,Maybe Handle mb_stderr ,ph :: ProcessHandle ph @(ProcessHandle MVar ProcessHandle__ _Bool delegating_ctlc MVar () _))=doProcessHandle -> IO () terminateProcess ProcessHandle ph -- Note, it's important that other threads that might be reading/writing-- these handles also get killed off, since otherwise they might be holding-- the handle lock and prevent us from closing, leading to deadlock.IO () -> (Handle -> IO ()) -> Maybe Handle -> IO () forall b a. b -> (a -> b) -> Maybe a -> b maybe(() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return())(IO () -> IO () ignoreSigPipe (IO () -> IO ()) -> (Handle -> IO ()) -> Handle -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c .Handle -> IO () hClose)Maybe Handle mb_stdin IO () -> (Handle -> IO ()) -> Maybe Handle -> IO () forall b a. b -> (a -> b) -> Maybe a -> b maybe(() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return())Handle -> IO () hCloseMaybe Handle mb_stdout IO () -> (Handle -> IO ()) -> Maybe Handle -> IO () forall b a. b -> (a -> b) -> Maybe a -> b maybe(() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return())Handle -> IO () hCloseMaybe Handle mb_stderr -- terminateProcess does not guarantee that it terminates the process.-- Indeed on Unix it's SIGTERM, which asks nicely but does not guarantee-- that it stops. If it doesn't stop, we don't want to hang, so we wait-- asynchronously using forkIO.-- However we want to end the Ctl-C handling synchronously, so we'll do-- that synchronously, and set delegating_ctlc as False for the-- waitForProcess (which would otherwise end the Ctl-C delegation itself).Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () whenBool delegating_ctlc IO () stopDelegateControlC ThreadId _<-IO () -> IO ThreadId forkIO(ProcessHandle -> IO ExitCode waitForProcess (ProcessHandle -> ProcessHandle resetCtlcDelegation ProcessHandle ph )IO ExitCode -> IO () -> IO () forall a b. IO a -> IO b -> IO b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >>() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return())() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()whereresetCtlcDelegation :: ProcessHandle -> ProcessHandle resetCtlcDelegation (ProcessHandle MVar ProcessHandle__ m Bool _MVar () l )=MVar ProcessHandle__ -> Bool -> MVar () -> ProcessHandle ProcessHandle MVar ProcessHandle__ m Bool FalseMVar () l -- ------------------------------------------------------------------------------ spawnProcess/spawnCommand-- | 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.0spawnProcess ::FilePath->[String]->IOProcessHandle spawnProcess :: String -> [String] -> IO ProcessHandle spawnProcess String cmd [String] args =do(Maybe Handle _,Maybe Handle _,Maybe Handle _,ProcessHandle p )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "spawnProcess"(String -> [String] -> CreateProcess proc String cmd [String] args )ProcessHandle -> IO ProcessHandle forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnProcessHandle p -- | 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.0spawnCommand ::String->IOProcessHandle spawnCommand :: String -> IO ProcessHandle spawnCommand String cmd =do(Maybe Handle _,Maybe Handle _,Maybe Handle _,ProcessHandle p )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "spawnCommand"(String -> CreateProcess shell String cmd )ProcessHandle -> IO ProcessHandle forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnProcessHandle p -- ------------------------------------------------------------------------------ callProcess/callCommand-- | 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.0callProcess ::FilePath->[String]->IO()callProcess :: String -> [String] -> IO () callProcess String cmd [String] args =doExitCode exit_code <-String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ExitCode) -> IO ExitCode forall a. String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess_ String "callProcess"(String -> [String] -> CreateProcess proc String cmd [String] args ){delegate_ctlc =True}((Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ExitCode) -> IO ExitCode) -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ExitCode) -> IO ExitCode forall a b. (a -> b) -> a -> b $\Maybe Handle _Maybe Handle _Maybe Handle _ProcessHandle p ->ProcessHandle -> IO ExitCode waitForProcess ProcessHandle p caseExitCode exit_code ofExitCode ExitSuccess->() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()ExitFailureInt r ->String -> String -> [String] -> Int -> IO () forall a. String -> String -> [String] -> Int -> IO a processFailedException String "callProcess"String cmd [String] args Int r -- | 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.0callCommand ::String->IO()callCommand :: String -> IO () callCommand String cmd =doExitCode exit_code <-String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ExitCode) -> IO ExitCode forall a. String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess_ String "callCommand"(String -> CreateProcess shell String cmd ){delegate_ctlc =True}((Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ExitCode) -> IO ExitCode) -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ExitCode) -> IO ExitCode forall a b. (a -> b) -> a -> b $\Maybe Handle _Maybe Handle _Maybe Handle _ProcessHandle p ->ProcessHandle -> IO ExitCode waitForProcess ProcessHandle p caseExitCode exit_code ofExitCode ExitSuccess->() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()ExitFailureInt r ->String -> String -> [String] -> Int -> IO () forall a. String -> String -> [String] -> Int -> IO a processFailedException String "callCommand"String cmd []Int r processFailedException ::String->String->[String]->Int->IOa processFailedException :: forall a. String -> String -> [String] -> Int -> IO a processFailedException String fun String cmd [String] args Int exit_code =IOError -> IO a forall a. IOError -> IO a ioError(IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError mkIOErrorIOErrorType OtherError(String fun String -> String -> String forall a. [a] -> [a] -> [a] ++String ": "String -> String -> String forall a. [a] -> [a] -> [a] ++String cmd String -> String -> String forall a. [a] -> [a] -> [a] ++(String -> String) -> [String] -> String forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap((Char ' 'Char -> String -> String forall a. a -> [a] -> [a] :)(String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .String -> String forall a. Show a => a -> String show)[String] args String -> String -> String forall a. [a] -> [a] -> [a] ++String " (exit "String -> String -> String forall a. [a] -> [a] -> [a] ++Int -> String forall a. Show a => a -> String showInt exit_code String -> String -> String forall a. [a] -> [a] -> [a] ++String ")")Maybe Handle forall a. Maybe a NothingMaybe String forall a. Maybe a Nothing)-- ------------------------------------------------------------------------------ Control-C handling on Unix-- $ctlc-handling---- 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' = True@ option in the 'CreateProcess' 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 received the-- @SIGINT@ ourselves and begin an orderly shutdown.---- This behaviour is implemented by 'createProcess' (and-- 'waitForProcess' \/ 'getProcessExitCode') when the @'delegate_ctlc' = True@-- option is set. In particular, the @SIGINT@ 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)@. Typically you will not want to-- catch this exception, but let it propagate, giving a normal orderly shutdown.-- One detail to be aware of is that the '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-- <http://www.cons.org/cracauer/sigint.html "Proper handling of SIGINT/SIGQUIT">.-- $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.-- ------------------------------------------------------------------------------- | @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. See 'RawCommand' for-- further discussion of Windows semantics.---- * A string to pass on standard input to the forked process.--readProcess ::FilePath-- ^ Filename of the executable (see 'RawCommand' for details)->[String]-- ^ any arguments->String-- ^ standard input->IOString-- ^ stdoutreadProcess :: String -> [String] -> String -> IO String readProcess String cmd [String] args =CreateProcess -> String -> IO String readCreateProcess (CreateProcess -> String -> IO String) -> CreateProcess -> String -> IO String forall a b. (a -> b) -> a -> b $String -> [String] -> CreateProcess proc String cmd [String] args -- | @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 @Handle@s provided for @std_in@ or @std_out@ via the CreateProcess-- record will be ignored.---- @since 1.2.3.0readCreateProcess ::CreateProcess ->String-- ^ standard input->IOString-- ^ stdoutreadCreateProcess :: CreateProcess -> String -> IO String readCreateProcess CreateProcess cp String input =doletcp_opts :: CreateProcess cp_opts =CreateProcess cp {std_in =CreatePipe ,std_out =CreatePipe }(ExitCode ex ,String output )<-String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO (ExitCode, String)) -> IO (ExitCode, String) forall a. String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess_ String "readCreateProcess"CreateProcess cp_opts ((Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO (ExitCode, String)) -> IO (ExitCode, String)) -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO (ExitCode, String)) -> IO (ExitCode, String) forall a b. (a -> b) -> a -> b $\Maybe Handle mb_inh Maybe Handle mb_outh Maybe Handle _ProcessHandle ph ->case(Maybe Handle mb_inh ,Maybe Handle mb_outh )of(JustHandle inh ,JustHandle outh )->do-- fork off a thread to start consuming the outputString output <-Handle -> IO String hGetContentsHandle outh IO () -> (IO () -> IO ()) -> IO () forall a. IO () -> (IO () -> IO a) -> IO a withForkWait (() -> IO () forall a. a -> IO a C.evaluate(() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $String -> () forall a. NFData a => a -> () rnfString output )((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\IO () waitOut ->do-- now write any inputBool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless(String -> Bool forall a. [a] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool nullString input )(IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $IO () -> IO () ignoreSigPipe (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $Handle -> String -> IO () hPutStrHandle inh String input -- hClose performs implicit hFlush, and thus may trigger a SIGPIPEIO () -> IO () ignoreSigPipe (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $Handle -> IO () hCloseHandle inh -- wait on the outputIO () waitOut Handle -> IO () hCloseHandle outh -- wait on the processExitCode ex <-ProcessHandle -> IO ExitCode waitForProcess ProcessHandle ph (ExitCode, String) -> IO (ExitCode, String) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ExitCode ex ,String output )(Maybe Handle Nothing,Maybe Handle _)->String -> IO (ExitCode, String) forall a. HasCallStack => String -> a errorString "readCreateProcess: Failed to get a stdin handle."(Maybe Handle _,Maybe Handle Nothing)->String -> IO (ExitCode, String) forall a. HasCallStack => String -> a errorString "readCreateProcess: Failed to get a stdout handle."caseExitCode ex ofExitCode ExitSuccess->String -> IO String forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnString output ExitFailureInt r ->String -> String -> [String] -> Int -> IO String forall a. String -> String -> [String] -> Int -> IO a processFailedException String "readCreateProcess"String cmd [String] args Int r wherecmd :: String cmd =caseCreateProcess cp ofCreateProcess {cmdspec :: CreateProcess -> CmdSpec cmdspec =ShellCommand String sc }->String sc CreateProcess {cmdspec :: CreateProcess -> CmdSpec cmdspec =RawCommand String fp [String] _}->String fp args :: [String] args =caseCreateProcess cp ofCreateProcess {cmdspec :: CreateProcess -> CmdSpec cmdspec =ShellCommand String _}->[]CreateProcess {cmdspec :: CreateProcess -> CmdSpec cmdspec =RawCommand String _[String] args' }->[String] args' -- | @readProcessWithExitCode@ is like 'readProcess' but with two differences:---- * it returns the 'ExitCode' of the process, and does not throw any-- exception if the code is not 'ExitSuccess'.---- * 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.--readProcessWithExitCode ::FilePath-- ^ Filename of the executable (see 'RawCommand' for details)->[String]-- ^ any arguments->String-- ^ standard input->IO(ExitCode,String,String)-- ^ exitcode, stdout, stderrreadProcessWithExitCode :: String -> [String] -> String -> IO (ExitCode, String, String) readProcessWithExitCode String cmd [String] args =CreateProcess -> String -> IO (ExitCode, String, String) readCreateProcessWithExitCode (CreateProcess -> String -> IO (ExitCode, String, String)) -> CreateProcess -> String -> IO (ExitCode, String, String) forall a b. (a -> b) -> a -> b $String -> [String] -> CreateProcess proc String cmd [String] args -- | @readCreateProcessWithExitCode@ works exactly like 'readProcessWithExitCode' except that it-- lets you pass 'CreateProcess' giving better flexibility.---- Note that @Handle@s provided for @std_in@, @std_out@, or @std_err@ via the CreateProcess-- record will be ignored.---- @since 1.2.3.0readCreateProcessWithExitCode ::CreateProcess ->String-- ^ standard input->IO(ExitCode,String,String)-- ^ exitcode, stdout, stderrreadCreateProcessWithExitCode :: CreateProcess -> String -> IO (ExitCode, String, String) readCreateProcessWithExitCode CreateProcess cp String input =doletcp_opts :: CreateProcess cp_opts =CreateProcess cp {std_in =CreatePipe ,std_out =CreatePipe ,std_err =CreatePipe }String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO (ExitCode, String, String)) -> IO (ExitCode, String, String) forall a. String -> CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a) -> IO a withCreateProcess_ String "readCreateProcessWithExitCode"CreateProcess cp_opts ((Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO (ExitCode, String, String)) -> IO (ExitCode, String, String)) -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO (ExitCode, String, String)) -> IO (ExitCode, String, String) forall a b. (a -> b) -> a -> b $\Maybe Handle mb_inh Maybe Handle mb_outh Maybe Handle mb_errh ProcessHandle ph ->case(Maybe Handle mb_inh ,Maybe Handle mb_outh ,Maybe Handle mb_errh )of(JustHandle inh ,JustHandle outh ,JustHandle errh )->doString out <-Handle -> IO String hGetContentsHandle outh String err <-Handle -> IO String hGetContentsHandle errh -- fork off threads to start consuming stdout & stderrIO () -> (IO () -> IO ()) -> IO () forall a. IO () -> (IO () -> IO a) -> IO a withForkWait (() -> IO () forall a. a -> IO a C.evaluate(() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $String -> () forall a. NFData a => a -> () rnfString out )((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\IO () waitOut ->IO () -> (IO () -> IO ()) -> IO () forall a. IO () -> (IO () -> IO a) -> IO a withForkWait (() -> IO () forall a. a -> IO a C.evaluate(() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $String -> () forall a. NFData a => a -> () rnfString err )((IO () -> IO ()) -> IO ()) -> (IO () -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\IO () waitErr ->do-- now write any inputBool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless(String -> Bool forall a. [a] -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool nullString input )(IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $IO () -> IO () ignoreSigPipe (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $Handle -> String -> IO () hPutStrHandle inh String input -- hClose performs implicit hFlush, and thus may trigger a SIGPIPEIO () -> IO () ignoreSigPipe (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $Handle -> IO () hCloseHandle inh -- wait on the outputIO () waitOut IO () waitErr Handle -> IO () hCloseHandle outh Handle -> IO () hCloseHandle errh -- wait on the processExitCode ex <-ProcessHandle -> IO ExitCode waitForProcess ProcessHandle ph (ExitCode, String, String) -> IO (ExitCode, String, String) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ExitCode ex ,String out ,String err )(Maybe Handle Nothing,Maybe Handle _,Maybe Handle _)->String -> IO (ExitCode, String, String) forall a. HasCallStack => String -> a errorString "readCreateProcessWithExitCode: Failed to get a stdin handle."(Maybe Handle _,Maybe Handle Nothing,Maybe Handle _)->String -> IO (ExitCode, String, String) forall a. HasCallStack => String -> a errorString "readCreateProcessWithExitCode: Failed to get a stdout handle."(Maybe Handle _,Maybe Handle _,Maybe Handle Nothing)->String -> IO (ExitCode, String, String) forall a. HasCallStack => String -> a errorString "readCreateProcessWithExitCode: Failed to get a stderr handle."-- ------------------------------------------------------------------------------ showCommandForUser-- | 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).showCommandForUser ::FilePath->[String]->StringshowCommandForUser :: String -> [String] -> String showCommandForUser String cmd [String] args =[String] -> String unwords((String -> String) -> [String] -> [String] forall a b. (a -> b) -> [a] -> [b] mapString -> String translate (String cmd String -> [String] -> [String] forall a. a -> [a] -> [a] :[String] args ))-- ------------------------------------------------------------------------------ getPid-- | 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.0getPid ::ProcessHandle ->IO(MaybePid )getPid :: ProcessHandle -> IO (Maybe Pid) getPid (ProcessHandle MVar ProcessHandle__ mh Bool _MVar () _)=doProcessHandle__ p_ <-MVar ProcessHandle__ -> IO ProcessHandle__ forall a. MVar a -> IO a readMVarMVar ProcessHandle__ mh caseProcessHandle__ p_ of #if defined(javascript_HOST_ARCH) OpenHandleh->dopid<-getProcessIdhreturn$Justpid #elif defined(mingw32_HOST_OS) OpenHandleh->dopid<-getProcessIdhreturn$Justpid #else OpenHandle Pid pid ->Maybe Pid -> IO (Maybe Pid) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe Pid -> IO (Maybe Pid)) -> Maybe Pid -> IO (Maybe Pid) forall a b. (a -> b) -> a -> b $Pid -> Maybe Pid forall a. a -> Maybe a JustPid pid #endif ProcessHandle__ _->Maybe Pid -> IO (Maybe Pid) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnMaybe Pid forall a. Maybe a Nothing-- ------------------------------------------------------------------------------ getCurrentPid-- | Returns the PID (process ID) of the current process. On POSIX systems,-- this calls 'getProcessID' from "System.Posix.Process" in the @unix@ package.-- On Windows, this calls 'getCurrentProcessId' from "System.Win32.Process" in-- the @Win32@ package.---- @since 1.6.12.0getCurrentPid ::IOPid getCurrentPid :: IO Pid getCurrentPid = #if defined(javascript_HOST_ARCH) getCurrentProcessId #elif defined(mingw32_HOST_OS) getCurrentProcessId #else IO Pid getProcessID #endif -- ------------------------------------------------------------------------------ waitForProcess{- | Waits for the specified process to terminate, and returns its exit code. On Unix systems, may throw 'UserInterrupt' when using 'delegate_ctlc'. GHC Note: in order to call @waitForProcess@ without blocking all the other threads in the system, you must compile the program with @-threaded@. Note that it is safe to call @waitForProcess@ for the same process in multiple threads. When the process ends, threads blocking on this call will wake in FIFO order. When using 'delegate_ctlc' and the process is interrupted, only the first waiting thread will throw 'UserInterrupt'. (/Since: 1.2.0.0/) On Unix systems, a negative value @'ExitFailure' -/signum/@ indicates that the child was terminated by signal @/signum/@. 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. -}waitForProcess ::ProcessHandle ->IOExitCodewaitForProcess :: ProcessHandle -> IO ExitCode waitForProcess ph :: ProcessHandle ph @(ProcessHandle MVar ProcessHandle__ _Bool delegating_ctlc MVar () _)=IO ExitCode -> IO ExitCode forall {b}. IO b -> IO b lockWaitpid (IO ExitCode -> IO ExitCode) -> IO ExitCode -> IO ExitCode forall a b. (a -> b) -> a -> b $doProcessHandle__ p_ <-ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, ProcessHandle__)) -> IO ProcessHandle__ forall a. ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, a)) -> IO a modifyProcessHandle ProcessHandle ph ((ProcessHandle__ -> IO (ProcessHandle__, ProcessHandle__)) -> IO ProcessHandle__) -> (ProcessHandle__ -> IO (ProcessHandle__, ProcessHandle__)) -> IO ProcessHandle__ forall a b. (a -> b) -> a -> b $\ProcessHandle__ p_ ->(ProcessHandle__, ProcessHandle__) -> IO (ProcessHandle__, ProcessHandle__) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ProcessHandle__ p_ ,ProcessHandle__ p_ )caseProcessHandle__ p_ ofClosedHandle ExitCode e ->ExitCode -> IO ExitCode forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnExitCode e OpenHandle Pid h ->do-- don't hold the MVar while we call c_waitForProcess...ExitCode e <-Pid -> IO ExitCode waitForProcess' Pid h (ExitCode e' ,Bool was_open )<-ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, (ExitCode, Bool))) -> IO (ExitCode, Bool) forall a. ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, a)) -> IO a modifyProcessHandle ProcessHandle ph ((ProcessHandle__ -> IO (ProcessHandle__, (ExitCode, Bool))) -> IO (ExitCode, Bool)) -> (ProcessHandle__ -> IO (ProcessHandle__, (ExitCode, Bool))) -> IO (ExitCode, Bool) forall a b. (a -> b) -> a -> b $\ProcessHandle__ p_' ->caseProcessHandle__ p_' ofClosedHandle ExitCode e' ->(ProcessHandle__, (ExitCode, Bool)) -> IO (ProcessHandle__, (ExitCode, Bool)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ProcessHandle__ p_' ,(ExitCode e' ,Bool False))OpenExtHandle {}->String -> IO (ProcessHandle__, (ExitCode, Bool)) forall a. String -> IO a forall (m :: * -> *) a. MonadFail m => String -> m a failString "waitForProcess(OpenExtHandle): this cannot happen"OpenHandle Pid ph' ->doPid -> IO () closePHANDLE Pid ph' (ProcessHandle__, (ExitCode, Bool)) -> IO (ProcessHandle__, (ExitCode, Bool)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ExitCode -> ProcessHandle__ ClosedHandle ExitCode e ,(ExitCode e ,Bool True))-- endDelegateControlC after closing the handle, since it-- may throw UserInterruptBool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when(Bool was_open Bool -> Bool -> Bool &&Bool delegating_ctlc )(IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ExitCode -> IO () endDelegateControlC ExitCode e ExitCode -> IO ExitCode forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnExitCode e' #if defined(mingw32_HOST_OS) OpenExtHandlehjob->do-- First wait for completion of the job...waitForJobCompletionjobe<-waitForProcess'he'<-modifyProcessHandleph$\p_'->casep_'ofClosedHandlee'->return(p_',e')OpenHandle{}->fail"waitForProcess(OpenHandle): this cannot happen"OpenExtHandleph'job'->doclosePHANDLEph'closePHANDLEjob'return(ClosedHandlee,e)-- omit endDelegateControlC since it's a no-op on Windowsreturne' #else OpenExtHandle Pid _Pid _job ->ExitCode -> IO ExitCode forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ExitCode -> IO ExitCode) -> ExitCode -> IO ExitCode forall a b. (a -> b) -> a -> b $Int -> ExitCode ExitFailure(-Int 1) #endif where-- If more than one thread calls `waitpid` at a time, `waitpid` will-- return the exit code to one of them and (-1) to the rest of them,-- causing an exception to be thrown.-- Cf. https://github.com/haskell/process/issues/46, and-- https://github.com/haskell/process/pull/58 for further discussionlockWaitpid :: IO b -> IO b lockWaitpid IO b m =MVar () -> (() -> IO b) -> IO b forall a b. MVar a -> (a -> IO b) -> IO b withMVar(ProcessHandle -> MVar () waitpidLock ProcessHandle ph )((() -> IO b) -> IO b) -> (() -> IO b) -> IO b forall a b. (a -> b) -> a -> b $\()->IO b m waitForProcess' ::PHANDLE ->IOExitCodewaitForProcess' :: Pid -> IO ExitCode waitForProcess' Pid h =(Ptr CInt -> IO ExitCode) -> IO ExitCode forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca((Ptr CInt -> IO ExitCode) -> IO ExitCode) -> (Ptr CInt -> IO ExitCode) -> IO ExitCode forall a b. (a -> b) -> a -> b $\Ptr CInt pret ->do #if defined(javascript_HOST_ARCH) throwErrnoIfMinus1Retry_"waitForProcess"(C.interruptible$c_waitForProcesshpret) #else String -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1Retry_String "waitForProcess"(IO () allowInterruptIO () -> IO CInt -> IO CInt forall a b. IO a -> IO b -> IO b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >>Pid -> Ptr CInt -> IO CInt c_waitForProcess Pid h Ptr CInt pret ) #endif CInt -> ExitCode mkExitCode (CInt -> ExitCode) -> IO CInt -> IO ExitCode forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>Ptr CInt -> IO CInt forall a. Storable a => Ptr a -> IO a peekPtr CInt pret mkExitCode ::CInt->ExitCodemkExitCode :: CInt -> ExitCode mkExitCode CInt code |CInt code CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool ==CInt 0=ExitCode ExitSuccess|Bool otherwise=Int -> ExitCode ExitFailure(CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegralCInt code )-- ------------------------------------------------------------------------------ getProcessExitCode{- | This is a non-blocking version of 'waitForProcess'. If the process is still running, 'Nothing' is returned. If the process has exited, then @'Just' e@ is returned where @e@ 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. May throw 'UserInterrupt' when using 'delegate_ctlc'. -}getProcessExitCode ::ProcessHandle ->IO(MaybeExitCode)getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode) getProcessExitCode ph :: ProcessHandle ph @(ProcessHandle MVar ProcessHandle__ _Bool delegating_ctlc MVar () _)=IO (Maybe ExitCode) -> IO (Maybe ExitCode) tryLockWaitpid (IO (Maybe ExitCode) -> IO (Maybe ExitCode)) -> IO (Maybe ExitCode) -> IO (Maybe ExitCode) forall a b. (a -> b) -> a -> b $do(Maybe ExitCode m_e ,Bool was_open )<-ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> IO (Maybe ExitCode, Bool) forall a. ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, a)) -> IO a modifyProcessHandle ProcessHandle ph ((ProcessHandle__ -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> IO (Maybe ExitCode, Bool)) -> (ProcessHandle__ -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> IO (Maybe ExitCode, Bool) forall a b. (a -> b) -> a -> b $\ProcessHandle__ p_ ->caseProcessHandle__ p_ ofClosedHandle ExitCode e ->(ProcessHandle__, (Maybe ExitCode, Bool)) -> IO (ProcessHandle__, (Maybe ExitCode, Bool)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ProcessHandle__ p_ ,(ExitCode -> Maybe ExitCode forall a. a -> Maybe a JustExitCode e ,Bool False))ProcessHandle__ open ->do(Ptr CInt -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> IO (ProcessHandle__, (Maybe ExitCode, Bool)) forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca((Ptr CInt -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> (Ptr CInt -> IO (ProcessHandle__, (Maybe ExitCode, Bool))) -> IO (ProcessHandle__, (Maybe ExitCode, Bool)) forall a b. (a -> b) -> a -> b $\Ptr CInt pExitCode ->docaseProcessHandle__ -> Maybe Pid getHandle ProcessHandle__ open ofMaybe Pid Nothing->(ProcessHandle__, (Maybe ExitCode, Bool)) -> IO (ProcessHandle__, (Maybe ExitCode, Bool)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ProcessHandle__ p_ ,(Maybe ExitCode forall a. Maybe a Nothing,Bool False))JustPid h ->doCInt res <-String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => String -> IO a -> IO a throwErrnoIfMinus1RetryString "getProcessExitCode"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $Pid -> Ptr CInt -> IO CInt c_getProcessExitCode Pid h Ptr CInt pExitCode CInt code <-Ptr CInt -> IO CInt forall a. Storable a => Ptr a -> IO a peekPtr CInt pExitCode ifCInt res CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool ==CInt 0then(ProcessHandle__, (Maybe ExitCode, Bool)) -> IO (ProcessHandle__, (Maybe ExitCode, Bool)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ProcessHandle__ p_ ,(Maybe ExitCode forall a. Maybe a Nothing,Bool False))elsedoPid -> IO () closePHANDLE Pid h lete :: ExitCode e |CInt code CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool ==CInt 0=ExitCode ExitSuccess|Bool otherwise=Int -> ExitCode ExitFailure(CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegralCInt code )(ProcessHandle__, (Maybe ExitCode, Bool)) -> IO (ProcessHandle__, (Maybe ExitCode, Bool)) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(ExitCode -> ProcessHandle__ ClosedHandle ExitCode e ,(ExitCode -> Maybe ExitCode forall a. a -> Maybe a JustExitCode e ,Bool True))-- endDelegateControlC after closing the handle, since it-- may throw UserInterruptcaseMaybe ExitCode m_e ofJustExitCode e |Bool was_open Bool -> Bool -> Bool &&Bool delegating_ctlc ->ExitCode -> IO () endDelegateControlC ExitCode e Maybe ExitCode _->() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()Maybe ExitCode -> IO (Maybe ExitCode) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnMaybe ExitCode m_e wheregetHandle ::ProcessHandle__ ->MaybePHANDLE getHandle :: ProcessHandle__ -> Maybe Pid getHandle (OpenHandle Pid h )=Pid -> Maybe Pid forall a. a -> Maybe a JustPid h getHandle (ClosedHandle ExitCode _)=Maybe Pid forall a. Maybe a NothinggetHandle (OpenExtHandle Pid h Pid _)=Pid -> Maybe Pid forall a. a -> Maybe a JustPid h -- If somebody is currently holding the waitpid lock, we don't want to-- accidentally remove the pid from the process table.-- Try acquiring the waitpid lock. If it is held, we are done-- since that means the process is still running and we can return-- `Nothing`. If it is not held, acquire it so we can run the-- (non-blocking) call to `waitpid` without worrying about any-- other threads calling it at the same time.tryLockWaitpid ::IO(MaybeExitCode)->IO(MaybeExitCode)tryLockWaitpid :: IO (Maybe ExitCode) -> IO (Maybe ExitCode) tryLockWaitpid IO (Maybe ExitCode) action =IO (Maybe ()) -> (Maybe () -> IO ()) -> (Maybe () -> IO (Maybe ExitCode)) -> IO (Maybe ExitCode) forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracketIO (Maybe ()) acquire Maybe () -> IO () release Maybe () -> IO (Maybe ExitCode) between whereacquire :: IO (Maybe ()) acquire =MVar () -> IO (Maybe ()) forall a. MVar a -> IO (Maybe a) tryTakeMVar(ProcessHandle -> MVar () waitpidLock ProcessHandle ph )release :: Maybe () -> IO () release Maybe () m =caseMaybe () m ofMaybe () Nothing->() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()Just()->MVar () -> () -> IO () forall a. MVar a -> a -> IO () putMVar(ProcessHandle -> MVar () waitpidLock ProcessHandle ph )()between :: Maybe () -> IO (Maybe ExitCode) between Maybe () m =caseMaybe () m ofMaybe () Nothing->Maybe ExitCode -> IO (Maybe ExitCode) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnMaybe ExitCode forall a. Maybe a NothingJust()->IO (Maybe ExitCode) action -- ------------------------------------------------------------------------------ terminateProcess-- | 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.terminateProcess ::ProcessHandle ->IO()terminateProcess :: ProcessHandle -> IO () terminateProcess ProcessHandle ph =doProcessHandle -> (ProcessHandle__ -> IO ()) -> IO () forall a. ProcessHandle -> (ProcessHandle__ -> IO a) -> IO a withProcessHandle ProcessHandle ph ((ProcessHandle__ -> IO ()) -> IO ()) -> (ProcessHandle__ -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\ProcessHandle__ p_ ->caseProcessHandle__ p_ ofClosedHandle ExitCode _->() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return() #if defined(mingw32_HOST_OS) OpenExtHandle{}->terminateJobUnsafep_1>>return() #else OpenExtHandle {}->String -> IO () forall a. HasCallStack => String -> a errorString "terminateProcess with OpenExtHandle should not happen on POSIX." #endif OpenHandle Pid h ->doString -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> IO a -> IO () throwErrnoIfMinus1Retry_String "terminateProcess"(IO CInt -> IO ()) -> IO CInt -> IO () forall a b. (a -> b) -> a -> b $Pid -> IO CInt c_terminateProcess Pid h () -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()-- does not close the handle, we might want to try terminating it-- again, or get its exit code.-- ------------------------------------------------------------------------------ Interface to C bits #if defined(wasm32_HOST_ARCH) c_terminateProcess::PHANDLE->IOCIntc_terminateProcess_=ioError(ioeSetLocationunsupportedOperation"terminateProcess")c_getProcessExitCode::PHANDLE->PtrCInt->IOCIntc_getProcessExitCode__=ioError(ioeSetLocationunsupportedOperation"getProcessExitCode")c_waitForProcess::PHANDLE->PtrCInt->IOCIntc_waitForProcess__=ioError(ioeSetLocationunsupportedOperation"waitForProcess") #elif defined(javascript_HOST_ARCH) foreignimportjavascriptunsafe"h$process_terminateProcess"c_terminateProcess::PHANDLE->IOIntforeignimportjavascriptunsafe"h$process_getProcessExitCode"c_getProcessExitCode::PHANDLE->PtrInt->IOIntforeignimportjavascriptinterruptible"h$process_waitForProcess"c_waitForProcess::PHANDLE->PtrCInt->IOCInt #else foreignimportccallunsafe"terminateProcess"c_terminateProcess ::PHANDLE ->IOCIntforeignimportccallunsafe"getProcessExitCode"c_getProcessExitCode ::PHANDLE ->PtrCInt->IOCIntforeignimportccallinterruptible"waitForProcess"-- NB. safe - can blockc_waitForProcess ::PHANDLE ->PtrCInt->IOCInt #endif -- ------------------------------------------------------------------------------ Old deprecated variants-- ------------------------------------------------------------------------------ TODO: We're not going to mark these functions as DEPRECATED immediately in-- process-1.2.0.0. That's because some of their replacements have not been-- around for all that long. But they should eventually be marked with a-- suitable DEPRECATED pragma after a release or two.-- ------------------------------------------------------------------------------ runCommand--TODO: in a later release {-# DEPRECATED runCommand "Use 'spawnCommand' instead" #-}{- | Runs a command using the shell. -}runCommand ::String->IOProcessHandle runCommand :: String -> IO ProcessHandle runCommand String string =do(Maybe Handle _,Maybe Handle _,Maybe Handle _,ProcessHandle ph )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "runCommand"(String -> CreateProcess shell String string )ProcessHandle -> IO ProcessHandle forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnProcessHandle ph -- ------------------------------------------------------------------------------ runProcess--TODO: in a later release {-# DEPRECATED runProcess "Use 'spawnProcess' or 'createProcess' instead" #-}{- | Runs a raw command, optionally specifying 'Handle's from which to take the @stdin@, @stdout@ and @stderr@ channels for the new process (otherwise these handles are inherited from the current process). Any 'Handle's passed to 'runProcess' are placed immediately in the closed state. Note: consider using the more general 'createProcess' instead of 'runProcess'. -}runProcess ::FilePath-- ^ Filename of the executable (see 'RawCommand' for details)->[String]-- ^ Arguments to pass to the executable->MaybeFilePath-- ^ Optional path to the working directory->Maybe[(String,String)]-- ^ Optional environment (otherwise inherit)->MaybeHandle-- ^ Handle to use for @stdin@ (Nothing => use existing @stdin@)->MaybeHandle-- ^ Handle to use for @stdout@ (Nothing => use existing @stdout@)->MaybeHandle-- ^ Handle to use for @stderr@ (Nothing => use existing @stderr@)->IOProcessHandle runProcess :: String -> [String] -> Maybe String -> Maybe [(String, String)] -> Maybe Handle -> Maybe Handle -> Maybe Handle -> IO ProcessHandle runProcess String cmd [String] args Maybe String mb_cwd Maybe [(String, String)] mb_env Maybe Handle mb_stdin Maybe Handle mb_stdout Maybe Handle mb_stderr =do(Maybe Handle _,Maybe Handle _,Maybe Handle _,ProcessHandle ph )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "runProcess"(String -> [String] -> CreateProcess proc String cmd [String] args ){cwd =mb_cwd ,env =mb_env ,std_in =mbToStd mb_stdin ,std_out =mbToStd mb_stdout ,std_err =mbToStd mb_stderr }Maybe Handle -> IO () maybeClose Maybe Handle mb_stdin Maybe Handle -> IO () maybeClose Maybe Handle mb_stdout Maybe Handle -> IO () maybeClose Maybe Handle mb_stderr ProcessHandle -> IO ProcessHandle forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a returnProcessHandle ph wheremaybeClose ::MaybeHandle->IO()maybeClose :: Maybe Handle -> IO () maybeClose (JustHandle hdl )|Handle hdl Handle -> Handle -> Bool forall a. Eq a => a -> a -> Bool /=Handle stdinBool -> Bool -> Bool &&Handle hdl Handle -> Handle -> Bool forall a. Eq a => a -> a -> Bool /=Handle stdoutBool -> Bool -> Bool &&Handle hdl Handle -> Handle -> Bool forall a. Eq a => a -> a -> Bool /=Handle stderr=Handle -> IO () hCloseHandle hdl maybeClose Maybe Handle _=() -> IO () forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return()mbToStd ::MaybeHandle->StdStream mbToStd :: Maybe Handle -> StdStream mbToStd Maybe Handle Nothing=StdStream Inherit mbToStd (JustHandle hdl )=Handle -> StdStream UseHandle Handle hdl -- ------------------------------------------------------------------------------ runInteractiveCommand--TODO: in a later release {-# DEPRECATED runInteractiveCommand "Use 'createProcess' instead" #-}{- | Runs a command using the shell, and returns 'Handle's that may be used to communicate with the process via its @stdin@, @stdout@, and @stderr@ respectively. -}runInteractiveCommand ::String->IO(Handle,Handle,Handle,ProcessHandle )runInteractiveCommand :: String -> IO (Handle, Handle, Handle, ProcessHandle) runInteractiveCommand String string =String -> CreateProcess -> IO (Handle, Handle, Handle, ProcessHandle) runInteractiveProcess1 String "runInteractiveCommand"(String -> CreateProcess shell String string )-- ------------------------------------------------------------------------------ runInteractiveProcess--TODO: in a later release {-# DEPRECATED runInteractiveCommand "Use 'createProcess' instead" #-}{- | Runs a raw command, and returns 'Handle's 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) -}runInteractiveProcess ::FilePath-- ^ Filename of the executable (see 'RawCommand' for details)->[String]-- ^ Arguments to pass to the executable->MaybeFilePath-- ^ Optional path to the working directory->Maybe[(String,String)]-- ^ Optional environment (otherwise inherit)->IO(Handle,Handle,Handle,ProcessHandle )runInteractiveProcess :: String -> [String] -> Maybe String -> Maybe [(String, String)] -> IO (Handle, Handle, Handle, ProcessHandle) runInteractiveProcess String cmd [String] args Maybe String mb_cwd Maybe [(String, String)] mb_env =doString -> CreateProcess -> IO (Handle, Handle, Handle, ProcessHandle) runInteractiveProcess1 String "runInteractiveProcess"(String -> [String] -> CreateProcess proc String cmd [String] args ){cwd =mb_cwd ,env =mb_env }runInteractiveProcess1 ::String->CreateProcess ->IO(Handle,Handle,Handle,ProcessHandle )runInteractiveProcess1 :: String -> CreateProcess -> IO (Handle, Handle, Handle, ProcessHandle) runInteractiveProcess1 String fun CreateProcess cmd =do(Maybe Handle mb_in ,Maybe Handle mb_out ,Maybe Handle mb_err ,ProcessHandle p )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String fun CreateProcess cmd {std_in =CreatePipe ,std_out =CreatePipe ,std_err =CreatePipe }(Handle, Handle, Handle, ProcessHandle) -> IO (Handle, Handle, Handle, ProcessHandle) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(Maybe Handle -> Handle forall a. HasCallStack => Maybe a -> a fromJustMaybe Handle mb_in ,Maybe Handle -> Handle forall a. HasCallStack => Maybe a -> a fromJustMaybe Handle mb_out ,Maybe Handle -> Handle forall a. HasCallStack => Maybe a -> a fromJustMaybe Handle mb_err ,ProcessHandle p )-- ----------------------------------------------------------------------------- system & rawSystem--TODO: in a later release {-# DEPRECATED system "Use 'callCommand' (or 'spawnCommand' and 'waitForProcess') instead" #-}{-| 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 'System.IO.Error.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. -}system ::String->IOExitCodesystem :: String -> IO ExitCode system String ""=IOError -> IO ExitCode forall a. IOError -> IO a ioException(IOError -> String -> IOError ioeSetErrorString(IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError mkIOErrorIOErrorType InvalidArgumentString "system"Maybe Handle forall a. Maybe a NothingMaybe String forall a. Maybe a Nothing)String "null command")system String str =do(Maybe Handle _,Maybe Handle _,Maybe Handle _,ProcessHandle p )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "system"(String -> CreateProcess shell String str ){delegate_ctlc =True}ProcessHandle -> IO ExitCode waitForProcess ProcessHandle p --TODO: in a later release {-# DEPRECATED rawSystem "Use 'callProcess' (or 'spawnProcess' and 'waitForProcess') instead" #-}{-| The computation @'rawSystem' /cmd/ /args/@ runs the operating system command @/cmd/@ 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'. -}rawSystem ::String->[String]->IOExitCoderawSystem :: String -> [String] -> IO ExitCode rawSystem String cmd [String] args =do(Maybe Handle _,Maybe Handle _,Maybe Handle _,ProcessHandle p )<-String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) createProcess_ String "rawSystem"(String -> [String] -> CreateProcess proc String cmd [String] args ){delegate_ctlc =True}ProcessHandle -> IO ExitCode waitForProcess ProcessHandle p