Skip to content

Commit de96ec0

Browse files
authored
Merge pull request #231 from robx/fix-ctlc-wait
Fix waitForProcess not closing process handles with delegate_ctlc
2 parents 240f0c4 + 93fbe58 commit de96ec0

File tree

2 files changed

+185
-63
lines changed

2 files changed

+185
-63
lines changed

System/Process.hs

+15-9
Original file line numberDiff line numberDiff line change
@@ -676,14 +676,16 @@ getCurrentPid =
676676
-- waitForProcess
677677

678678
{- | Waits for the specified process to terminate, and returns its exit code.
679+
On Unix systems, may throw 'UserInterrupt' when using 'delegate_ctlc'.
679680
680681
GHC Note: in order to call @waitForProcess@ without blocking all the
681682
other threads in the system, you must compile the program with
682683
@-threaded@.
683684
684685
Note that it is safe to call @waitForProcess@ for the same process in multiple
685686
threads. When the process ends, threads blocking on this call will wake in
686-
FIFO order.
687+
FIFO order. When using 'delegate_ctlc' and the process is interrupted, only
688+
the first waiting thread will throw 'UserInterrupt'.
687689
688690
(/Since: 1.2.0.0/) On Unix systems, a negative value @'ExitFailure' -/signum/@
689691
indicates that the child was terminated by signal @/signum/@.
@@ -703,15 +705,17 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc _) = lockWaitpid $ do
703705
OpenHandle h -> do
704706
-- don't hold the MVar while we call c_waitForProcess...
705707
e <- waitForProcess' h
706-
e' <- modifyProcessHandle ph $ \p_' ->
708+
(e', was_open) <- modifyProcessHandle ph $ \p_' ->
707709
case p_' of
708-
ClosedHandle e' -> return (p_', e')
710+
ClosedHandle e' -> return (p_', (e', False))
709711
OpenExtHandle{} -> fail "waitForProcess(OpenExtHandle): this cannot happen"
710712
OpenHandle ph' -> do
711713
closePHANDLE ph'
712-
when delegating_ctlc $
713-
endDelegateControlC e
714-
return (ClosedHandle e, e)
714+
return (ClosedHandle e, (e, True))
715+
-- endDelegateControlC after closing the handle, since it
716+
-- may throw UserInterrupt
717+
when (was_open && delegating_ctlc) $
718+
endDelegateControlC e
715719
return e'
716720
#if defined(WINDOWS)
717721
OpenExtHandle h job -> do
@@ -725,9 +729,8 @@ waitForProcess ph@(ProcessHandle _ delegating_ctlc _) = lockWaitpid $ do
725729
OpenExtHandle ph' job' -> do
726730
closePHANDLE ph'
727731
closePHANDLE job'
728-
when delegating_ctlc $
729-
endDelegateControlC e
730732
return (ClosedHandle e, e)
733+
-- omit endDelegateControlC since it's a no-op on Windows
731734
return e'
732735
#else
733736
OpenExtHandle _ _job ->
@@ -761,7 +764,8 @@ still running, 'Nothing' is returned. If the process has exited, then
761764
@'Just' e@ is returned where @e@ is the exit code of the process.
762765
763766
On Unix systems, see 'waitForProcess' for the meaning of exit codes
764-
when the process died as the result of a signal.
767+
when the process died as the result of a signal. May throw
768+
'UserInterrupt' when using 'delegate_ctlc'.
765769
-}
766770

767771
getProcessExitCode :: ProcessHandle -> IO (Maybe ExitCode)
@@ -784,6 +788,8 @@ getProcessExitCode ph@(ProcessHandle _ delegating_ctlc _) = tryLockWaitpid $ do
784788
let e | code == 0 = ExitSuccess
785789
| otherwise = ExitFailure (fromIntegral code)
786790
return (ClosedHandle e, (Just e, True))
791+
-- endDelegateControlC after closing the handle, since it
792+
-- may throw UserInterrupt
787793
case m_e of
788794
Just e | was_open && delegating_ctlc -> endDelegateControlC e
789795
_ -> return ()

test/main.hs

+170-54
Original file line numberDiff line numberDiff line change
@@ -7,12 +7,14 @@ import System.Directory (getCurrentDirectory, setCurrentDirectory)
77
import System.Process
88
import Control.Concurrent
99
import Data.Char (isDigit)
10+
import Data.IORef
1011
import Data.List (isInfixOf)
1112
import Data.Maybe (isNothing)
1213
import System.IO (hClose, openBinaryTempFile, hGetContents)
1314
import qualified Data.ByteString as S
1415
import qualified Data.ByteString.Char8 as S8
1516
import System.Directory (getTemporaryDirectory, removeFile)
17+
import GHC.Conc.Sync (getUncaughtExceptionHandler, setUncaughtExceptionHandler)
1618

1719
ifWindows :: IO () -> IO ()
1820
ifWindows action
@@ -28,6 +30,26 @@ isWindows = False
2830

2931
main :: IO ()
3032
main = do
33+
testDoesNotExist
34+
testModifiers
35+
testSubdirectories
36+
testBinaryHandles
37+
testMultithreadedWait
38+
testInterruptMaskedWait
39+
testGetPid
40+
testReadProcess
41+
testInterruptWith
42+
testDoubleWait
43+
testKillDoubleWait
44+
putStrLn ">>> Tests passed successfully"
45+
46+
run :: String -> IO () -> IO ()
47+
run label test = do
48+
putStrLn $ ">>> Running: " ++ label
49+
test
50+
51+
testDoesNotExist :: IO ()
52+
testDoesNotExist = run "non-existent executable" $ do
3153
res <- handle (return . Left . isDoesNotExistError) $ do
3254
(_, _, _, ph) <- createProcess (proc "definitelydoesnotexist" [])
3355
{ close_fds = True
@@ -37,14 +59,14 @@ main = do
3759
Left True -> return ()
3860
_ -> error $ show res
3961

40-
let test name modifier = do
41-
putStrLn $ "Running test: " ++ name
62+
testModifiers :: IO ()
63+
testModifiers = do
64+
let test name modifier = run ("modifier " ++ name) $ do
4265
(_, _, _, ph) <- createProcess
4366
$ modifier $ proc "echo" ["hello", "world"]
4467
ec <- waitForProcess ph
45-
if ec == ExitSuccess
46-
then putStrLn $ "Success running: " ++ name
47-
else error $ "echo returned: " ++ show ec
68+
unless (ec == ExitSuccess)
69+
$ error $ "echo returned: " ++ show ec
4870

4971
test "vanilla" id
5072

@@ -54,9 +76,9 @@ main = do
5476
test "create_new_console" $ \cp -> cp { create_new_console = True }
5577
test "new_session" $ \cp -> cp { new_session = True }
5678

57-
putStrLn "Testing subdirectories"
58-
59-
ifWindows $ withCurrentDirectory "exes" $ do
79+
testSubdirectories :: IO ()
80+
testSubdirectories = ifWindows $ run "subdirectories" $ do
81+
withCurrentDirectory "exes" $ do
6082
res1 <- readCreateProcess (proc "./echo.bat" []) ""
6183
unless ("parent" `isInfixOf` res1 && not ("child" `isInfixOf` res1)) $ error $
6284
"echo.bat with cwd failed: " ++ show res1
@@ -65,7 +87,8 @@ main = do
6587
unless ("child" `isInfixOf` res2 && not ("parent" `isInfixOf` res2)) $ error $
6688
"echo.bat with cwd failed: " ++ show res2
6789

68-
putStrLn "Binary handles"
90+
testBinaryHandles :: IO ()
91+
testBinaryHandles = run "binary handles" $ do
6992
tmpDir <- getTemporaryDirectory
7093
bracket
7194
(openBinaryTempFile tmpDir "process-binary-test.bin")
@@ -86,54 +109,147 @@ main = do
86109
unless (bs == res')
87110
$ error $ "Unexpected result: " ++ show res'
88111

89-
do -- multithreaded waitForProcess
90-
(_, _, _, p) <- createProcess (proc "sleep" ["0.1"])
91-
me1 <- newEmptyMVar
92-
_ <- forkIO . void $ waitForProcess p >>= putMVar me1
93-
-- check for race / deadlock between waitForProcess and getProcessExitCode
94-
e3 <- getProcessExitCode p
95-
e2 <- waitForProcess p
96-
e1 <- readMVar me1
97-
unless (isNothing e3)
98-
$ error $ "unexpected exit " ++ show e3
99-
unless (e1 == ExitSuccess && e2 == ExitSuccess)
100-
$ error "sleep exited with non-zero exit code!"
101-
102-
do
103-
putStrLn "interrupt masked waitForProcess"
104-
(_, _, _, p) <- createProcess (proc "sleep" ["1.0"])
105-
mec <- newEmptyMVar
106-
tid <- mask_ . forkIO $
107-
(waitForProcess p >>= putMVar mec . Just)
108-
`catchThreadKilled` putMVar mec Nothing
109-
killThread tid
110-
eec <- takeMVar mec
111-
case eec of
112-
Nothing -> return ()
113-
Just ec ->
114-
if isWindows
115-
then putStrLn "FIXME ignoring known failure on Windows"
116-
else error $ "waitForProcess not interrupted: sleep exited with " ++ show ec
117-
118-
putStrLn "testing getPid"
119-
do
120-
(_, Just out, _, p) <-
121-
if isWindows
122-
then createProcess $ (proc "sh" ["-c", "z=$$; cat /proc/$z/winpid"]) {std_out = CreatePipe}
123-
else createProcess $ (proc "sh" ["-c", "echo $$"]) {std_out = CreatePipe}
124-
pid <- getPid p
125-
line <- hGetContents out
126-
putStrLn $ " queried PID: " ++ show pid
127-
putStrLn $ " PID reported by stdout: " ++ show line
128-
_ <- waitForProcess p
129-
hClose out
130-
let numStdoutPid = read (takeWhile isDigit line) :: Pid
131-
unless (Just numStdoutPid == pid) $
112+
testMultithreadedWait :: IO ()
113+
testMultithreadedWait = run "multithreaded wait" $ do
114+
(_, _, _, p) <- createProcess (proc "sleep" ["0.1"])
115+
me1 <- newEmptyMVar
116+
_ <- forkIO . void $ waitForProcess p >>= putMVar me1
117+
-- check for race / deadlock between waitForProcess and getProcessExitCode
118+
e3 <- getProcessExitCode p
119+
e2 <- waitForProcess p
120+
e1 <- readMVar me1
121+
unless (isNothing e3)
122+
$ error $ "unexpected exit " ++ show e3
123+
unless (e1 == ExitSuccess && e2 == ExitSuccess)
124+
$ error "sleep exited with non-zero exit code!"
125+
126+
testInterruptMaskedWait :: IO ()
127+
testInterruptMaskedWait = run "interrupt masked wait" $ do
128+
(_, _, _, p) <- createProcess (proc "sleep" ["1.0"])
129+
mec <- newEmptyMVar
130+
tid <- mask_ . forkIO $
131+
(waitForProcess p >>= putMVar mec . Just)
132+
`catchThreadKilled` putMVar mec Nothing
133+
killThread tid
134+
eec <- takeMVar mec
135+
case eec of
136+
Nothing -> return ()
137+
Just ec ->
132138
if isWindows
133139
then putStrLn "FIXME ignoring known failure on Windows"
134-
else error "subprocess reported unexpected PID"
140+
else error $ "waitForProcess not interrupted: sleep exited with " ++ show ec
141+
142+
testGetPid :: IO ()
143+
testGetPid = run "getPid" $ do
144+
(_, Just out, _, p) <-
145+
if isWindows
146+
then createProcess $ (proc "sh" ["-c", "z=$$; cat /proc/$z/winpid"]) {std_out = CreatePipe}
147+
else createProcess $ (proc "sh" ["-c", "echo $$"]) {std_out = CreatePipe}
148+
pid <- getPid p
149+
line <- hGetContents out
150+
putStrLn $ " queried PID: " ++ show pid
151+
putStrLn $ " PID reported by stdout: " ++ show line
152+
_ <- waitForProcess p
153+
hClose out
154+
let numStdoutPid = read (takeWhile isDigit line) :: Pid
155+
unless (Just numStdoutPid == pid) $
156+
if isWindows
157+
then putStrLn "FIXME ignoring known failure on Windows"
158+
else error "subprocess reported unexpected PID"
159+
160+
testReadProcess :: IO ()
161+
testReadProcess = run "readProcess" $ do
162+
output <- readProcess "echo" ["hello", "world"] ""
163+
unless (output == "hello world\n") $
164+
error $ "unexpected output, got: " ++ output
165+
166+
-- | Test that withCreateProcess doesn't throw exceptions besides
167+
-- the expected UserInterrupt when the child process is interrupted
168+
-- by Ctrl-C.
169+
testInterruptWith :: IO ()
170+
testInterruptWith = unless isWindows $ run "interrupt withCreateProcess" $ do
171+
mpid <- newEmptyMVar
172+
forkIO $ do
173+
pid <- takeMVar mpid
174+
void $ readProcess "kill" ["-INT", show pid] ""
175+
176+
-- collect unhandled exceptions in any threads (specifically
177+
-- the asynchronous 'waitForProcess' call from 'cleanupProcess')
178+
es <- collectExceptions $ do
179+
let sleep = (proc "sleep" ["10"]) { delegate_ctlc = True }
180+
res <- try $ withCreateProcess sleep $ \_ _ _ p -> do
181+
Just pid <- getPid p
182+
putMVar mpid pid
183+
waitForProcess p
184+
unless (res == Left UserInterrupt) $
185+
error $ "expected UserInterrupt, got " ++ show res
186+
187+
unless (null es) $
188+
error $ "uncaught exceptions: " ++ show es
189+
190+
where
191+
collectExceptions action = do
192+
oldHandler <- getUncaughtExceptionHandler
193+
flip finally (setUncaughtExceptionHandler oldHandler) $ do
194+
exceptions <- newIORef ([] :: [SomeException])
195+
setUncaughtExceptionHandler (\e -> atomicModifyIORef exceptions $ \es -> (e:es, ()))
196+
action
197+
threadDelay 1000 -- give some time for threads to finish
198+
readIORef exceptions
199+
200+
-- Test that we can wait without exception twice, if the process exited on its own.
201+
testDoubleWait :: IO ()
202+
testDoubleWait = run "run process, then wait twice" $ do
203+
let sleep = (proc "sleep" ["0"])
204+
(_, _, _, p) <- createProcess sleep
205+
res <- try $ waitForProcess p
206+
case res of
207+
Left e -> error $ "waitForProcess threw: " ++ show (e :: SomeException)
208+
Right ExitSuccess -> return ()
209+
Right exitCode -> error $ "unexpected exit code: " ++ show exitCode
210+
211+
res2 <- try $ waitForProcess p
212+
case res2 of
213+
Left e -> error $ "second waitForProcess threw: " ++ show (e :: SomeException)
214+
Right ExitSuccess -> return ()
215+
Right exitCode -> error $ "unexpected exit code: " ++ show exitCode
216+
217+
-- Test that we can wait without exception twice, if the process was killed.
218+
testKillDoubleWait :: IO ()
219+
testKillDoubleWait = unless isWindows $ do
220+
run "terminate process, then wait twice (delegate_ctlc = False)" $ runTest "TERM" False
221+
run "terminate process, then wait twice (delegate_ctlc = True)" $ runTest "TERM" True
222+
run "interrupt process, then wait twice (delegate_ctlc = False)" $ runTest "INT" False
223+
run "interrupt process, then wait twice (delegate_ctlc = True)" $ runTest "INT" True
224+
where
225+
runTest sig delegate = do
226+
let sleep = (proc "sleep" ["10"])
227+
(_, _, _, p) <- createProcess sleep { delegate_ctlc = delegate }
228+
Just pid <- getPid p
229+
void $ readProcess "kill" ["-" ++ sig, show pid] ""
230+
231+
res <- try $ waitForProcess p
232+
checkFirst sig delegate res
233+
234+
res' <- try $ waitForProcess p
235+
checkSecond sig delegate res'
236+
237+
checkFirst :: String -> Bool -> Either SomeException ExitCode -> IO ()
238+
checkFirst sig delegate res = case (sig, delegate) of
239+
("INT", True) -> case res of
240+
Left e -> case fromException e of
241+
Just UserInterrupt -> putStrLn "result ok"
242+
Nothing -> error $ "expected UserInterrupt, got " ++ show e
243+
Right _ -> error $ "expected exception, got " ++ show res
244+
_ -> case res of
245+
Left e -> error $ "waitForProcess threw: " ++ show e
246+
Right ExitSuccess -> error "expected failure"
247+
_ -> putStrLn "result ok"
135248

136-
putStrLn "Tests passed successfully"
249+
checkSecond :: String -> Bool -> Either SomeException ExitCode -> IO ()
250+
checkSecond sig delegate res = case (sig, delegate) of
251+
("INT", True) -> checkFirst "INT" False res
252+
_ -> checkFirst sig delegate res
137253

138254
withCurrentDirectory :: FilePath -> IO a -> IO a
139255
withCurrentDirectory new inner = do

0 commit comments

Comments
 (0)