|
1 | 1 | {-# LANGUAGE CPP #-}
|
| 2 | +{-# LANGUAGE LambdaCase #-} |
2 | 3 | {-# LANGUAGE TypeFamilies #-}
|
3 | 4 | {-# LANGUAGE DeriveDataTypeable #-}
|
4 | 5 | {-# LANGUAGE RecordWildCards #-}
|
@@ -130,13 +131,15 @@ module System.Process.Typed
|
130 | 131 | ) where
|
131 | 132 |
|
132 | 133 | import Control.Exception hiding (bracket, finally)
|
| 134 | +import Control.Monad ((>=>), guard) |
133 | 135 | import Control.Monad.IO.Class
|
134 | 136 | import qualified System.Process as P
|
135 | 137 | import System.IO (hClose)
|
136 | 138 | import System.IO.Error (isPermissionError)
|
137 | 139 | 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) |
| 140 | +import Control.Concurrent.Async (asyncWithUnmask) |
| 141 | +import qualified Control.Concurrent.Async as Async |
| 142 | +import Control.Concurrent.STM (newEmptyTMVarIO, atomically, putTMVar, TMVar, readTMVar, tryReadTMVar, STM, throwSTM, catchSTM) |
140 | 143 | import System.Exit (ExitCode (ExitSuccess, ExitFailure))
|
141 | 144 | import System.Process.Typed.Internal
|
142 | 145 | import qualified Data.ByteString.Lazy as L
|
@@ -239,27 +242,18 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
|
239 | 242 | atomically $ putTMVar pExitCode ec
|
240 | 243 | return ec
|
241 | 244 |
|
| 245 | + let waitForProcess = Async.wait waitingThread :: IO ExitCode |
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 |
| 247 | + _ :: ExitCode <- Async.poll waitingThread >>= \ case |
253 | 248 | -- Process already exited, nothing to do
|
254 |
| - Right _ec -> return () |
| 249 | + Just r -> either throwIO return r |
255 | 250 |
|
256 | 251 | -- Process didn't exit yet, let's terminate it and
|
257 | 252 | -- then call waitForProcess ourselves
|
258 |
| - Left _ -> do |
| 253 | + Nothing -> do |
259 | 254 | terminateProcess pHandle
|
260 |
| - ec <- P.waitForProcess pHandle |
261 |
| - success <- atomically $ tryPutTMVar pExitCode ec |
262 |
| - evaluate $ assert success () |
| 255 | + waitForProcess |
| 256 | + return () |
263 | 257 |
|
264 | 258 | return Process {..}
|
265 | 259 | where
|
|
0 commit comments