{-# LANGUAGE CPP #-} ----------------------------------------------------------------------------- -- -- Misc process handling code for SysTools -- -- (c) The GHC Team 2017 -- ----------------------------------------------------------------------------- module GHC.SysTools.Process ( readCreateProcessWithExitCode' , getGccEnv , runSomething , runSomethingResponseFile , runSomethingFiltered , runSomethingWith ) where import GHC.Prelude import GHC.Utils.Exception import GHC.Utils.Error import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Misc import GHC.Utils.Logger import GHC.Utils.TmpFs import GHC.Utils.CliOption import GHC.Types.SrcLoc ( SrcLoc, mkSrcLoc, mkSrcSpan ) import GHC.Data.FastString import GHC.IO.Encoding #if defined(__IO_MANAGER_WINIO__) import GHC.IO.SubSystem (()) import GHC.IO.Handle.Windows (handleToHANDLE) import GHC.Event.Windows (associateHandle') #endif import Control.Concurrent import Data.Char import System.Exit import System.Environment import System.FilePath import System.IO import System.IO.Error as IO import System.Process -- | Enable process jobs support on Windows if it can be expected to work (e.g. -- @process >= 1.6.9.0@). enableProcessJobs :: CreateProcess -> CreateProcess enableProcessJobs opts = opts { use_process_jobs = True } -- Similar to System.Process.readCreateProcessWithExitCode, but stderr is -- inherited from the parent process, and output to stderr is not captured. readCreateProcessWithExitCode' :: CreateProcess -> IO (ExitCode, String) -- ^ stdout readCreateProcessWithExitCode' proc = do (_, Just outh, _, pid) <- createProcess $ enableProcessJobs $ proc{ std_out = CreatePipe } -- fork off a thread to start consuming the output outMVar <- newEmptyMVar let onError :: SomeException -> IO () onError exc = putMVar outMVar (Left exc) _ <- forkIO $ handle onError $ do output <- hGetContents' outh putMVar outMVar $ Right output -- wait on the output result <- takeMVar outMVar hClose outh output <- case result of Left exc -> throwIO exc Right output -> return output -- wait on the process ex <- waitForProcess pid return (ex, output) -- If the -B