summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_compile/T14366.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/typecheck/should_compile/T14366.hs')
-rw-r--r--testsuite/tests/typecheck/should_compile/T14366.hs12
1 files changed, 9 insertions, 3 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T14366.hs b/testsuite/tests/typecheck/should_compile/T14366.hs
index 56abad5d30..8a78468cc4 100644
--- a/testsuite/tests/typecheck/should_compile/T14366.hs
+++ b/testsuite/tests/typecheck/should_compile/T14366.hs
@@ -1,13 +1,19 @@
{-# LANGUAGE TypeFamilies #-}
-{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE ExplicitForAll #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
module T14366 where
+
import Data.Kind
import Data.Type.Equality
-type family Cast (a :: Type) (b :: Type) (e :: a :~: b) (x :: a) :: b where
+type Cast :: forall (a :: Type) (b :: Type) -> a :~: b -> a -> b
+type family Cast a b e x where
Cast _ _ Refl x = x
-type family F (a :: Type) :: Type where
+type F :: Type -> Type
+type family F a where
F (a :: _) = a