diff options
Diffstat (limited to 'testsuite/tests/dependent/should_compile/Rae31.hs')
-rw-r--r-- | testsuite/tests/dependent/should_compile/Rae31.hs | 23 |
1 files changed, 13 insertions, 10 deletions
diff --git a/testsuite/tests/dependent/should_compile/Rae31.hs b/testsuite/tests/dependent/should_compile/Rae31.hs index cedc019cf3..7a50b606ee 100644 --- a/testsuite/tests/dependent/should_compile/Rae31.hs +++ b/testsuite/tests/dependent/should_compile/Rae31.hs @@ -1,24 +1,27 @@ {-# LANGUAGE TemplateHaskell, TypeOperators, PolyKinds, DataKinds, - TypeFamilies, TypeInType #-} + TypeFamilies #-} module A where import Data.Kind -data family Sing (k :: *) :: k -> * +data family Sing (k :: Type) :: k -> Type type Sing' (x :: k) = Sing k x -data TyFun' (a :: *) (b :: *) :: * -type TyFun (a :: *) (b :: *) = TyFun' a b -> * +data TyFun' (a :: Type) (b :: Type) :: Type +type TyFun (a :: Type) (b :: Type) = TyFun' a b -> Type type family (a :: TyFun k1 k2) @@ (b :: k1) :: k2 -data TyPi' (a :: *) (b :: TyFun a *) :: * -type TyPi (a :: *) (b :: TyFun a *) = TyPi' a b -> * +data TyPi' (a :: Type) (b :: TyFun a Type) :: Type +type TyPi (a :: Type) (b :: TyFun a Type) = TyPi' a b -> Type type family (a :: TyPi k1 k2) @@@ (b :: k1) :: k2 @@ b $(return []) -data A (a :: *) (b :: a) (c :: TyFun' a *) -- A :: forall a -> a -> a ~> * -type instance (@@) (A a b) c = * +data A (a :: Type) (b :: a) (c :: TyFun' a Type) + -- A :: forall a -> a -> a ~> Type +type instance (@@) (A a b) c = Type $(return []) -data B (a :: *) (b :: TyFun' a *) -- B :: forall a -> a ~> * +data B (a :: Type) (b :: TyFun' a Type) + -- B :: forall a -> a ~> Type type instance (@@) (B a) b = TyPi a (A a b) $(return []) -data C (a :: *) (b :: TyPi a (B a)) (c :: a) (d :: a) (e :: TyFun' (b @@@ c @@@ d) *) +data C (a :: Type) (b :: TyPi a (B a)) (c :: a) (d :: a) + (e :: TyFun' (b @@@ c @@@ d) Type) |