summaryrefslogtreecommitdiff
path: root/testsuite/tests/patsyn/should_fail
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2018-10-16 14:47:12 +0100
committerSimon Peyton Jones <simonpj@microsoft.com>2018-10-24 16:38:55 +0100
commit7ea714cd8d64dd0a7646d71d45e18c9f6a3527cb (patch)
tree9e64c8c5bf78f4c606181fb2803ccc6aff290823 /testsuite/tests/patsyn/should_fail
parent0faf7fd3e6c652575af9993787f07cad86f452f6 (diff)
downloadhaskell-7ea714cd8d64dd0a7646d71d45e18c9f6a3527cb.tar.gz
Solve equalities in a pattern signature
Trac #15694 showed that we were forgetting to solve the equalities of a pattern signature until too late. Result: WARNINGs and a panic: "Type-correct unfilled coercion hole"
Diffstat (limited to 'testsuite/tests/patsyn/should_fail')
-rw-r--r--testsuite/tests/patsyn/should_fail/T15694.hs25
-rw-r--r--testsuite/tests/patsyn/should_fail/T15694.stderr4
-rw-r--r--testsuite/tests/patsyn/should_fail/all.T1
3 files changed, 30 insertions, 0 deletions
diff --git a/testsuite/tests/patsyn/should_fail/T15694.hs b/testsuite/tests/patsyn/should_fail/T15694.hs
new file mode 100644
index 0000000000..915ad7e7dd
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/T15694.hs
@@ -0,0 +1,25 @@
+{-# Language RankNTypes, PatternSynonyms, TypeOperators, DataKinds, PolyKinds, KindSignatures, GADTs #-}
+
+module T15694 where
+
+import Data.Kind
+import Data.Type.Equality
+
+data Ctx :: Type -> Type where
+ E :: Ctx(Type)
+ (:&:) :: a -> Ctx(as) -> Ctx(a -> as)
+
+data ApplyT(kind::Type) :: kind -> Ctx(kind) -> Type where
+ AO :: a -> ApplyT(Type) a E
+ AS :: ApplyT(ks) (f a) ctx
+ -> ApplyT(k -> ks) f (a:&:ctx)
+
+
+pattern ASSO :: () => forall ks k (f :: k -> ks) (a1 :: k) (ctx :: Ctx ks)
+ (ks1 :: Type) k1 (a2 :: k1) (ctx1 :: Ctx ks1) a3.
+ (kind ~ (k -> ks), a ~~ f, b ~~ (a1 :&: ctx),
+ ks ~ (k1 -> ks1), ctx ~~ (a2 :&: E),
+ ks1 ~ Type, f a1 a2 ~~ a3)
+ => a3 -> ApplyT kind a b
+
+pattern ASSO a = AS (AS (AO a))
diff --git a/testsuite/tests/patsyn/should_fail/T15694.stderr b/testsuite/tests/patsyn/should_fail/T15694.stderr
new file mode 100644
index 0000000000..360fb30ba2
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/T15694.stderr
@@ -0,0 +1,4 @@
+
+T15694.hs:22:35: error:
+ • Expected kind ‘k1 -> k00’, but ‘f a1’ has kind ‘ks’
+ • In the first argument of ‘(~~)’, namely ‘f a1 a2’
diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T
index e726eaa1f2..099e9059d9 100644
--- a/testsuite/tests/patsyn/should_fail/all.T
+++ b/testsuite/tests/patsyn/should_fail/all.T
@@ -46,3 +46,4 @@ test('T14507', normal, compile_fail, ['-dsuppress-uniques'])
test('T15289', normal, compile_fail, [''])
test('T15685', normal, compile_fail, [''])
test('T15692', normal, compile, ['']) # It has -fdefer-type-errors inside
+test('T15694', normal, compile_fail, [''])