summaryrefslogtreecommitdiff
path: root/testsuite/tests/indexed-types/should_fail/T14246.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/indexed-types/should_fail/T14246.hs')
-rw-r--r--testsuite/tests/indexed-types/should_fail/T14246.hs13
1 files changed, 9 insertions, 4 deletions
diff --git a/testsuite/tests/indexed-types/should_fail/T14246.hs b/testsuite/tests/indexed-types/should_fail/T14246.hs
index 6ae8760c84..e3fba67df7 100644
--- a/testsuite/tests/indexed-types/should_fail/T14246.hs
+++ b/testsuite/tests/indexed-types/should_fail/T14246.hs
@@ -1,4 +1,6 @@
-{-# LANGUAGE RankNTypes, GADTs, TypeOperators, PolyKinds, DataKinds, TypeFamilies, AllowAmbiguousTypes, UndecidableInstances, TypeInType #-}
+{-# LANGUAGE RankNTypes, GADTs, TypeOperators, PolyKinds, DataKinds,
+ TypeFamilies, AllowAmbiguousTypes, UndecidableInstances,
+ StandaloneKindSignatures #-}
module T14246 where
@@ -6,7 +8,8 @@ import Data.Kind
data Nat = Z | S Nat
-data Vect :: Nat -> Type -> Type where
+type Vect :: Nat -> Type -> Type
+data Vect n a where
Nil :: Vect Z a
Cons :: a -> Vect n a -> Vect (S n) a
@@ -14,10 +17,12 @@ data Label a = Label a
data L
-type family KLN (n :: k) :: Nat where
+type KLN :: k -> Nat
+type family KLN n where
KLN (f :: v -> k) = S (KLN (forall t. f t))
KLN (f :: Type) = Z
-type family Reveal (n :: k) (l :: Vect (KLN n) L) :: Type where
+type Reveal :: forall n -> Vect (KLN n) L -> Type
+type family Reveal n l where
Reveal (f :: v -> k) (Cons (Label (t :: v)) l) = Reveal (f t) l
Reveal (a :: Type) Nil = a