[commit: ghc] wip/sgraf-no-exnstr: Add regression test for #14171 (e9c6424)
git at git.haskell.org
git at git.haskell.org
Fri Feb 1 05:55:29 UTC 2019
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/sgraf-no-exnstr
Link : http://ghc.haskell.org/trac/ghc/changeset/e9c6424275946d6373c65c28309f51ac72b9bbc8/ghc
>---------------------------------------------------------------
commit e9c6424275946d6373c65c28309f51ac72b9bbc8
Author: Sebastian Graf <sebastian.graf at kit.edu>
Date: Thu Jan 31 18:00:35 2019 +0100
Add regression test for #14171
>---------------------------------------------------------------
e9c6424275946d6373c65c28309f51ac72b9bbc8
testsuite/tests/stranal/should_run/T14171.hs | 16 ++++++++++++++++
testsuite/tests/stranal/should_run/all.T | 1 +
2 files changed, 17 insertions(+)
diff --git a/testsuite/tests/stranal/should_run/T14171.hs b/testsuite/tests/stranal/should_run/T14171.hs
new file mode 100644
index 0000000..edee083
--- /dev/null
+++ b/testsuite/tests/stranal/should_run/T14171.hs
@@ -0,0 +1,16 @@
+module Main where
+
+import Control.Concurrent.STM
+import Control.Concurrent.STM.TVar
+
+chkLoop :: TVar String -> STM ()
+chkLoop v = do
+ val <- readTVar v
+ if (length val == 2) then retry else return ()
+
+main :: IO ()
+main = do
+ v <- newTVarIO "hi"
+ atomically $ do
+ chkLoop v `orElse` return ()
+ error "you're expected to see this"
diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T
index f33adac..278b91b 100644
--- a/testsuite/tests/stranal/should_run/all.T
+++ b/testsuite/tests/stranal/should_run/all.T
@@ -20,5 +20,6 @@ test('T11555a', normal, compile_and_run, [''])
test('T12368', exit_code(1), compile_and_run, [''])
test('T12368a', exit_code(1), compile_and_run, [''])
test('T13380', [expect_broken(13380), exit_code(1)], compile_and_run, [''])
+test('T14171', [expect_broken(14171), exit_code(1)], compile_and_run, [''])
test('T14290', normal, compile_and_run, [''])
test('T14285', normal, multimod_compile_and_run, ['T14285', ''])
More information about the ghc-commits
mailing list