[commit: ghc] master: Add regression tests for #14904 (5de0be8)

git at git.haskell.org git at git.haskell.org
Thu May 3 14:17:37 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5de0be8d7ee48eac0af42387eb40b5a5a9b08a35/ghc

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

commit 5de0be8d7ee48eac0af42387eb40b5a5a9b08a35
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Thu May 3 10:15:45 2018 -0400

    Add regression tests for #14904
    
    Trac #14904 was fixed in commit
    faec8d358985e5d0bf363bd96f23fe76c9e281f7. Let's add some tests to
    ensure that it stays fixed.


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

5de0be8d7ee48eac0af42387eb40b5a5a9b08a35
 testsuite/tests/typecheck/should_fail/T14904a.hs                 | 9 +++++++++
 .../T11648b.stderr => typecheck/should_fail/T14904a.stderr}      | 6 +++---
 testsuite/tests/typecheck/should_fail/T14904b.hs                 | 9 +++++++++
 testsuite/tests/typecheck/should_fail/T14904b.stderr             | 6 ++++++
 testsuite/tests/typecheck/should_fail/all.T                      | 2 ++
 5 files changed, 29 insertions(+), 3 deletions(-)

diff --git a/testsuite/tests/typecheck/should_fail/T14904a.hs b/testsuite/tests/typecheck/should_fail/T14904a.hs
new file mode 100644
index 0000000..654f5a6
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T14904a.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeInType #-}
+module T14904a where
+
+import Data.Kind
+
+type family F (f :: forall a. g a) :: Type where
+  F (f :: forall a. g a) = Int
diff --git a/testsuite/tests/polykinds/T11648b.stderr b/testsuite/tests/typecheck/should_fail/T14904a.stderr
similarity index 72%
copy from testsuite/tests/polykinds/T11648b.stderr
copy to testsuite/tests/typecheck/should_fail/T14904a.stderr
index e709e00..94cad4a 100644
--- a/testsuite/tests/polykinds/T11648b.stderr
+++ b/testsuite/tests/typecheck/should_fail/T14904a.stderr
@@ -1,8 +1,8 @@
 
-T11648b.hs:7:1: error:
+T14904a.hs:8:1: error:
     You have written a *complete user-suppled kind signature*,
     but the following variable is undetermined: k0 :: *
     Perhaps add a kind signature.
     Inferred kinds of user-written variables:
-      k :: k0
-      a :: Proxy k
+      g :: k0 -> *
+      f :: forall (a :: k0). g a
diff --git a/testsuite/tests/typecheck/should_fail/T14904b.hs b/testsuite/tests/typecheck/should_fail/T14904b.hs
new file mode 100644
index 0000000..d8cfa1e
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T14904b.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeInType #-}
+module T14904b where
+
+import Data.Kind
+
+type family F f :: Type where
+  F ((f :: forall a. g a) :: forall a. g a) = Int
diff --git a/testsuite/tests/typecheck/should_fail/T14904b.stderr b/testsuite/tests/typecheck/should_fail/T14904b.stderr
new file mode 100644
index 0000000..fff6942
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T14904b.stderr
@@ -0,0 +1,6 @@
+
+T14904b.hs:9:7: error:
+    • Expected kind ‘forall (a :: k1). g a’, but ‘f’ has kind ‘k0’
+    • In the first argument of ‘F’, namely
+        ‘((f :: forall a. g a) :: forall a. g a)’
+      In the type family declaration for ‘F’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 16fd5de..a4150ea 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -471,3 +471,5 @@ test('T14605', normal, compile_fail, [''])
 test('T14761a', normal, compile_fail, [''])
 test('T14761b', normal, compile_fail, [''])
 test('T14884', normal, compile_fail, [''])
+test('T14904a', normal, compile_fail, [''])
+test('T14904b', normal, compile_fail, [''])



More information about the ghc-commits mailing list