[commit: ghc] master: Test #15825 in dependent/should_fail/T15825 (731c95f)
git at git.haskell.org
git at git.haskell.org
Mon Oct 29 16:37:33 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/731c95f5167246aecd2205743a9b0d8d21bcccf9/ghc
>---------------------------------------------------------------
commit 731c95f5167246aecd2205743a9b0d8d21bcccf9
Author: Richard Eisenberg <rae at cs.brynmawr.edu>
Date: Mon Oct 29 09:59:07 2018 -0400
Test #15825 in dependent/should_fail/T15825
>---------------------------------------------------------------
731c95f5167246aecd2205743a9b0d8d21bcccf9
testsuite/tests/dependent/should_fail/T15825.hs | 14 ++++++++++++++
testsuite/tests/dependent/should_fail/T15825.stderr | 5 +++++
testsuite/tests/dependent/should_fail/all.T | 1 +
3 files changed, 20 insertions(+)
diff --git a/testsuite/tests/dependent/should_fail/T15825.hs b/testsuite/tests/dependent/should_fail/T15825.hs
new file mode 100644
index 0000000..01227a8
--- /dev/null
+++ b/testsuite/tests/dependent/should_fail/T15825.hs
@@ -0,0 +1,14 @@
+{-# Language RankNTypes #-}
+{-# Language PolyKinds #-}
+{-# Language KindSignatures #-}
+{-# Language DataKinds #-}
+{-# Language FlexibleInstances #-}
+
+{-# Options_GHC -dcore-lint #-}
+
+module T15825 where
+
+type C k = (forall (x::k). *)
+
+class X (a :: *)
+instance forall (a :: C k). X (a :: *)
diff --git a/testsuite/tests/dependent/should_fail/T15825.stderr b/testsuite/tests/dependent/should_fail/T15825.stderr
new file mode 100644
index 0000000..5e67bf7
--- /dev/null
+++ b/testsuite/tests/dependent/should_fail/T15825.stderr
@@ -0,0 +1,5 @@
+
+T15825.hs:14:29: error:
+ • Illegal type synonym family application ‘GHC.Types.Any’ in instance:
+ X a
+ • In the instance declaration for ‘X (a :: *)’
diff --git a/testsuite/tests/dependent/should_fail/all.T b/testsuite/tests/dependent/should_fail/all.T
index 2b602fa..d76fc35 100644
--- a/testsuite/tests/dependent/should_fail/all.T
+++ b/testsuite/tests/dependent/should_fail/all.T
@@ -37,3 +37,4 @@ test('T15591b', normal, compile_fail, [''])
test('T15591c', normal, compile_fail, [''])
test('T15743c', normal, compile_fail, [''])
test('T15743d', normal, compile_fail, [''])
+test('T15825', normal, compile_fail, [''])
More information about the ghc-commits
mailing list