[commit: ghc] master: Test #9632 in dependent/should_compile/T9632 (05fe546)
git at git.haskell.org
git at git.haskell.org
Mon Dec 14 20:59:48 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/05fe5463143769a2e84d5e3508a829792d5a1817/ghc
>---------------------------------------------------------------
commit 05fe5463143769a2e84d5e3508a829792d5a1817
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Mon Dec 14 15:59:21 2015 -0500
Test #9632 in dependent/should_compile/T9632
>---------------------------------------------------------------
05fe5463143769a2e84d5e3508a829792d5a1817
testsuite/tests/dependent/should_compile/T9632.hs | 11 +++++++++++
testsuite/tests/dependent/should_compile/all.T | 1 +
2 files changed, 12 insertions(+)
diff --git a/testsuite/tests/dependent/should_compile/T9632.hs b/testsuite/tests/dependent/should_compile/T9632.hs
new file mode 100644
index 0000000..bea468f
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T9632.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TypeInType #-}
+
+module T9632 where
+
+import Data.Kind
+
+data B = T | F
+data P :: B -> *
+
+type B' = B
+data P' :: B' -> *
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index 1724ff6..e1e064a 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -9,3 +9,4 @@ test('KindLevels', normal, compile, [''])
test('RaeBlogPost', normal, compile, [''])
test('mkGADTVars', normal, compile, [''])
test('TypeLevelVec',normal,compile, [''])
+test('T9632', normal, compile, [''])
More information about the ghc-commits
mailing list