1
1
{-# LANGUAGE CPP #-}
2
+ {-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE TypeFamilies #-}
3
4
{-# LANGUAGE DeriveDataTypeable #-}
4
5
{-# LANGUAGE RecordWildCards #-}
@@ -135,8 +136,9 @@ import qualified System.Process as P
135
136
import System.IO (hClose )
136
137
import System.IO.Error (isPermissionError )
137
138
import 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 )
140
142
import System.Exit (ExitCode (ExitSuccess , ExitFailure ))
141
143
import System.Process.Typed.Internal
142
144
import qualified Data.ByteString.Lazy as L
@@ -239,23 +241,12 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
239
241
atomically $ putTMVar pExitCode ec
240
242
return ec
241
243
244
+ let waitForProcess = Async. wait waitingThread :: IO ExitCode
245
+
242
246
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
259
250
eres <- try $ P. terminateProcess pHandle
260
251
ec <-
261
252
case eres of
@@ -272,11 +263,11 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
272
263
-- Recommendation: always use the multi-threaded
273
264
-- runtime!
274
265
| isPermissionError e && not multiThreadedRuntime && isWindows ->
275
- P. waitForProcess pHandle
266
+ waitForProcess
276
267
| 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 ()
280
271
281
272
return Process {.. }
282
273
where
0 commit comments