Skip to content
Snippets Groups Projects
Forked from Glasgow Haskell Compiler / GHC
5508 commits behind the upstream repository.
  • Vladislav Zavialov's avatar
    679bbc97
    testsuite: Do not require CUSKs · 679bbc97
    Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
    Numerous tests make use of CUSKs (complete user-supplied kinds),
    a legacy feature scheduled for deprecation. In order to proceed
    with the said deprecation, the tests have been updated to use SAKS
    instead (standalone kind signatures).
    
    This also allows us to remove the Haskell2010 language pragmas that
    were added in 115cd3c8 to work around the lack of CUSKs in GHC2021.
    679bbc97
    History
    testsuite: Do not require CUSKs
    Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
    Numerous tests make use of CUSKs (complete user-supplied kinds),
    a legacy feature scheduled for deprecation. In order to proceed
    with the said deprecation, the tests have been updated to use SAKS
    instead (standalone kind signatures).
    
    This also allows us to remove the Haskell2010 language pragmas that
    were added in 115cd3c8 to work around the lack of CUSKs in GHC2021.
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
DumpParsedAst.hs 675 B
{-# LANGUAGE DataKinds, GADTs, PolyKinds, RankNTypes, TypeOperators, TypeFamilies
             , TypeApplications #-}

module DumpParsedAst where
import Data.Kind

data Peano = Zero | Succ Peano

type Length :: [k] -> Peano
type family Length (as :: [k]) :: Peano where
  Length (a : as) = Succ (Length as)
  Length '[]      = Zero

-- vis kind app
data T f (a :: k) = MkT (f a)

type F1 :: k -> (k -> Type) -> Type
type family F1 (a :: k) (f :: k -> Type) :: Type where
  F1 @Peano a f = T @Peano f a

data family Nat :: k -> k -> Type
newtype instance Nat (a :: k -> Type) :: (k -> Type) -> Type where
  Nat :: (forall xx. f xx -> g xx) -> Nat f g

main = putStrLn "hello"