summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorEdward Z. Yang <ezyang@cs.stanford.edu>2017-01-22 20:11:05 (GMT)
committerEdward Z. Yang <ezyang@cs.stanford.edu>2017-01-22 20:11:05 (GMT)
commit9ef237b7ca816edb65126d3e2d0eea649f8c9db7 (patch)
treee44bff84c0719151ebd94fabf7134e31ea2c76cb
parentbbe8956f345d8b2e0d3c068cba9d24569458f704 (diff)
downloadghc-9ef237b7ca816edb65126d3e2d0eea649f8c9db7.zip
ghc-9ef237b7ca816edb65126d3e2d0eea649f8c9db7.tar.gz
ghc-9ef237b7ca816edb65126d3e2d0eea649f8c9db7.tar.bz2
Failing test for #13149.
Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
-rw-r--r--testsuite/tests/backpack/should_compile/T13149.bkp16
-rw-r--r--testsuite/tests/backpack/should_compile/all.T2
2 files changed, 18 insertions, 0 deletions
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, [''])