[commit: ghc] master: testsuite: Add test for #12966 (81c4956)

git at git.haskell.org git at git.haskell.org
Thu Dec 15 23:17:34 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/81c49562570a403e8470f73f4decd3e0cb891983/ghc

>---------------------------------------------------------------

commit 81c49562570a403e8470f73f4decd3e0cb891983
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Thu Dec 15 15:27:01 2016 -0500

    testsuite: Add test for #12966
    
    This isn't exactly a typechecker test, but it was the most appropriate
    directory I could think of. The issue being tested is fixed.
    
    Test Plan: Validate
    
    Reviewers: austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2857
    
    GHC Trac Issues: #12966


>---------------------------------------------------------------

81c49562570a403e8470f73f4decd3e0cb891983
 testsuite/tests/typecheck/should_fail/T12966.hs     | 4 ++++
 testsuite/tests/typecheck/should_fail/T12966.stderr | 6 ++++++
 testsuite/tests/typecheck/should_fail/all.T         | 1 +
 3 files changed, 11 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/T12966.hs b/testsuite/tests/typecheck/should_fail/T12966.hs
new file mode 100644
index 0000000..27bcff6
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12966.hs
@@ -0,0 +1,4 @@
+{-# LANGUAGE RankNTypes #-}
+module T12966 where
+-- This should fail with a proper error message, not a compiler panic.
+type Maybeify c = forall d. (c d) => ((~) (Maybe d))
diff --git a/testsuite/tests/typecheck/should_fail/T12966.stderr b/testsuite/tests/typecheck/should_fail/T12966.stderr
new file mode 100644
index 0000000..dd63bf4
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12966.stderr
@@ -0,0 +1,6 @@
+
+T12966.hs:4:39: error:
+    • Expecting one more argument to ‘(~) (Maybe d)’
+      Expected a type, but ‘(~) (Maybe d)’ has kind ‘* -> Constraint’
+    • In the type ‘forall d. (c d) => ((~) (Maybe d))’
+      In the type declaration for ‘Maybeify’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 6f99a94..9f578a0 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -432,3 +432,4 @@ test('T12529', normal, compile_fail, [''])
 test('T12729', normal, compile_fail, [''])
 test('T12803', normal, compile_fail, [''])
 test('T12042', extra_clean(['T12042a.hi', 'T12042a.o', 'T12042.hi-boot', 'T12042.o-boot']), multimod_compile_fail, ['T12042', ''])
+test('T12966', normal, compile_fail, [''])
\ No newline at end of file



More information about the ghc-commits mailing list