[commit: ghc] master: Two tests for Trac #14230 (80d665a)

git at git.haskell.org git at git.haskell.org
Fri Nov 30 14:39:05 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/80d665a123305721c58a3d7652c64e2b3c69b70e/ghc

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

commit 80d665a123305721c58a3d7652c64e2b3c69b70e
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Nov 30 14:00:14 2018 +0000

    Two tests for Trac #14230


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

80d665a123305721c58a3d7652c64e2b3c69b70e
 testsuite/tests/indexed-types/should_fail/T14230.hs      | 11 +++++++++++
 testsuite/tests/indexed-types/should_fail/T14230.stderr  |  7 +++++++
 testsuite/tests/indexed-types/should_fail/T14230a.hs     | 13 +++++++++++++
 testsuite/tests/indexed-types/should_fail/T14230a.stderr |  6 ++++++
 testsuite/tests/indexed-types/should_fail/all.T          |  2 ++
 5 files changed, 39 insertions(+)

diff --git a/testsuite/tests/indexed-types/should_fail/T14230.hs b/testsuite/tests/indexed-types/should_fail/T14230.hs
new file mode 100644
index 0000000..d409ba6
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T14230.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+module T14230 where
+
+class C k where
+  data CD :: k -> k -> *
+
+instance C (Maybe a) where
+  data CD :: (k -> *) -> (k -> *) -> *
diff --git a/testsuite/tests/indexed-types/should_fail/T14230.stderr b/testsuite/tests/indexed-types/should_fail/T14230.stderr
new file mode 100644
index 0000000..174a15a
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T14230.stderr
@@ -0,0 +1,7 @@
+
+T14230.hs:11:3: error:
+    • Type indexes must match class instance head
+      Expected: CD @(Maybe a)
+        Actual: CD @(k -> *) -- Defined at T14230.hs:11:8
+    • In the data instance declaration for ‘CD’
+      In the instance declaration for ‘C (Maybe a)’
diff --git a/testsuite/tests/indexed-types/should_fail/T14230a.hs b/testsuite/tests/indexed-types/should_fail/T14230a.hs
new file mode 100644
index 0000000..84cd6f1
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T14230a.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeInType #-}
+module T14230a where
+
+import Data.Kind
+
+class C a where
+  data CD k (a :: k) :: k -> *
+
+instance C (Maybe a) where
+  data CD k (a :: k -> *) :: (k -> *) -> *
diff --git a/testsuite/tests/indexed-types/should_fail/T14230a.stderr b/testsuite/tests/indexed-types/should_fail/T14230a.stderr
new file mode 100644
index 0000000..726764a
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T14230a.stderr
@@ -0,0 +1,6 @@
+
+T14230a.hs:13:14: error:
+    • Expected kind ‘k -> *’, but ‘a’ has kind ‘*’
+    • In the second argument of ‘CD’, namely ‘(a :: k -> *)’
+      In the data instance declaration for ‘CD’
+      In the instance declaration for ‘C (Maybe a)’
diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T
index 6273f59..4f6863b 100644
--- a/testsuite/tests/indexed-types/should_fail/all.T
+++ b/testsuite/tests/indexed-types/should_fail/all.T
@@ -152,3 +152,5 @@ test('T15740', normal, compile_fail, [''])
 test('T15764', normal, compile_fail, [''])
 test('T15870', normal, compile_fail, [''])
 test('T14887', normal, compile_fail, [''])
+test('T14230', normal, compile_fail, [''])
+test('T14230a', normal, compile_fail, [''])



More information about the ghc-commits mailing list