[commit: ghc] master, wip/andrey/drop-symlink-traversal: Add regression test for #15918 (db039a4)

git at git.haskell.org git at git.haskell.org
Wed Mar 6 21:49:05 UTC 2019


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

On branches: master,wip/andrey/drop-symlink-traversal
Link       : http://ghc.haskell.org/trac/ghc/changeset/db039a4a10fc8fa9e03e6781d1c0dc33151beda6/ghc

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

commit db039a4a10fc8fa9e03e6781d1c0dc33151beda6
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Tue Mar 5 05:58:29 2019 -0500

    Add regression test for #15918
    
    The test case in #15918 no longer triggers an `ASSERT` failure on
    GHC HEAD, likely due to commit
    682783828275cca5fd8bf5be5b52054c75e0e22c (`Make a smart mkAppTyM`).
    This patch adds a regression test for #15918 to finally put it to
    rest.


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

db039a4a10fc8fa9e03e6781d1c0dc33151beda6
 testsuite/tests/quantified-constraints/T15918.hs     | 19 +++++++++++++++++++
 testsuite/tests/quantified-constraints/T15918.stderr |  7 +++++++
 testsuite/tests/quantified-constraints/all.T         |  1 +
 3 files changed, 27 insertions(+)

diff --git a/testsuite/tests/quantified-constraints/T15918.hs b/testsuite/tests/quantified-constraints/T15918.hs
new file mode 100644
index 0000000..16e1e35
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T15918.hs
@@ -0,0 +1,19 @@
+{-# Language PolyKinds             #-}
+{-# Language TypeFamilies          #-}
+{-# Language ConstraintKinds       #-}
+{-# Language FlexibleContexts      #-}
+{-# Language QuantifiedConstraints #-}
+{-# Language UndecidableInstances  #-}
+module T15918 where
+
+import Data.Kind
+
+class Rev f where
+  rev :: f a
+
+instance (forall xx. cls xx => Rev xx) => Rev (Build cls) where
+  rev = undefined
+
+data Build :: ((k -> Type) -> Constraint) -> (k -> Type)
+
+uu = rev :: Build [] a
diff --git a/testsuite/tests/quantified-constraints/T15918.stderr b/testsuite/tests/quantified-constraints/T15918.stderr
new file mode 100644
index 0000000..fa06b0e
--- /dev/null
+++ b/testsuite/tests/quantified-constraints/T15918.stderr
@@ -0,0 +1,7 @@
+
+T15918.hs:19:19: error:
+    • Expected kind ‘(k0 -> *) -> Constraint’,
+        but ‘[]’ has kind ‘* -> *’
+    • In the first argument of ‘Build’, namely ‘[]’
+      In an expression type signature: Build [] a
+      In the expression: rev :: Build [] a
diff --git a/testsuite/tests/quantified-constraints/all.T b/testsuite/tests/quantified-constraints/all.T
index 1e2eca8..da58582 100644
--- a/testsuite/tests/quantified-constraints/all.T
+++ b/testsuite/tests/quantified-constraints/all.T
@@ -20,3 +20,4 @@ test('T15359', normal, compile, [''])
 test('T15359a', normal, compile, [''])
 test('T15625', normal, compile, [''])
 test('T15625a', normal, compile, [''])
+test('T15918', normal, compile_fail, [''])



More information about the ghc-commits mailing list