module System.Process (
ProcessHandle,
runCommand,
runProcess,
runInteractiveCommand,
runInteractiveProcess,
waitForProcess,
getProcessExitCode,
terminateProcess,
) where
import Prelude
import System.Process.Internals
import Foreign
import Foreign.C
import System.IO
import System.Exit
import System.Posix.Internals
import GHC.IOBase ( FD )
import GHC.Handle ( fdToHandle' )
runCommand
:: String
-> IO ProcessHandle
runCommand string = do
(cmd,args) <- commandToProcess string
#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runProcessPosix "runCommand" cmd args Nothing Nothing Nothing Nothing Nothing
Nothing Nothing
#else
runProcessWin32 "runCommand" cmd [] Nothing Nothing Nothing Nothing Nothing args
#endif
runProcess
:: FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String,String)]
-> Maybe Handle
-> Maybe Handle
-> Maybe Handle
-> IO ProcessHandle
runProcess cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr = do
#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
h <- runProcessPosix "runProcess" cmd args mb_cwd mb_env
mb_stdin mb_stdout mb_stderr
Nothing Nothing
#else
h <- runProcessWin32 "runProcess" cmd args mb_cwd mb_env
mb_stdin mb_stdout mb_stderr ""
#endif
maybe (return ()) hClose mb_stdin
maybe (return ()) hClose mb_stdout
maybe (return ()) hClose mb_stderr
return h
runInteractiveCommand
:: String
-> IO (Handle,Handle,Handle,ProcessHandle)
runInteractiveCommand string = do
(cmd,args) <- commandToProcess string
#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runInteractiveProcess1 "runInteractiveCommand" cmd args Nothing Nothing
#else
runInteractiveProcess1 "runInteractiveCommand" cmd [] Nothing Nothing args
#endif
runInteractiveProcess
:: FilePath
-> [String]
-> Maybe FilePath
-> Maybe [(String,String)]
-> IO (Handle,Handle,Handle,ProcessHandle)
#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
runInteractiveProcess cmd args mb_cwd mb_env =
runInteractiveProcess1 "runInteractiveProcess" cmd args mb_cwd mb_env
runInteractiveProcess1 fun cmd args mb_cwd mb_env = do
withFilePathException cmd $
alloca $ \ pfdStdInput ->
alloca $ \ pfdStdOutput ->
alloca $ \ pfdStdError ->
maybeWith withCEnvironment mb_env $ \pEnv ->
maybeWith withCString mb_cwd $ \pWorkDir ->
withMany withCString (cmd:args) $ \cstrs ->
withArray0 nullPtr cstrs $ \pargs -> do
proc_handle <- throwErrnoIfMinus1 fun
(c_runInteractiveProcess pargs pWorkDir pEnv
pfdStdInput pfdStdOutput pfdStdError)
hndStdInput <- fdToHandle pfdStdInput WriteMode
hndStdOutput <- fdToHandle pfdStdOutput ReadMode
hndStdError <- fdToHandle pfdStdError ReadMode
ph <- mkProcessHandle proc_handle
return (hndStdInput, hndStdOutput, hndStdError, ph)
foreign import ccall unsafe "runInteractiveProcess"
c_runInteractiveProcess
:: Ptr CString
-> CString
-> Ptr CString
-> Ptr FD
-> Ptr FD
-> Ptr FD
-> IO PHANDLE
#else
runInteractiveProcess cmd args mb_cwd mb_env =
runInteractiveProcess1 "runInteractiveProcess" cmd args mb_cwd mb_env ""
runInteractiveProcess1 fun cmd args workDir env extra_cmdline
= withFilePathException cmd $ do
let cmdline = translate cmd ++
concat (map ((' ':) . translate) args) ++
(if null extra_cmdline then "" else ' ':extra_cmdline)
withCString cmdline $ \pcmdline ->
alloca $ \ pfdStdInput ->
alloca $ \ pfdStdOutput ->
alloca $ \ pfdStdError -> do
maybeWith withCEnvironment env $ \pEnv -> do
maybeWith withCString workDir $ \pWorkDir -> do
proc_handle <- throwErrnoIfMinus1 fun $
c_runInteractiveProcess pcmdline pWorkDir pEnv
pfdStdInput pfdStdOutput pfdStdError
hndStdInput <- fdToHandle pfdStdInput WriteMode
hndStdOutput <- fdToHandle pfdStdOutput ReadMode
hndStdError <- fdToHandle pfdStdError ReadMode
ph <- mkProcessHandle proc_handle
return (hndStdInput, hndStdOutput, hndStdError, ph)
foreign import ccall unsafe "runInteractiveProcess"
c_runInteractiveProcess
:: CString
-> CString
-> Ptr ()
-> Ptr FD
-> Ptr FD
-> Ptr FD
-> IO PHANDLE
#endif
fdToHandle :: Ptr FD -> IOMode -> IO Handle
fdToHandle pfd mode = do
fd <- peek pfd
fdToHandle' fd (Just Stream)
False
("fd:" ++ show fd) mode True
waitForProcess
:: ProcessHandle
-> IO ExitCode
waitForProcess ph = do
p_ <- withProcessHandle ph $ \p_ -> return (p_,p_)
case p_ of
ClosedHandle e -> return e
OpenHandle h -> do
code <- throwErrnoIfMinus1 "waitForProcess" (c_waitForProcess h)
withProcessHandle ph $ \p_ ->
case p_ of
ClosedHandle e -> return (p_,e)
OpenHandle ph -> do
closePHANDLE ph
let e = if (code == 0)
then ExitSuccess
else (ExitFailure (fromIntegral code))
return (ClosedHandle e, e)
terminateProcess :: ProcessHandle -> IO ()
terminateProcess ph = do
withProcessHandle_ ph $ \p_ ->
case p_ of
ClosedHandle _ -> return p_
OpenHandle h -> do
throwErrnoIfMinus1_ "terminateProcess" $ c_terminateProcess h
return p_
getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode)
getProcessExitCode ph = do
withProcessHandle ph $ \p_ ->
case p_ of
ClosedHandle e -> return (p_, Just e)
OpenHandle h ->
alloca $ \pExitCode -> do
res <- throwErrnoIfMinus1 "getProcessExitCode" $
c_getProcessExitCode h pExitCode
code <- peek pExitCode
if res == 0
then return (p_, Nothing)
else do
closePHANDLE h
let e | code == 0 = ExitSuccess
| otherwise = ExitFailure (fromIntegral code)
return (ClosedHandle e, Just e)
foreign import ccall unsafe "terminateProcess"
c_terminateProcess
:: PHANDLE
-> IO CInt
foreign import ccall unsafe "getProcessExitCode"
c_getProcessExitCode
:: PHANDLE
-> Ptr CInt
-> IO CInt
foreign import ccall safe "waitForProcess"
c_waitForProcess
:: PHANDLE
-> IO CInt