11{-# LANGUAGE CPP #-}
2+ {-# LANGUAGE LambdaCase #-}
23{-# LANGUAGE TypeFamilies #-}
34{-# LANGUAGE DeriveDataTypeable #-}
45{-# LANGUAGE RecordWildCards #-}
@@ -135,8 +136,9 @@ import qualified System.Process as P
135136import System.IO (hClose )
136137import System.IO.Error (isPermissionError )
137138import Control.Concurrent (threadDelay )
138- import Control.Concurrent.Async (asyncWithUnmask , cancel , waitCatch )
139- import Control.Concurrent.STM (newEmptyTMVarIO , atomically , putTMVar , TMVar , readTMVar , tryReadTMVar , STM , tryPutTMVar , throwSTM , catchSTM )
139+ import Control.Concurrent.Async (asyncWithUnmask )
140+ import qualified Control.Concurrent.Async as Async
141+ import Control.Concurrent.STM (newEmptyTMVarIO , atomically , putTMVar , TMVar , readTMVar , tryReadTMVar , STM , throwSTM , catchSTM )
140142import System.Exit (ExitCode (ExitSuccess , ExitFailure ))
141143import System.Process.Typed.Internal
142144import qualified Data.ByteString.Lazy as L
@@ -239,23 +241,12 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
239241 atomically $ putTMVar pExitCode ec
240242 return ec
241243
244+ let waitForProcess = Async. wait waitingThread :: IO ExitCode
245+
242246 let pCleanup = pCleanup1 `finally` do
243- -- First: stop calling waitForProcess, so that we can
244- -- avoid race conditions where the process is removed from
245- -- the system process table while we're trying to
246- -- terminate it.
247- cancel waitingThread
248-
249- -- Now check if the process had already exited
250- eec <- waitCatch waitingThread
251-
252- case eec of
253- -- Process already exited, nothing to do
254- Right _ec -> return ()
255-
256- -- Process didn't exit yet, let's terminate it and
257- -- then call waitForProcess ourselves
258- Left _ -> do
247+ _ :: ExitCode <- Async. poll waitingThread >>= \ case
248+ Just r -> either throwIO return r
249+ Nothing -> do
259250 eres <- try $ P. terminateProcess pHandle
260251 ec <-
261252 case eres of
@@ -272,11 +263,11 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
272263 -- Recommendation: always use the multi-threaded
273264 -- runtime!
274265 | isPermissionError e && not multiThreadedRuntime && isWindows ->
275- P. waitForProcess pHandle
266+ waitForProcess
276267 | otherwise -> throwIO e
277- Right () -> P. waitForProcess pHandle
278- success <- atomically $ tryPutTMVar pExitCode ec
279- evaluate $ assert success ()
268+ Right () -> waitForProcess
269+ return ec
270+ return ()
280271
281272 return Process {.. }
282273 where
0 commit comments