[commit: ghc] wip/dmd-arity: Add tests for Trac #16221 and #16342 (07f378c)

git at git.haskell.org git at git.haskell.org
Thu Mar 7 17:41:25 UTC 2019


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

On branch  : wip/dmd-arity
Link       : http://ghc.haskell.org/trac/ghc/changeset/07f378cee37338c5f2655b3a7e46dfef3f1c5cc1/ghc

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

commit 07f378cee37338c5f2655b3a7e46dfef3f1c5cc1
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Mar 6 09:54:06 2019 +0000

    Add tests for Trac #16221 and #16342


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

07f378cee37338c5f2655b3a7e46dfef3f1c5cc1
 testsuite/tests/polykinds/T16221.hs      | 13 +++++++++++++
 testsuite/tests/polykinds/T16221a.hs     |  7 +++++++
 testsuite/tests/polykinds/T16221a.stderr |  6 ++++++
 testsuite/tests/polykinds/T16342.hs      | 13 +++++++++++++
 testsuite/tests/polykinds/all.T          |  3 +++
 5 files changed, 42 insertions(+)

diff --git a/testsuite/tests/polykinds/T16221.hs b/testsuite/tests/polykinds/T16221.hs
new file mode 100644
index 0000000..56a8374
--- /dev/null
+++ b/testsuite/tests/polykinds/T16221.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE GADTs, TypeInType, ExistentialQuantification #-}
+
+module T16221 where
+
+-- Failed Lint
+data T3 a = forall k (b :: k). MkT3 (T3 b) !Int
+
+-- Works with GADT
+data T4 a where
+   MkT4 :: T4 b -> !Int -> T4 a
+
+-- Works with CUSK
+data T5 (a :: j) = forall k (b :: k). MkT5 (T5 b) !Int
diff --git a/testsuite/tests/polykinds/T16221a.hs b/testsuite/tests/polykinds/T16221a.hs
new file mode 100644
index 0000000..50128aa
--- /dev/null
+++ b/testsuite/tests/polykinds/T16221a.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TypeInType, ExistentialQuantification #-}
+
+module T16221a where
+
+data SameKind :: k -> k -> *
+data T2 a = forall k (b :: k). MkT2 (SameKind a b) !Int
+
diff --git a/testsuite/tests/polykinds/T16221a.stderr b/testsuite/tests/polykinds/T16221a.stderr
new file mode 100644
index 0000000..27edc2c
--- /dev/null
+++ b/testsuite/tests/polykinds/T16221a.stderr
@@ -0,0 +1,6 @@
+
+T16221a.hs:6:49: error:
+    • Expected kind ‘k1’, but ‘b’ has kind ‘k’
+    • In the second argument of ‘SameKind’, namely ‘b’
+      In the type ‘(SameKind a b)’
+      In the definition of data constructor ‘MkT2’
diff --git a/testsuite/tests/polykinds/T16342.hs b/testsuite/tests/polykinds/T16342.hs
new file mode 100644
index 0000000..5eafcee
--- /dev/null
+++ b/testsuite/tests/polykinds/T16342.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE MultiParamTypeClasses, TypeInType, ConstrainedClassMethods, ScopedTypeVariables #-}
+
+module T16342 where
+
+import Data.Proxy
+
+class C (a::ka) x where
+  cop :: D a x => x -> Proxy a -> Proxy a
+  cop _ x = x :: Proxy (a::ka)
+
+class D (b::kb) y where
+  dop :: C b y => y -> Proxy b -> Proxy b
+  dop _ x = x :: Proxy (b::kb)
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 1cfb2aa..927319c 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -207,3 +207,6 @@ test('T14847', normal, compile, [''])
 test('T15795', normal, compile, [''])
 test('T15795a', normal, compile, [''])
 test('KindVarOrder', normal, ghci_script, ['KindVarOrder.script'])
+test('T16221', normal, compile, [''])
+test('T16221a', normal, compile_fail, [''])
+test('T16342', normal, compile, [''])



More information about the ghc-commits mailing list