[commit: ghc] master: Failing test for #13149. (9ef237b)
git at git.haskell.org
git at git.haskell.org
Sun Jan 22 20:11:17 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/9ef237b7ca816edb65126d3e2d0eea649f8c9db7/ghc
>---------------------------------------------------------------
commit 9ef237b7ca816edb65126d3e2d0eea649f8c9db7
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date: Sun Jan 22 12:11:05 2017 -0800
Failing test for #13149.
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
>---------------------------------------------------------------
9ef237b7ca816edb65126d3e2d0eea649f8c9db7
testsuite/tests/backpack/should_compile/T13149.bkp | 16 ++++++++++++++++
testsuite/tests/backpack/should_compile/all.T | 2 ++
2 files changed, 18 insertions(+)
diff --git a/testsuite/tests/backpack/should_compile/T13149.bkp b/testsuite/tests/backpack/should_compile/T13149.bkp
new file mode 100644
index 0000000..cdaf767
--- /dev/null
+++ b/testsuite/tests/backpack/should_compile/T13149.bkp
@@ -0,0 +1,16 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE Rank2Types #-}
+{-# LANGUAGE TypeInType #-}
+unit p where
+ signature A where
+ import GHC.Types
+ type family F a where
+ F Bool = Type
+ module B where
+ import A
+ foo :: forall (a :: F Bool). a -> a
+ foo x = x
+unit q where
+ dependency p[A=<A>]
+ module C where
+ import B
diff --git a/testsuite/tests/backpack/should_compile/all.T b/testsuite/tests/backpack/should_compile/all.T
index 9897c03..e7834df 100644
--- a/testsuite/tests/backpack/should_compile/all.T
+++ b/testsuite/tests/backpack/should_compile/all.T
@@ -42,3 +42,5 @@ test('bkp47', normal, backpack_compile, [''])
test('bkp48', normal, backpack_compile, [''])
test('bkp49', normal, backpack_compile, [''])
test('bkp50', normal, backpack_compile, [''])
+
+test('T13149', expect_broken(13149), backpack_compile, [''])
More information about the ghc-commits
mailing list