@@ -7,12 +7,14 @@ import System.Directory (getCurrentDirectory, setCurrentDirectory)
7
7
import System.Process
8
8
import Control.Concurrent
9
9
import Data.Char (isDigit )
10
+ import Data.IORef
10
11
import Data.List (isInfixOf )
11
12
import Data.Maybe (isNothing )
12
13
import System.IO (hClose , openBinaryTempFile , hGetContents )
13
14
import qualified Data.ByteString as S
14
15
import qualified Data.ByteString.Char8 as S8
15
16
import System.Directory (getTemporaryDirectory , removeFile )
17
+ import GHC.Conc.Sync (getUncaughtExceptionHandler , setUncaughtExceptionHandler )
16
18
17
19
ifWindows :: IO () -> IO ()
18
20
ifWindows action
@@ -28,6 +30,26 @@ isWindows = False
28
30
29
31
main :: IO ()
30
32
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
31
53
res <- handle (return . Left . isDoesNotExistError) $ do
32
54
(_, _, _, ph) <- createProcess (proc " definitelydoesnotexist" [] )
33
55
{ close_fds = True
@@ -37,14 +59,14 @@ main = do
37
59
Left True -> return ()
38
60
_ -> error $ show res
39
61
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
42
65
(_, _, _, ph) <- createProcess
43
66
$ modifier $ proc " echo" [" hello" , " world" ]
44
67
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
48
70
49
71
test " vanilla" id
50
72
@@ -54,9 +76,9 @@ main = do
54
76
test " create_new_console" $ \ cp -> cp { create_new_console = True }
55
77
test " new_session" $ \ cp -> cp { new_session = True }
56
78
57
- putStrLn " Testing subdirectories "
58
-
59
- ifWindows $ withCurrentDirectory " exes" $ do
79
+ testSubdirectories :: IO ()
80
+ testSubdirectories = ifWindows $ run " subdirectories " $ do
81
+ withCurrentDirectory " exes" $ do
60
82
res1 <- readCreateProcess (proc " ./echo.bat" [] ) " "
61
83
unless (" parent" `isInfixOf` res1 && not (" child" `isInfixOf` res1)) $ error $
62
84
" echo.bat with cwd failed: " ++ show res1
@@ -65,7 +87,8 @@ main = do
65
87
unless (" child" `isInfixOf` res2 && not (" parent" `isInfixOf` res2)) $ error $
66
88
" echo.bat with cwd failed: " ++ show res2
67
89
68
- putStrLn " Binary handles"
90
+ testBinaryHandles :: IO ()
91
+ testBinaryHandles = run " binary handles" $ do
69
92
tmpDir <- getTemporaryDirectory
70
93
bracket
71
94
(openBinaryTempFile tmpDir " process-binary-test.bin" )
@@ -86,54 +109,147 @@ main = do
86
109
unless (bs == res')
87
110
$ error $ " Unexpected result: " ++ show res'
88
111
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 ->
132
138
if isWindows
133
139
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"
135
248
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
137
253
138
254
withCurrentDirectory :: FilePath -> IO a -> IO a
139
255
withCurrentDirectory new inner = do
0 commit comments