@@ -137,7 +137,7 @@ import qualified System.Process as P
137137import System.IO (hClose )
138138import System.IO.Error (isPermissionError )
139139import Control.Concurrent (threadDelay )
140- import Control.Concurrent.Async (asyncWithUnmask )
140+ import Control.Concurrent.Async (Async , asyncWithUnmask )
141141import qualified Control.Concurrent.Async as Async
142142import Control.Concurrent.STM (newEmptyTMVarIO , atomically , putTMVar , TMVar , readTMVar , tryReadTMVar , STM , throwSTM , catchSTM )
143143import System.Exit (ExitCode (ExitSuccess , ExitFailure ))
@@ -168,7 +168,7 @@ data Process stdin stdout stderr = Process
168168 , pStdout :: ! stdout
169169 , pStderr :: ! stderr
170170 , pHandle :: ! P. ProcessHandle
171- , pExitCode :: ! (TMVar ExitCode )
171+ , pExitCode :: ! (Async ExitCode )
172172 }
173173instance Show (Process stdin stdout stderr ) where
174174 show p = " Running process: " ++ show (pConfig p)
@@ -222,8 +222,7 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
222222 <*> ssCreate pcStdout pConfig moutH
223223 <*> ssCreate pcStderr pConfig merrH
224224
225- pExitCode <- newEmptyTMVarIO
226- waitingThread <- asyncWithUnmask $ \ unmask -> do
225+ pExitCode <- asyncWithUnmask $ \ unmask -> do
227226 ec <- unmask $ -- make sure the masking state from a bracket isn't inherited
228227 if multiThreadedRuntime
229228 then P. waitForProcess pHandle
@@ -239,12 +238,11 @@ startProcess pConfig'@ProcessConfig {..} = liftIO $ do
239238 Nothing -> loop $ min maxDelay (delay * 2 )
240239 Just ec -> pure ec
241240 loop minDelay
242- atomically $ putTMVar pExitCode ec
243241 return ec
244242
245- let waitForProcess = Async. wait waitingThread :: IO ExitCode
243+ let waitForProcess = Async. wait pExitCode :: IO ExitCode
246244 let pCleanup = pCleanup1 `finally` do
247- _ :: ExitCode <- Async. poll waitingThread >>= \ case
245+ _ :: ExitCode <- Async. poll pExitCode >>= \ case
248246 -- Process already exited, nothing to do
249247 Just r -> either throwIO return r
250248
@@ -596,7 +594,7 @@ waitExitCode = liftIO . atomically . waitExitCodeSTM
596594--
597595-- @since 0.1.0.0
598596waitExitCodeSTM :: Process stdin stdout stderr -> STM ExitCode
599- waitExitCodeSTM = readTMVar . pExitCode
597+ waitExitCodeSTM = Async. waitSTM . pExitCode
600598
601599-- | Check if a process has exited and, if so, return its 'ExitCode'.
602600--
@@ -608,7 +606,9 @@ getExitCode = liftIO . atomically . getExitCodeSTM
608606--
609607-- @since 0.1.0.0
610608getExitCodeSTM :: Process stdin stdout stderr -> STM (Maybe ExitCode )
611- getExitCodeSTM = tryReadTMVar . pExitCode
609+ getExitCodeSTM p = Async. pollSTM (pExitCode p) >>= \ case
610+ Nothing -> return Nothing
611+ Just er -> either throwSTM (return . Just ) er
612612
613613-- | Wait for a process to exit, and ensure that it exited
614614-- successfully. If not, throws an 'ExitCodeException'.
@@ -625,7 +625,7 @@ checkExitCode = liftIO . atomically . checkExitCodeSTM
625625-- @since 0.1.0.0
626626checkExitCodeSTM :: Process stdin stdout stderr -> STM ()
627627checkExitCodeSTM p = do
628- ec <- readTMVar (pExitCode p)
628+ ec <- Async. waitSTM (pExitCode p)
629629 case ec of
630630 ExitSuccess -> return ()
631631 _ -> throwSTM ExitCodeException
0 commit comments