{- System.Process enhancements, including additional ways of running
 - processes, and logging.
 -
 - Copyright 2012-2015 Joey Hess <id@joeyh.name>
 -
 - License: BSD-2-clause
 -}

{-# LANGUAGE CPP, Rank2Types #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}

module Utility.Process (
	module X,
	CreateProcess(..),
	StdHandle(..),
	readProcess,
	readProcess',
	readProcessEnv,
	writeReadProcessEnv,
	forceSuccessProcess,
	forceSuccessProcess',
	checkSuccessProcess,
	ignoreFailureProcess,
	createProcessSuccess,
	createProcessChecked,
	createBackgroundProcess,
	withHandle,
	withIOHandles,
	withOEHandles,
	withNullHandle,
	withQuietOutput,
	feedWithQuietOutput,
	createProcess,
	waitForProcess,
	startInteractiveProcess,
	stdinHandle,
	stdoutHandle,
	stderrHandle,
	ioHandles,
	processHandle,
	devNull,
) where

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

import System.Exit
import System.IO
import System.Log.Logger
import Control.Concurrent
import qualified Control.Exception as E
import Control.Monad

type CreateProcessRunner = forall a. CreateProcess -> ((Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a) -> IO a

data StdHandle = StdinHandle | StdoutHandle | StderrHandle
	deriving (StdHandle -> StdHandle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StdHandle -> StdHandle -> Bool
$c/= :: StdHandle -> StdHandle -> Bool
== :: StdHandle -> StdHandle -> Bool
$c== :: StdHandle -> StdHandle -> Bool
Eq)

-- | Normally, when reading from a process, it does not need to be fed any
-- standard input.
readProcess :: FilePath	-> [String] -> IO String
readProcess :: FilePath -> [FilePath] -> IO FilePath
readProcess FilePath
cmd [FilePath]
args = FilePath
-> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO FilePath
readProcessEnv FilePath
cmd [FilePath]
args forall a. Maybe a
Nothing

readProcessEnv :: FilePath -> [String] -> Maybe [(String, String)] -> IO String
readProcessEnv :: FilePath
-> [FilePath] -> Maybe [(FilePath, FilePath)] -> IO FilePath
readProcessEnv FilePath
cmd [FilePath]
args Maybe [(FilePath, FilePath)]
environ = CreateProcess -> IO FilePath
readProcess' CreateProcess
p
  where
	p :: CreateProcess
p = (FilePath -> [FilePath] -> CreateProcess
proc FilePath
cmd [FilePath]
args)
		{ std_out :: StdStream
std_out = StdStream
CreatePipe
		, env :: Maybe [(FilePath, FilePath)]
env = Maybe [(FilePath, FilePath)]
environ
		}

readProcess' :: CreateProcess -> IO String
readProcess' :: CreateProcess -> IO FilePath
readProcess' CreateProcess
p = forall a.
StdHandle
-> CreateProcessRunner -> CreateProcess -> (Handle -> IO a) -> IO a
withHandle StdHandle
StdoutHandle CreateProcessRunner
createProcessSuccess CreateProcess
p forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
	FilePath
output  <- Handle -> IO FilePath
hGetContentsStrict Handle
h
	Handle -> IO ()
hClose Handle
h
	forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
output

-- | Runs an action to write to a process on its stdin, 
-- returns its output, and also allows specifying the environment.
writeReadProcessEnv
	:: FilePath
	-> [String]
	-> Maybe [(String, String)]
	-> (Maybe (Handle -> IO ()))
	-> (Maybe (Handle -> IO ()))
	-> IO String
writeReadProcessEnv :: FilePath
-> [FilePath]
-> Maybe [(FilePath, FilePath)]
-> Maybe (Handle -> IO ())
-> Maybe (Handle -> IO ())
-> IO FilePath
writeReadProcessEnv FilePath
cmd [FilePath]
args Maybe [(FilePath, FilePath)]
environ Maybe (Handle -> IO ())
writestdin Maybe (Handle -> IO ())
adjusthandle = do
	(Just Handle
inh, Just Handle
outh, Maybe Handle
_, ProcessHandle
pid) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess CreateProcess
p

	forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return ()) (\Handle -> IO ()
a -> Handle -> IO ()
a Handle
inh) Maybe (Handle -> IO ())
adjusthandle
	forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return ()) (\Handle -> IO ()
a -> Handle -> IO ()
a Handle
outh) Maybe (Handle -> IO ())
adjusthandle

	-- fork off a thread to start consuming the output
	FilePath
