summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSebastian Graf <sebastian.graf@kit.edu>2021-04-01 17:27:14 +0200
committerSebastian Graf <sebastian.graf@kit.edu>2021-04-01 18:32:55 +0200
commit87f27cb27643e995561abb13b405c516fcc20575 (patch)
tree29336cb9a6de3f560171223670ca1e7b3e65674c
parentd44e42a26e54857cc6174f2bb7dc86cc41fcd249 (diff)
downloadhaskell-wip/T19622.tar.gz
Pmc: Add regression test for #19622wip/T19622
It appears that the issue has already been fixed. Judging by the use of a pattern synonym with a provided constraint, my bet is on 1793ca9d. Fixes #19622.
-rw-r--r--testsuite/tests/pmcheck/should_compile/T19622.hs55
-rw-r--r--testsuite/tests/pmcheck/should_compile/all.T2
2 files changed, 57 insertions, 0 deletions
diff --git a/testsuite/tests/pmcheck/should_compile/T19622.hs b/testsuite/tests/pmcheck/should_compile/T19622.hs
new file mode 100644
index 0000000000..950628580e
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T19622.hs
@@ -0,0 +1,55 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE PatternSynonyms #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE ViewPatterns #-}
+
+module T19622 where
+
+import Data.Kind (Type)
+
+data A
+data B
+
+data ElemKind k where
+ ElemKindA :: ElemKind A
+ ElemKindB :: ElemKind B
+
+class KnownElemKind (xs :: [k]) where
+ getKind :: TypedList f xs -> ElemKind k
+
+data TypedList (f :: (k -> Type)) (xs :: [k]) where
+ Nil :: TypedList f '[]
+ Cons :: f x -> TypedList f xs -> TypedList f (x ': xs)
+
+data Dim (x :: k)
+
+pattern DimA :: forall k (xs :: [k]) . KnownElemKind xs => (k ~ A) => TypedList Dim xs
+pattern DimA <- (getKind -> ElemKindA)
+
+{-# COMPLETE DimA #-}
+{-# COMPLETE Nil, Cons #-}
+
+f :: forall (xns :: [B]) . TypedList Dim xns -> TypedList Dim xns -> Bool
+f Nil Nil = True
+f (Cons _ _) (Cons _ _) = True
+
+g :: forall (xns :: [B]) . TypedList Dim xns -> Bool
+g Nil = True
+g (Cons _ _) = True
+
+h :: forall (xns :: [A]) . TypedList Dim xns -> Bool
+h Nil = True
+h (Cons _ _) = True
+
+i :: forall (xns :: [A]) . TypedList Dim xns -> TypedList Dim xns -> Bool
+i Nil Nil = True
+i (Cons _ _) (Cons _ _) = True
+
+j :: forall k (xns :: [k]) . TypedList Dim xns -> TypedList Dim xns -> Bool
+j Nil Nil = True
+j (Cons _ _) (Cons _ _) = True
+
+l :: forall (xns :: [A]) . KnownElemKind xns => TypedList Dim xns -> Bool
+l DimA = True
diff --git a/testsuite/tests/pmcheck/should_compile/all.T b/testsuite/tests/pmcheck/should_compile/all.T
index 5245862851..3880ca0756 100644
--- a/testsuite/tests/pmcheck/should_compile/all.T
+++ b/testsuite/tests/pmcheck/should_compile/all.T
@@ -162,6 +162,8 @@ test('T18708', normal, compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
test('T18932', normal, compile,
['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
+test('T19622', normal, compile,
+ ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
# Other tests
test('pmc001', [], compile,