summaryrefslogtreecommitdiff
path: root/testsuite/tests/dependent/should_compile/T16326_Compile1.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/dependent/should_compile/T16326_Compile1.hs')
-rw-r--r--testsuite/tests/dependent/should_compile/T16326_Compile1.hs18
1 files changed, 10 insertions, 8 deletions
diff --git a/testsuite/tests/dependent/should_compile/T16326_Compile1.hs b/testsuite/tests/dependent/should_compile/T16326_Compile1.hs
index 138ab486ca..bdffcf758f 100644
--- a/testsuite/tests/dependent/should_compile/T16326_Compile1.hs
+++ b/testsuite/tests/dependent/should_compile/T16326_Compile1.hs
@@ -4,6 +4,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE UnicodeSyntax #-}
module T16326_Compile1 where
@@ -20,14 +21,15 @@ type DComp a
(x :: a) =
f (g x)
--- Ensure that ElimList has a CUSK, beuas it is
--- is used polymorphically its RHS (c.f. #16344)
-type family ElimList (a :: Type)
- (p :: [a] -> Type)
- (s :: [a])
- (pNil :: p '[])
- (pCons :: forall (x :: a) (xs :: [a]) -> p xs -> p (x:xs))
- :: p s where
+
+type ElimList ::
+ forall (a :: Type)
+ (p :: [a] -> Type)
+ (s :: [a])
+ (pNil :: p '[])
+ (pCons :: forall (x :: a) (xs :: [a]) -> p xs -> p (x:xs))
+ -> p s
+type family ElimList a p s pNil pCons where
forall a p pNil (pCons :: forall (x :: a) (xs :: [a]) -> p xs -> p (x:xs)).
ElimList a p '[] pNil pCons =
pNil