output  <- Handle -> IO FilePath
hGetContents Handle
outh
	MVar ()
outMVar <- forall a. IO (MVar a)
newEmptyMVar
	ThreadId
_ <- IO () -> IO ThreadId
forkIO forall a b. (a -> b) -> a -> b
$ forall a. a -> IO a
E.evaluate (forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
output) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. MVar a -> a -> IO ()
putMVar MVar ()
outMVar ()

	-- now write and flush any input
	forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return ()) (\Handle -> IO ()
a -> Handle -> IO ()
a Handle
inh forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> IO ()
hFlush Handle
inh) Maybe (Handle -> IO ())
writestdin
	Handle -> IO ()
hClose Handle
inh -- done with stdin

	-- wait on the output
	forall a. MVar a -> IO a
takeMVar MVar ()
outMVar
	Handle -> IO ()
hClose Handle
outh

	-- wait on the process
	CreateProcess -> ProcessHandle -> IO ()
forceSuccessProcess CreateProcess
p ProcessHandle
pid

	forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
output

  where
	p :: CreateProcess
p = (FilePath -> [FilePath] -> CreateProcess
proc FilePath
cmd [FilePath]
args)
		{ std_in :: StdStream
std_in = StdStream
CreatePipe
		, std_out :: StdStream
std_out = StdStream
CreatePipe
		, std_err :: StdStream
std_err = StdStream
Inherit
		, env :: Maybe [(FilePath, FilePath)]
env = Maybe [(FilePath, FilePath)]
environ
		}

-- | Waits for a ProcessHandle, and throws an IOError if the process
-- did not exit successfully.
forceSuccessProcess :: CreateProcess -> ProcessHandle -> IO ()
forceSuccessProcess :: CreateProcess -> ProcessHandle -> IO ()
forceSuccessProcess CreateProcess
p ProcessHandle
pid = ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CreateProcess -> ExitCode -> IO ()
forceSuccessProcess' CreateProcess
p

forceSuccessProcess' :: CreateProcess -> ExitCode -> IO ()
forceSuccessProcess' :: CreateProcess -> ExitCode -> IO ()
forceSuccessProcess' CreateProcess
_ ExitCode
ExitSuccess = forall (m :: * -> *) a. Monad m => a -> m a
return ()
forceSuccessProcess' CreateProcess
p (ExitFailure Int
n) = forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall a b. (a -> b) -> a -> b
$
	CreateProcess -> FilePath
showCmd CreateProcess
p forall a. [a] -> [a] -> [a]
++ FilePath
" exited " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Int
n

-- | 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. -}
checkSuccessProcess :: ProcessHandle -> IO Bool
checkSuccessProcess :: ProcessHandle -> IO Bool
checkSuccessProcess ProcessHandle
pid = do
	ExitCode
code <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid
	forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ExitCode
code forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess

ignoreFailureProcess :: ProcessHandle -> IO Bool
ignoreFailureProcess :: ProcessHandle -> IO Bool
ignoreFailureProcess ProcessHandle
pid = do
	forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
pid
	forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True

