[commit: ghc] master: Add regression test for #11964 (a13adcf)
git at git.haskell.org
git at git.haskell.org
Fri May 12 13:08:20 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a13adcf8cfc650979a80101c0879c11a507734f9/ghc
>---------------------------------------------------------------
commit a13adcf8cfc650979a80101c0879c11a507734f9
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Fri May 12 09:06:24 2017 -0400
Add regression test for #11964
This issue was only ever present in the GHC 8.0.1 release candidates, but
let's add a regression test for it just to be safe.
>---------------------------------------------------------------
a13adcf8cfc650979a80101c0879c11a507734f9
testsuite/tests/dependent/should_run/T11964.hs | 10 ++++++++++
testsuite/tests/dependent/should_run/T11964a.hs | 5 +++++
testsuite/tests/dependent/should_run/all.T | 2 +-
3 files changed, 16 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/dependent/should_run/T11964.hs b/testsuite/tests/dependent/should_run/T11964.hs
new file mode 100644
index 0000000..96a83dc
--- /dev/null
+++ b/testsuite/tests/dependent/should_run/T11964.hs
@@ -0,0 +1,10 @@
+module T11964 where
+
+import Data.Kind
+import T11964a
+
+t1 :: T Type Int
+t1 = T ()
+
+t2 :: T Star Int
+t2 = T ()
diff --git a/testsuite/tests/dependent/should_run/T11964a.hs b/testsuite/tests/dependent/should_run/T11964a.hs
new file mode 100644
index 0000000..f057654
--- /dev/null
+++ b/testsuite/tests/dependent/should_run/T11964a.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE TypeInType #-}
+module T11964a where
+import Data.Kind
+type Star = Type
+newtype T k (t :: k) = T ()
diff --git a/testsuite/tests/dependent/should_run/all.T b/testsuite/tests/dependent/should_run/all.T
index c3b18c1..29877a7 100755
--- a/testsuite/tests/dependent/should_run/all.T
+++ b/testsuite/tests/dependent/should_run/all.T
@@ -1,4 +1,4 @@
# test('T11311', normal, compile_and_run, [''])
-
+test('T11964', normal, multimod_compile, ['T11964', '-v0'])
More information about the ghc-commits
mailing list