Skip to content

Commit 46ddc7b

Browse files
committed
Ensure that waitForProcess is never called multiple times (fixes #69)
1 parent 971f04a commit 46ddc7b

File tree

4 files changed

+29
-23
lines changed

4 files changed

+29
-23
lines changed

ChangeLog.md

+5
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,10 @@
11
# ChangeLog for typed-process
22

3+
## 0.2.12.0
4+
5+
* Ensure that `waitForProcess` is never called multiple times
6+
[#70](https://github.com/fpco/typed-process/pull/70)
7+
38
## 0.2.11.0
49

510
* Expose more from `System.Process.Typed.Internal`

package.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
name: typed-process
2-
version: 0.2.11.0
2+
version: 0.2.12.0
33
synopsis: Run external processes, with strong typing of streams
44
description: Please see the tutorial at <https://github.com/fpco/typed-process#readme>
55
category: System

src/System/Process/Typed.hs

+13-22
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
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
135136
import System.IO (hClose)
136137
import System.IO.Error (isPermissionError)
137138
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)
140142
import System.Exit (ExitCode (ExitSuccess, ExitFailure))
141143
import System.Process.Typed.Internal
142144
import 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

test/System/Process/TypedSpec.hs

+10
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module System.Process.TypedSpec (spec) where
55
import System.Process.Typed
66
import System.Process.Typed.Internal
77
import System.IO
8+
import Control.Exception
89
import Control.Concurrent.Async (Concurrently (..))
910
import Control.Concurrent.STM (atomically)
1011
import Test.Hspec
@@ -170,3 +171,12 @@ spec = do
170171
it "empty param are showed" $
171172
let expected = "Raw command: podman exec --detach-keys \"\" ctx bash\n"
172173
in show (proc "podman" ["exec", "--detach-keys", "", "ctx", "bash"]) `shouldBe` expected
174+
175+
describe "stopProcess" $ do
176+
it "never calls waitForProcess multiple times (fix for #69)" $ do
177+
-- https://github.com/fpco/typed-process/issues/70
178+
let config = setStdout createPipe (proc "echo" ["foo"])
179+
withProcessWait config $ \p -> do
180+
_ <- S.hGetContents (getStdout p)
181+
throwIO DivideByZero
182+
`shouldThrow` (== DivideByZero)

0 commit comments

Comments
 (0)