-- | Runs createProcess, then an action on its handles, and then
-- forceSuccessProcess.
createProcessSuccess :: CreateProcessRunner
createProcessSuccess :: CreateProcessRunner
createProcessSuccess CreateProcess
p (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a
a = forall b. (ProcessHandle -> IO b) -> CreateProcessRunner
createProcessChecked (CreateProcess -> ProcessHandle -> IO ()
forceSuccessProcess CreateProcess
p) CreateProcess
p (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a
a

-- | Runs createProcess, then an action on its handles, and then
-- a checker action on its exit code, which must wait for the process.
createProcessChecked :: (ProcessHandle -> IO b) -> CreateProcessRunner
createProcessChecked :: forall b. (ProcessHandle -> IO b) -> CreateProcessRunner
createProcessChecked ProcessHandle -> IO b
checker CreateProcess
p (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a
a = do
	t :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
t@(Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
pid) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess CreateProcess
p
	Either SomeException a
r <- forall (m :: * -> *) a.
MonadCatch m =>
m a -> m (Either SomeException a)
tryNonAsync forall a b. (a -> b) -> a -> b
$ (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a
a (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
t
	b
_ <- ProcessHandle -> IO b
checker ProcessHandle
pid
	forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a e. Exception e => e -> a
E.throw forall (m :: * -> *) a. Monad m => a -> m a
return Either SomeException a
r

-- | Leaves the process running, suitable for lazy streaming.
-- Note: Zombies will result, and must be waited on.
createBackgroundProcess :: CreateProcessRunner
createBackgroundProcess :: CreateProcessRunner
createBackgroundProcess CreateProcess
p (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a
a = (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> IO a
a forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess CreateProcess
p

-- | 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.
withHandle
	:: StdHandle
	-> CreateProcessRunner
	-> CreateProcess
	-> (Handle -> IO a)
	-> IO a
withHandle :: forall a.
StdHandle
-> CreateProcessRunner -> CreateProcess -> (Handle -> IO a) -> IO a
withHandle StdHandle
h CreateProcessRunner
creator CreateProcess
p Handle -> IO a
a = CreateProcessRunner
creator CreateProcess
p' forall a b. (a -> b) -> a -> b
$ Handle -> IO a
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. HandleExtractor
select
  where
	base :: CreateProcess
base = CreateProcess
p
		{ std_in :: StdStream
std_in = StdStream
Inherit
		, std_out :: StdStream
std_out = StdStream
Inherit
		, std_err :: StdStream
std_err = StdStream
Inherit
		}
	(HandleExtractor
select, CreateProcess
p') = case StdHandle
h of
		StdHandle
StdinHandle -> (HandleExtractor
stdinHandle, CreateProcess
base { std_in :: StdStream
std_in = StdStream
CreatePipe })
		StdHandle
StdoutHandle -> (HandleExtractor
stdoutHandle, CreateProcess
base { std_out :: StdStream
std_out = StdStream
CreatePipe })
		StdHandle
StderrHandle -> (HandleExtractor
stderrHandle, CreateProcess
base { std_err :: StdStream
std_err = StdStream
CreatePipe })

-- | Like withHandle, but passes (stdin, stdout) handles to the action.
withIOHandles
	:: CreateProcessRunner
	-> CreateProcess
	-> ((Handle, Handle) -> IO a)
	-> IO a
withIOHandles :: forall a.
CreateProcessRunner
-> CreateProcess -> ((Handle, Handle) -> IO a) -> IO a
withIOHandles CreateProcessRunner
creator CreateProcess
p (Handle, Handle) -> IO a
a = CreateProcessRunner
creator CreateProcess
p' forall a b. (a -> b) -> a -> b
$ (Handle, Handle) -> IO a
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> (Handle, Handle)
ioHandles
  where
	p' :: CreateProcess
p' = CreateProcess
p
		{ std_in :: StdStream
std_in = StdStream
CreatePipe
		, std_out :: StdStream
std_out = StdStream
CreatePipe
		, std_err :: StdStream
std_err = StdStream
Inherit
		}

-- | Like withHandle, but passes (stdout, stderr) handles to the action.
withOEHandles
	:: CreateProcessRunner
	-> CreateProcess
	-> ((Handle, Handle) -> IO a)
	-> IO a
withOEHandles :: forall a.
CreateProcessRunner
-> CreateProcess -> ((Handle, Handle) -> IO a) -> IO a
withOEHandles CreateProcessRunner
creator CreateProcess
p (Handle, Handle) -> IO a
a = CreateProcessRunner
creator CreateProcess
p' forall a b. (a -> b) -> a -> b
$ (Handle, Handle) -> IO a
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> (Handle, Handle)
oeHandles
  where
	p' :: CreateProcess
p' = CreateProcess
p
		{ std_in :: StdStream
std_in = StdStream
Inherit
		, std_out :: StdStream
std_out = StdStream
CreatePipe
		, std_err :: StdStream
std_err = StdStream
CreatePipe
		}

withNullHandle :: (Handle -> IO a) -> IO a
withNullHandle :: forall a. (Handle -> IO a) -> IO a
withNullHandle = forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
devNull IOMode
WriteMode

-- | Forces the CreateProcessRunner to run quietly;
-- both stdout and stderr are discarded.
withQuietOutput
	:: CreateProcessRunner
	-> CreateProcess
	-> IO ()
withQuietOutput :: CreateProcessRunner -> CreateProcess -> IO ()
withQuietOutput CreateProcessRunner
creator CreateProcess
p = forall a. (Handle -> IO a) -> IO a
withNullHandle forall a b. (a -> b) -> a -> b
$ \Handle
nullh -> do
	let p' :: CreateProcess
p' = CreateProcess
p
		{ std_out :: StdStream
std_out = Handle -> StdStream
UseHandle Handle
nullh
		, std_err :: StdStream
std_err = Handle -> StdStream
UseHandle Handle
nullh
		}
	CreateProcessRunner
creator CreateProcess
p' forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Stdout and stderr are discarded, while the process is fed stdin
-- from the handle.
feedWithQuietOutput
	:: CreateProcessRunner
	-> CreateProcess
	-> (Handle -> IO a)
	-> IO a
feedWithQuietOutput :: forall a.
CreateProcessRunner -> CreateProcess -> (Handle -> IO a) -> IO a
feedWithQuietOutput CreateProcessRunner
creator CreateProcess
p Handle -> IO a
a = forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
devNull IOMode
WriteMode forall a b. (a -> b) -> a -> b
$ \Handle
nullh -> do
	let p' :: CreateProcess
p' = CreateProcess
p
		{ std_in :: StdStream
std_in = StdStream
CreatePipe
		, std_out :: StdStream
std_out = Handle -> StdStream
UseHandle Handle
nullh
		, std_err :: StdStream
std_err = Handle -> StdStream
UseHandle Handle
nullh
		}
	CreateProcessRunner
creator CreateProcess
p' forall a b. (a -> b) -> a -> b
$ Handle -> IO a
a forall b c a. (b -> c) -> (a -> b) -> a -> c
. HandleExtractor
stdinHandle

devNull :: FilePath
#ifndef mingw32_HOST_OS
devNull :: FilePath
devNull = FilePath
"/dev/null"
#else
-- Use device namespace to prevent GHC from rewriting path
devNull = "\\\\.\\NUL"
#endif

-- | 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.
type HandleExtractor = (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> Handle
stdinHandle :: HandleExtractor
stdinHandle :: HandleExtractor
stdinHandle (Just Handle
h, Maybe Handle
_, Maybe Handle
_, ProcessHandle
_) = Handle
h
stdinHandle (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
_ = forall a. HasCallStack => FilePath -> a
error FilePath
"expected stdinHandle"
stdoutHandle :: HandleExtractor
stdoutHandle :: HandleExtractor
stdoutHandle (Maybe Handle
_, Just Handle
h, Maybe Handle
_, ProcessHandle
_) = Handle
h
stdoutHandle (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
_ = forall a. HasCallStack => FilePath -> a
error FilePath
"expected stdoutHandle"
stderrHandle :: HandleExtractor
stderrHandle :: HandleExtractor
stderrHandle (Maybe Handle
_, Maybe Handle
_, Just Handle
h, ProcessHandle
_) = Handle
h
stderrHandle (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
_ = forall a. HasCallStack => FilePath -> a
error FilePath
"expected stderrHandle"
ioHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Handle, Handle)
ioHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> (Handle, Handle)
ioHandles (Just Handle
hin, Just Handle
hout, Maybe Handle
_, ProcessHandle
_) = (Handle
hin, Handle
hout)
ioHandles (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
_ = forall a. HasCallStack => FilePath -> a
error FilePath
"expected ioHandles"
oeHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> (Handle, Handle)
oeHandles :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> (Handle, Handle)
oeHandles (Maybe Handle
_, Just Handle
hout, Just Handle
herr, ProcessHandle
_) = (Handle
hout, Handle
herr)
oeHandles (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
_ = forall a. HasCallStack => FilePath -> a
error FilePath
"expected oeHandles"

processHandle :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) -> ProcessHandle
processHandle :: (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-> ProcessHandle
processHandle (Maybe Handle
_, Maybe Handle
_, Maybe Handle
_, ProcessHandle
pid) = ProcessHandle
pid

-- | Shows the command that a CreateProcess will run.
showCmd :: CreateProcess -> String
showCmd :: CreateProcess -> FilePath
showCmd = CmdSpec -> FilePath
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateProcess -> CmdSpec
cmdspec
  where
	go :: CmdSpec -> FilePath
go (ShellCommand FilePath
s) = FilePath
s
	go (RawCommand FilePath
c [FilePath]
ps) = FilePath
c forall a. [a] -> [a] -> [a]
++ FilePath
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show [FilePath]
ps

-- | Starts an interactive process. Unlike runInteractiveProcess in
-- System.Process, stderr is inherited.
startInteractiveProcess
	:: FilePath
	-> [String]
	-> Maybe [(String, String)]
	-> IO (ProcessHandle, Handle, Handle)
startInteractiveProcess :: FilePath
-> [FilePath]
-> Maybe [(FilePath, FilePath)]
-> IO (ProcessHandle, Handle, Handle)
startInteractiveProcess FilePath
cmd [FilePath]
args Maybe [(FilePath, FilePath)]
environ = do
	let p :: CreateProcess
p = (FilePath -> [FilePath] -> CreateProcess
proc FilePath
cmd [FilePath]
args)
		{ std_in :: StdStream
std_in = StdStream
CreatePipe
		, std_out :: StdStream
std_out = StdStream
CreatePipe
		, std_err :: StdStream
std_err = StdStream
Inherit
		, env :: Maybe [(FilePath, FilePath)]
env = Maybe [(FilePath, FilePath)]
environ
		}
	(Just Handle
from, Just Handle
to, Maybe Handle
_, ProcessHandle
pid) <- CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess CreateProcess
p
	forall (m :: * -> *) a. Monad m => a -> m a
return (ProcessHandle
pid, Handle
to, Handle
from)

-- | Wrapper around 'System.Process.createProcess' that does debug logging.
createProcess :: CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess :: CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
createProcess CreateProcess
p = do
	CreateProcess -> IO ()
debugProcess CreateProcess
p
	CreateProcess
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
Utility.Process.Shim.createProcess CreateProcess
p

-- | Debugging trace for a CreateProcess.
debugProcess :: CreateProcess -> IO ()
debugProcess :: CreateProcess -> IO ()
debugProcess CreateProcess
p = FilePath -> FilePath -> IO ()
debugM FilePath
"Utility.Process" forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
unwords
	[ FilePath
action forall a. [a] -> [a] -> [a]
++ FilePath
":"
	, CreateProcess -> FilePath
showCmd CreateProcess
p
	]
  where
	action :: FilePath
action
		| StdStream -> Bool
piped (CreateProcess -> StdStream
std_in CreateProcess
p) Bool -> Bool -> Bool
&& StdStream -> Bool
piped (CreateProcess -> StdStream
std_out CreateProcess
p) = FilePath
"chat"
		| StdStream -> Bool
piped (CreateProcess -> StdStream
std_in CreateProcess
p)                      = FilePath
"feed"
		| StdStream -> Bool
piped (CreateProcess -> StdStream
std_out CreateProcess
p)                     = FilePath
"read"
		| Bool
otherwise                             = FilePath
"call"
	piped :: StdStream -> Bool
piped StdStream
Inherit = Bool
False
	piped StdStream
_ = Bool
True

-- | Wrapper around 'System.Process.waitForProcess' that does debug logging.
waitForProcess ::  ProcessHandle -> IO ExitCode
waitForProcess :: ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
h = do
	ExitCode
r <- ProcessHandle -> IO ExitCode
Utility.Process.Shim.waitForProcess ProcessHandle
h
	FilePath -> FilePath -> IO ()
debugM FilePath
"Utility.Process" (FilePath
"process done " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show ExitCode
r)
	forall (m :: * -> *) a. Monad m => a -> m a
return ExitCode
r