[commit: ghc] master: Add testcase for #11216 (59d3948)

git at git.haskell.org git at git.haskell.org
Mon Dec 14 14:33:25 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/59d3948f02b8a50788f2049014b302bb5b88c5a7/ghc

>---------------------------------------------------------------

commit 59d3948f02b8a50788f2049014b302bb5b88c5a7
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Mon Dec 14 15:14:36 2015 +0100

    Add testcase for #11216


>---------------------------------------------------------------

59d3948f02b8a50788f2049014b302bb5b88c5a7
 testsuite/tests/rebindable/T11216.hs | 6 ++++++
 testsuite/tests/rebindable/all.T     | 1 +
 2 files changed, 7 insertions(+)

diff --git a/testsuite/tests/rebindable/T11216.hs b/testsuite/tests/rebindable/T11216.hs
new file mode 100644
index 0000000..e05feb9
--- /dev/null
+++ b/testsuite/tests/rebindable/T11216.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE RebindableSyntax #-}
+
+module Bug where
+
+foo :: (a, b) -> ()
+foo x | (_,_) <- x = ()
diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T
index b00e721..3ca873e 100644
--- a/testsuite/tests/rebindable/all.T
+++ b/testsuite/tests/rebindable/all.T
@@ -31,3 +31,4 @@ test('T4851', normal, compile, [''])
 
 test('T5908', normal, compile, [''])
 test('T10112', normal, compile, [''])
+test('T11216', [expect_broken(11216)], compile, [''])
\ No newline at end of file



More information about the ghc-commits mailing list