summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_fail/T12785b.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/typecheck/should_fail/T12785b.hs')
-rw-r--r--testsuite/tests/typecheck/should_fail/T12785b.hs7
1 files changed, 5 insertions, 2 deletions
diff --git a/testsuite/tests/typecheck/should_fail/T12785b.hs b/testsuite/tests/typecheck/should_fail/T12785b.hs
index 951b04c6cd..6de914d2b3 100644
--- a/testsuite/tests/typecheck/should_fail/T12785b.hs
+++ b/testsuite/tests/typecheck/should_fail/T12785b.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE RankNTypes, TypeOperators, ViewPatterns #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds, PolyKinds, GADTs #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
module T12785b where
@@ -13,7 +14,8 @@ data HTree n a where
Leaf :: HTree (S n) a
Branch :: a -> HTree n (HTree (S n) a) -> HTree (S n) a
-data STree (n ::Peano) :: forall a . (a -> Type) -> HTree n a -> Type where
+type STree :: forall (n :: Peano) -> forall a. (a -> Type) -> HTree n a -> Type
+data STree n f s where
SPoint :: f a -> STree Z f (Point a)
SLeaf :: STree (S n) f Leaf
SBranch :: f a -> STree n (STree (S n) f) stru -> STree (S n) f (a `Branch` stru)
@@ -33,6 +35,7 @@ hmap f (Point a) = Point (f a)
hmap f Leaf = Leaf
hmap f (a `Branch` tr) = f a `Branch` hmap (hmap f) tr
-type family Payload (n :: Peano) (s :: HTree n x) :: x where
+type Payload :: forall x. forall (n :: Peano) (s :: HTree n x) -> x
+type family Payload n s where
Payload Z (Point a) = a
Payload (S n) (a `Branch` stru) = a