2012-07-19 04:43:36 +00:00
|
|
|
{- System.Process enhancements, including additional ways of running
|
|
|
|
- processes, and logging.
|
2012-07-18 19:30:26 +00:00
|
|
|
-
|
2015-05-30 15:27:40 +00:00
|
|
|
- Copyright 2012-2015 Joey Hess <id@joeyh.name>
|
2012-07-18 19:30:26 +00:00
|
|
|
-
|
2014-05-10 14:01:27 +00:00
|
|
|
- License: BSD-2-clause
|
2012-07-18 19:30:26 +00:00
|
|
|
-}
|
|
|
|
|
2013-05-10 20:08:53 +00:00
|
|
|
{-# LANGUAGE CPP, Rank2Types #-}
|
2015-05-10 20:31:50 +00:00
|
|
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
2012-07-18 19:30:26 +00:00
|
|
|
|
2012-07-19 04:43:36 +00:00
|
|
|
module Utility.Process (
|
|
|
|
module X,
|
2014-06-10 23:20:14 +00:00
|
|
|
CreateProcess(..),
|
2012-07-19 04:43:36 +00:00
|
|
|
StdHandle(..),
|
2012-08-25 00:50:39 +00:00
|
|
|
readProcess,
|
2014-11-19 04:55:33 +00:00
|
|
|
readProcess',
|
2012-07-19 04:43:36 +00:00
|
|
|
readProcessEnv,
|
2012-08-25 00:50:39 +00:00
|
|
|
writeReadProcessEnv,
|
2012-07-19 04:43:36 +00:00
|
|
|
forceSuccessProcess,
|
2016-03-07 00:07:38 +00:00
|
|
|
forceSuccessProcess',
|
2012-07-19 04:43:36 +00:00
|
|
|
checkSuccessProcess,
|
2012-09-22 03:25:06 +00:00
|
|
|
ignoreFailureProcess,
|
2012-07-19 04:43:36 +00:00
|
|
|
createProcessSuccess,
|
|
|
|
createProcessChecked,
|
|
|
|
createBackgroundProcess,
|
|
|
|
withHandle,
|
2015-04-03 19:33:28 +00:00
|
|
|
withIOHandles,
|
2015-04-03 20:48:30 +00:00
|
|
|
withOEHandles,
|
2018-03-08 18:02:18 +00:00
|
|
|
withNullHandle,
|
2012-10-28 17:51:14 +00:00
|
|
|
withQuietOutput,
|
2015-04-04 18:34:03 +00:00
|
|
|
feedWithQuietOutput,
|
2012-07-19 04:43:36 +00:00
|
|
|
createProcess,
|
2015-08-13 17:12:44 +00:00
|
|
|
waitForProcess,
|
2013-06-14 21:35:45 +00:00
|
|
|
startInteractiveProcess,
|
2012-09-22 03:25:06 +00:00
|
|
|
stdinHandle,
|
|
|
|
stdoutHandle,
|
|
|
|
stderrHandle,
|
2015-04-03 19:33:28 +00:00
|
|
|
ioHandles,
|
2014-04-12 19:59:34 +00:00
|
|
|
processHandle,
|
2013-12-11 03:19:18 +00:00
|
|
|
devNull,
|
2012-07-19 04:43:36 +00:00
|
|
|
) where
|
|
|
|
|
2015-10-28 04:18:01 +00:00
|
|
|
import qualified Utility.Process.Shim
|
|
|
|
import qualified Utility.Process.Shim as X hiding (CreateProcess(..), createProcess, runInteractiveProcess, readProcess, readProcessWithExitCode, system, rawSystem, runInteractiveCommand, runProcess)
|
|
|
|
import Utility.Process.Shim hiding (createProcess, readProcess, waitForProcess)
|
|
|
|
import Utility.Misc
|
|
|
|
import Utility.Exception
|
|
|
|
|
2012-07-18 19:30:26 +00:00
|
|
|
import System.Exit
|
|
|
|
import System.IO
|
2012-07-19 04:43:36 +00:00
|
|
|
import System.Log.Logger
|
2012-08-25 00:50:39 +00:00
|
|
|
import Control.Concurrent
|
|
|
|
import qualified Control.Exception as E
|
|
|
|
import Control.Monad
|
2012-07-18 19:30:26 +00:00
|
|
|
|
2012-07-19 04:43:36 +00:00
|
|
|
type CreateProcessRunner = forall a. CreateProcess -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a) -> IO a
|
|
|
|
|
|
|
|
data StdHandle = StdinHandle | StdoutHandle | StderrHandle
|
|
|
|
deriving (Eq)
|
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Normally, when reading from a process, it does not need to be fed any
|
|
|
|
-- standard input.
|
2012-08-25 00:50:39 +00:00
|
|
|
readProcess :: FilePath -> [String] -> IO String
|
|
|
|
readProcess cmd args = readProcessEnv cmd args Nothing
|
|
|
|
|
2012-07-19 04:43:36 +00:00
|
|
|
readProcessEnv :: FilePath -> [String] -> Maybe [(String, String)] -> IO String
|
2014-11-19 04:55:33 +00:00
|
|
|
readProcessEnv cmd args environ = readProcess' p
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
p = (proc cmd args)
|
|
|
|
{ std_out = CreatePipe
|
|
|
|
, env = environ
|
|
|
|
}
|
2012-07-19 04:43:36 +00:00
|
|
|
|
2014-11-19 04:55:33 +00:00
|
|
|
readProcess' :: CreateProcess -> IO String
|
|
|
|
readProcess' p = withHandle StdoutHandle createProcessSuccess p $ \h -> do
|
|
|
|
output <- hGetContentsStrict h
|
|
|
|
hClose h
|
|
|
|
return output
|
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Runs an action to write to a process on its stdin,
|
|
|
|
-- returns its output, and also allows specifying the environment.
|
2012-08-25 00:50:39 +00:00
|
|
|
writeReadProcessEnv
|
|
|
|
:: FilePath
|
|
|
|
-> [String]
|
|
|
|
-> Maybe [(String, String)]
|
2013-10-20 21:50:51 +00:00
|
|
|
-> (Maybe (Handle -> IO ()))
|
2012-10-12 16:19:30 +00:00
|
|
|
-> (Maybe (Handle -> IO ()))
|
2012-08-25 00:50:39 +00:00
|
|
|
-> IO String
|
2013-10-20 21:50:51 +00:00
|
|
|
writeReadProcessEnv cmd args environ writestdin adjusthandle = do
|
2012-08-25 00:50:39 +00:00
|
|
|
(Just inh, Just outh, _, pid) <- createProcess p
|
|
|
|
|
2012-10-12 16:19:30 +00:00
|
|
|
maybe (return ()) (\a -> a inh) adjusthandle
|
|
|
|
maybe (return ()) (\a -> a outh) adjusthandle
|
|
|
|
|
2012-08-25 00:50:39 +00:00
|
|
|
-- fork off a thread to start consuming the output
|
|
|
|
output <- hGetContents outh
|
|
|
|
outMVar <- newEmptyMVar
|
|
|
|
_ <- forkIO $ E.evaluate (length output) >> putMVar outMVar ()
|
|
|
|
|
|
|
|
-- now write and flush any input
|
2013-10-20 21:50:51 +00:00
|
|
|
maybe (return ()) (\a -> a inh >> hFlush inh) writestdin
|
2012-08-25 00:50:39 +00:00
|
|
|
hClose inh -- done with stdin
|
|
|
|
|
|
|
|
-- wait on the output
|
|
|
|
takeMVar outMVar
|
|
|
|
hClose outh
|
|
|
|
|
|
|
|
-- wait on the process
|
|
|
|
forceSuccessProcess p pid
|
|
|
|
|
|
|
|
return output
|
|
|
|
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
p = (proc cmd args)
|
|
|
|
{ std_in = CreatePipe
|
|
|
|
, std_out = CreatePipe
|
|
|
|
, std_err = Inherit
|
|
|
|
, env = environ
|
|
|
|
}
|
2012-08-25 00:50:39 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Waits for a ProcessHandle, and throws an IOError if the process
|
|
|
|
-- did not exit successfully.
|
2012-07-19 04:43:36 +00:00
|
|
|
forceSuccessProcess :: CreateProcess -> ProcessHandle -> IO ()
|
2016-03-07 00:07:38 +00:00
|
|
|
forceSuccessProcess p pid = waitForProcess pid >>= forceSuccessProcess' p
|
|
|
|
|
|
|
|
forceSuccessProcess' :: CreateProcess -> ExitCode -> IO ()
|
|
|
|
forceSuccessProcess' _ ExitSuccess = return ()
|
|
|
|
forceSuccessProcess' p (ExitFailure n) = fail $
|
|
|
|
showCmd p ++ " exited " ++ show n
|
2012-07-18 19:30:26 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Waits for a ProcessHandle and returns True if it exited successfully.
|
|
|
|
-- Note that using this with createProcessChecked will throw away
|
|
|
|
-- the Bool, and is only useful to ignore the exit code of a process,
|
|
|
|
-- while still waiting for it. -}
|
2012-07-19 04:43:36 +00:00
|
|
|
checkSuccessProcess :: ProcessHandle -> IO Bool
|
|
|
|
checkSuccessProcess pid = do
|
|
|
|
code <- waitForProcess pid
|
|
|
|
return $ code == ExitSuccess
|
|
|
|
|
2012-10-04 22:04:09 +00:00
|
|
|
ignoreFailureProcess :: ProcessHandle -> IO Bool
|
|
|
|
ignoreFailureProcess pid = do
|
|
|
|
void $ waitForProcess pid
|
|
|
|
return True
|
2012-09-22 03:25:06 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Runs createProcess, then an action on its handles, and then
|
|
|
|
-- forceSuccessProcess.
|
2012-07-19 04:43:36 +00:00
|
|
|
createProcessSuccess :: CreateProcessRunner
|
|
|
|
createProcessSuccess p a = createProcessChecked (forceSuccessProcess p) p a
|
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Runs createProcess, then an action on its handles, and then
|
|
|
|
-- a checker action on its exit code, which must wait for the process.
|
2012-07-19 04:43:36 +00:00
|
|
|
createProcessChecked :: (ProcessHandle -> IO b) -> CreateProcessRunner
|
|
|
|
createProcessChecked checker p a = do
|
|
|
|
t@(_, _, _, pid) <- createProcess p
|
2013-05-19 19:52:22 +00:00
|
|
|
r <- tryNonAsync $ a t
|
2012-07-19 04:43:36 +00:00
|
|
|
_ <- checker pid
|
2013-05-19 19:52:22 +00:00
|
|
|
either E.throw return r
|
2012-07-19 04:43:36 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Leaves the process running, suitable for lazy streaming.
|
|
|
|
-- Note: Zombies will result, and must be waited on.
|
2012-07-19 04:43:36 +00:00
|
|
|
createBackgroundProcess :: CreateProcessRunner
|
|
|
|
createBackgroundProcess p a = a =<< createProcess p
|
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Runs a CreateProcessRunner, on a CreateProcess structure, that
|
|
|
|
-- is adjusted to pipe only from/to a single StdHandle, and passes
|
|
|
|
-- the resulting Handle to an action.
|
2012-07-19 04:43:36 +00:00
|
|
|
withHandle
|
|
|
|
:: StdHandle
|
|
|
|
-> CreateProcessRunner
|
|
|
|
-> CreateProcess
|
|
|
|
-> (Handle -> IO a)
|
|
|
|
-> IO a
|
|
|
|
withHandle h creator p a = creator p' $ a . select
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
base = p
|
|
|
|
{ std_in = Inherit
|
|
|
|
, std_out = Inherit
|
|
|
|
, std_err = Inherit
|
|
|
|
}
|
|
|
|
(select, p')
|
|
|
|
| h == StdinHandle =
|
|
|
|
(stdinHandle, base { std_in = CreatePipe })
|
|
|
|
| h == StdoutHandle =
|
|
|
|
(stdoutHandle, base { std_out = CreatePipe })
|
|
|
|
| h == StderrHandle =
|
|
|
|
(stderrHandle, base { std_err = CreatePipe })
|
2012-07-19 04:43:36 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Like withHandle, but passes (stdin, stdout) handles to the action.
|
2015-04-03 19:33:28 +00:00
|
|
|
withIOHandles
|
2012-07-19 04:43:36 +00:00
|
|
|
:: CreateProcessRunner
|
|
|
|
-> CreateProcess
|
|
|
|
-> ((Handle, Handle) -> IO a)
|
|
|
|
-> IO a
|
2015-04-03 19:33:28 +00:00
|
|
|
withIOHandles creator p a = creator p' $ a . ioHandles
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
p' = p
|
|
|
|
{ std_in = CreatePipe
|
|
|
|
, std_out = CreatePipe
|
|
|
|
, std_err = Inherit
|
|
|
|
}
|
2012-07-19 04:43:36 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Like withHandle, but passes (stdout, stderr) handles to the action.
|
2015-04-03 20:48:30 +00:00
|
|
|
withOEHandles
|
|
|
|
:: CreateProcessRunner
|
|
|
|
-> CreateProcess
|
|
|
|
-> ((Handle, Handle) -> IO a)
|
|
|
|
-> IO a
|
|
|
|
withOEHandles creator p a = creator p' $ a . oeHandles
|
|
|
|
where
|
|
|
|
p' = p
|
|
|
|
{ std_in = Inherit
|
|
|
|
, std_out = CreatePipe
|
|
|
|
, std_err = CreatePipe
|
|
|
|
}
|
|
|
|
|
2018-03-08 18:02:18 +00:00
|
|
|
withNullHandle :: (Handle -> IO a) -> IO a
|
|
|
|
withNullHandle = withFile devNull WriteMode
|
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Forces the CreateProcessRunner to run quietly;
|
|
|
|
-- both stdout and stderr are discarded.
|
2012-10-28 17:51:14 +00:00
|
|
|
withQuietOutput
|
|
|
|
:: CreateProcessRunner
|
|
|
|
-> CreateProcess
|
|
|
|
-> IO ()
|
2018-03-08 18:02:18 +00:00
|
|
|
withQuietOutput creator p = withNullHandle $ \nullh -> do
|
2012-10-28 17:51:14 +00:00
|
|
|
let p' = p
|
2013-06-18 01:26:06 +00:00
|
|
|
{ std_out = UseHandle nullh
|
|
|
|
, std_err = UseHandle nullh
|
2012-10-28 17:51:14 +00:00
|
|
|
}
|
|
|
|
creator p' $ const $ return ()
|
2013-08-01 21:30:47 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Stdout and stderr are discarded, while the process is fed stdin
|
|
|
|
-- from the handle.
|
2015-04-04 18:34:03 +00:00
|
|
|
feedWithQuietOutput
|
|
|
|
:: CreateProcessRunner
|
|
|
|
-> CreateProcess
|
|
|
|
-> (Handle -> IO a)
|
|
|
|
-> IO a
|
|
|
|
feedWithQuietOutput creator p a = withFile devNull WriteMode $ \nullh -> do
|
|
|
|
let p' = p
|
|
|
|
{ std_in = CreatePipe
|
|
|
|
, std_out = UseHandle nullh
|
|
|
|
, std_err = UseHandle nullh
|
|
|
|
}
|
|
|
|
creator p' $ a . stdinHandle
|
|
|
|
|
2013-12-11 03:19:18 +00:00
|
|
|
devNull :: FilePath
|
2013-06-18 01:26:06 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2013-12-11 03:19:18 +00:00
|
|
|
devNull = "/dev/null"
|
2013-06-18 01:26:06 +00:00
|
|
|
#else
|
2013-12-11 03:19:18 +00:00
|
|
|
devNull = "NUL"
|
2013-06-18 01:26:06 +00:00
|
|
|
#endif
|
2012-10-28 17:51:14 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Extract a desired handle from createProcess's tuple.
|
|
|
|
-- These partial functions are safe as long as createProcess is run
|
|
|
|
-- with appropriate parameters to set up the desired handle.
|
|
|
|
-- Get it wrong and the runtime crash will always happen, so should be
|
|
|
|
-- easily noticed.
|
2012-07-19 04:43:36 +00:00
|
|
|
type HandleExtractor = (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> Handle
|
|
|
|
stdinHandle :: HandleExtractor
|
|
|
|
stdinHandle (Just h, _, _, _) = h
|
|
|
|
stdinHandle _ = error "expected stdinHandle"
|
|
|
|
stdoutHandle :: HandleExtractor
|
|
|
|
stdoutHandle (_, Just h, _, _) = h
|
|
|
|
stdoutHandle _ = error "expected stdoutHandle"
|
|
|
|
stderrHandle :: HandleExtractor
|
|
|
|
stderrHandle (_, _, Just h, _) = h
|
|
|
|
stderrHandle _ = error "expected stderrHandle"
|
2015-04-03 19:33:28 +00:00
|
|
|
ioHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Handle, Handle)
|
|
|
|
ioHandles (Just hin, Just hout, _, _) = (hin, hout)
|
|
|
|
ioHandles _ = error "expected ioHandles"
|
2015-04-03 23:48:56 +00:00
|
|
|
oeHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Handle, Handle)
|
2015-04-03 20:48:30 +00:00
|
|
|
oeHandles (_, Just hout, Just herr, _) = (hout, herr)
|
|
|
|
oeHandles _ = error "expected oeHandles"
|
2012-07-19 04:43:36 +00:00
|
|
|
|
2014-04-12 19:59:34 +00:00
|
|
|
processHandle :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> ProcessHandle
|
|
|
|
processHandle (_, _, _, pid) = pid
|
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Shows the command that a CreateProcess will run.
|
2012-07-19 04:43:36 +00:00
|
|
|
showCmd :: CreateProcess -> String
|
|
|
|
showCmd = go . cmdspec
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
go (ShellCommand s) = s
|
|
|
|
go (RawCommand c ps) = c ++ " " ++ show ps
|
2012-07-19 04:43:36 +00:00
|
|
|
|
2015-05-30 15:27:40 +00:00
|
|
|
-- | Starts an interactive process. Unlike runInteractiveProcess in
|
|
|
|
-- System.Process, stderr is inherited.
|
2013-06-14 21:35:45 +00:00
|
|
|
startInteractiveProcess
|
|
|
|
:: FilePath
|
|
|
|
-> [String]
|
|
|
|
-> Maybe [(String, String)]
|
|
|
|
-> IO (ProcessHandle, Handle, Handle)
|
|
|
|
startInteractiveProcess cmd args environ = do
|
|
|
|
let p = (proc cmd args)
|
|
|
|
{ std_in = CreatePipe
|
|
|
|
, std_out = CreatePipe
|
|
|
|
, std_err = Inherit
|
|
|
|
, env = environ
|
|
|
|
}
|
|
|
|
(Just from, Just to, _, pid) <- createProcess p
|
|
|
|
return (pid, to, from)
|
2013-07-08 18:51:43 +00:00
|
|
|
|
2015-08-13 17:12:44 +00:00
|
|
|
-- | Wrapper around 'System.Process.createProcess' that does debug logging.
|
2013-07-08 18:51:43 +00:00
|
|
|
createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
|
|
|
|
createProcess p = do
|
|
|
|
debugProcess p
|
2015-10-28 04:18:01 +00:00
|
|
|
Utility.Process.Shim.createProcess p
|
2015-08-13 17:12:44 +00:00
|
|
|
|
|
|
|
-- | Debugging trace for a CreateProcess.
|
|
|
|
debugProcess :: CreateProcess -> IO ()
|
2015-09-13 17:39:48 +00:00
|
|
|
debugProcess p = debugM "Utility.Process" $ unwords
|
|
|
|
[ action ++ ":"
|
|
|
|
, showCmd p
|
|
|
|
]
|
2015-08-13 17:12:44 +00:00
|
|
|
where
|
|
|
|
action
|
|
|
|
| piped (std_in p) && piped (std_out p) = "chat"
|
|
|
|
| piped (std_in p) = "feed"
|
|
|
|
| piped (std_out p) = "read"
|
|
|
|
| otherwise = "call"
|
|
|
|
piped Inherit = False
|
|
|
|
piped _ = True
|
|
|
|
|
|
|
|
-- | Wrapper around 'System.Process.waitForProcess' that does debug logging.
|
|
|
|
waitForProcess :: ProcessHandle -> IO ExitCode
|
|
|
|
waitForProcess h = do
|
2015-10-28 04:18:01 +00:00
|
|
|
r <- Utility.Process.Shim.waitForProcess h
|
2015-08-13 17:12:44 +00:00
|
|
|
debugM "Utility.Process" ("process done " ++ show r)
|
|
|
|
return r
|