[commit: testsuite] master: Add a test for #8035; patch from errge (e9a3f72)
Ian Lynagh
igloo at earth.li
Sun Jul 7 20:37:58 CEST 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
https://github.com/ghc/testsuite/commit/e9a3f72c7f86b7de74b759c109889222475e1e6f
>---------------------------------------------------------------
commit e9a3f72c7f86b7de74b759c109889222475e1e6f
Author: Ian Lynagh <ian at well-typed.com>
Date: Sun Jul 7 19:07:16 2013 +0100
Add a test for #8035; patch from errge
>---------------------------------------------------------------
tests/rts/T8035.hs | 10 ++++++++++
tests/rts/all.T | 1 +
2 files changed, 11 insertions(+), 0 deletions(-)
diff --git a/tests/rts/T8035.hs b/tests/rts/T8035.hs
new file mode 100644
index 0000000..73afc7f
--- /dev/null
+++ b/tests/rts/T8035.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+
+import Control.Exception
+import Control.Monad
+import GHC.Conc
+
+main = join $ atomically $ do
+ catchSTM
+ (throwSTM ThreadKilled `orElse` return (putStrLn "wtf"))
+ (\(e::SomeException) -> return (putStrLn "ok"))
diff --git a/tests/rts/all.T b/tests/rts/all.T
index 9a7f2fe..46c368f 100644
--- a/tests/rts/all.T
+++ b/tests/rts/all.T
@@ -179,3 +179,4 @@ test('T7919', [extra_clean(['T7919A.o','T7919A.hi',
when(fast(),skip) ],
compile_and_run, [''])
+test('T8035', normal, compile_and_run, [''])
More information about the ghc-commits
mailing list