Skip to content
Snippets Groups Projects
Commit 225162f7 authored by Ben Gamari's avatar Ben Gamari :turtle:
Browse files

testsuite: Reduce sensitivity to exception context

parent e1ff4d40
No related branches found
No related tags found
No related merge requests found
......@@ -6,8 +6,7 @@ test('stm050', [extra_run_opts('10000')], compile_and_run, ['-package stm'])
test('stm054', normal, compile_and_run, ['-package stm'])
test('stm055', [exit_code(1), js_broken(22576)], compile_and_run, ['-package stm'])
test('stm056', only_ways(['threaded1','threaded2']),
compile_and_run, ['-package stm'])
test('stm056', only_ways(['threaded1','threaded2']), compile_and_run, ['-package stm'])
test('stm061', normal, compile_and_run, ['-package stm'])
test('T2411', ignore_stdout, compile_and_run, ['-package stm'])
......
......@@ -11,8 +11,9 @@ inc tv = do
writeTVar tv (v + 1)
bad :: MVar () -> IO ()
bad m = do { evaluate (1 `quot` 0); return () }
`finally` putMVar m ()
bad m = handle (\(_ :: SomeException) -> putStrLn "bad" >> putMVar m ()) $ do
evaluate (1 `quot` 0)
return ()
main :: IO ()
main = do
......@@ -22,3 +23,4 @@ main = do
forkOS (bad m)
takeMVar m
threadDelay 100000 -- allow time for the exception to be printed
stm056: divide by zero
bad
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment