|
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,51 +242,39 @@ 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
|
266 | 260 | pConfig = clearStreams pConfig'
|
267 | 261 |
|
268 |
| - terminateProcess pHandle = do |
269 |
| - eres <- try $ P.terminateProcess pHandle |
270 |
| - case eres of |
271 |
| - Left e |
272 |
| - -- On Windows, with the single-threaded runtime, it |
273 |
| - -- seems that if a process has already exited, the |
274 |
| - -- call to terminateProcess will fail with a |
275 |
| - -- permission denied error. To work around this, we |
276 |
| - -- catch this exception and then immediately |
277 |
| - -- waitForProcess. There's a chance that there may be |
278 |
| - -- other reasons for this permission error to appear, |
279 |
| - -- in which case this code may allow us to wait too |
280 |
| - -- long for a child process instead of erroring out. |
281 |
| - -- Recommendation: always use the multi-threaded |
282 |
| - -- runtime! |
283 |
| - | isPermissionError e && not multiThreadedRuntime && isWindows -> |
284 |
| - pure () |
285 |
| - | otherwise -> throwIO e |
286 |
| - Right () -> pure () |
| 262 | + terminateProcess :: P.ProcessHandle -> IO () |
| 263 | + terminateProcess p = do |
| 264 | + -- On Windows, with the single-threaded runtime, it seems that if a |
| 265 | + -- process has already exited, the call to terminateProcess will fail |
| 266 | + -- with a permission denied error. To work around this, we ignore this |
| 267 | + -- exception. There's a chance that there may be other reasons for this |
| 268 | + -- permission error to appear, in which case this code may allow us to |
| 269 | + -- wait too long for a child process instead of erroring out on a |
| 270 | + -- subsequent call to `waitForProcess`. |
| 271 | + -- Recommendation: always use the multi-threaded runtime! |
| 272 | + ignorePermissionErrorOnSingleThreadedWindows $ P.terminateProcess p |
| 273 | + |
| 274 | + ignorePermissionErrorOnSingleThreadedWindows :: IO () -> IO () |
| 275 | + ignorePermissionErrorOnSingleThreadedWindows = tryJust (guard . p) >=> either return return |
| 276 | + where |
| 277 | + p e = isPermissionError e && not multiThreadedRuntime && isWindows |
287 | 278 |
|
288 | 279 | foreign import ccall unsafe "rtsSupportsBoundThreads"
|
289 | 280 | multiThreadedRuntime :: Bool
|
|
0 commit comments