Standalone kind signatures (#16794)
Implements GHC Proposal #54: .../ghc-proposals/blob/master/proposals/0054-kind-signatures.rst With this patch, a type constructor can now be given an explicit standalone kind signature: {-# LANGUAGE StandaloneKindSignatures #-} type Functor :: (Type -> Type) -> Constraint class Functor f where fmap :: (a -> b) -> f a -> f b This is a replacement for CUSKs (complete user-specified kind signatures), which are now scheduled for deprecation. User-facing changes ------------------- * A new extension flag has been added, -XStandaloneKindSignatures, which implies -XNoCUSKs. * There is a new syntactic construct, a standalone kind signature: type <name> :: <kind> Declarations of data types, classes, data families, type families, and type synonyms may be accompanied by a standalone kind signature. * A standalone kind signature enables polymorphic recursion in types, just like a function type signature enables polymorphic recursion in terms. This obviates the need for CUSKs. * TemplateHaskell AST has been extended with 'KiSigD' to represent standalone kind signatures. * GHCi :info command now prints the kind signature of type constructors: ghci> :info Functor type Functor :: (Type -> Type) -> Constraint ... Limitations ----------- * 'forall'-bound type variables of a standalone kind signature do not scope over the declaration body, even if the -XScopedTypeVariables is enabled. See #16635 and #16734. * Wildcards are not allowed in standalone kind signatures, as partial signatures do not allow for polymorphic recursion. * Associated types may not be given an explicit standalone kind signature. Instead, they are assumed to have a CUSK if the parent class has a standalone kind signature and regardless of the -XCUSKs flag. * Standalone kind signatures do not support multiple names at the moment: type T1, T2 :: Type -> Type -- rejected type T1 = Maybe type T2 = Either String See #16754. * Creative use of equality constraints in standalone kind signatures may lead to GHC panics: type C :: forall (a :: Type) -> a ~ Int => Constraint class C a where f :: C a => a -> Int See #16758. Implementation notes -------------------- * The heart of this patch is the 'kcDeclHeader' function, which is used to kind-check a declaration header against its standalone kind signature. It does so in two rounds: 1. check user-written binders 2. instantiate invisible binders a la 'checkExpectedKind' * 'kcTyClGroup' now partitions declarations into declarations with a standalone kind signature or a CUSK (kinded_decls) and declarations without either (kindless_decls): * 'kinded_decls' are kind-checked with 'checkInitialKinds' * 'kindless_decls' are kind-checked with 'getInitialKinds' * DerivInfo has been extended with a new field: di_scoped_tvs :: ![(Name,TyVar)] These variables must be added to the context in case the deriving clause references tcTyConScopedTyVars. See #16731.
Showing
- compiler/GHC/Hs/Decls.hs 82 additions, 52 deletionscompiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Extension.hs 6 additions, 0 deletionscompiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/Instances.hs 5 additions, 0 deletionscompiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Types.hs 27 additions, 2 deletionscompiler/GHC/Hs/Types.hs
- compiler/GHC/ThToHs.hs 6 additions, 0 deletionscompiler/GHC/ThToHs.hs
- compiler/basicTypes/NameEnv.hs 3 additions, 1 deletioncompiler/basicTypes/NameEnv.hs
- compiler/deSugar/DsMeta.hs 10 additions, 1 deletioncompiler/deSugar/DsMeta.hs
- compiler/hieFile/HieAst.hs 17 additions, 1 deletioncompiler/hieFile/HieAst.hs
- compiler/iface/IfaceSyn.hs 82 additions, 28 deletionscompiler/iface/IfaceSyn.hs
- compiler/iface/IfaceType.hs 76 additions, 18 deletionscompiler/iface/IfaceType.hs
- compiler/main/DynFlags.hs 4 additions, 0 deletionscompiler/main/DynFlags.hs
- compiler/parser/Parser.y 14 additions, 0 deletionscompiler/parser/Parser.y
- compiler/parser/RdrHsSyn.hs 25 additions, 0 deletionscompiler/parser/RdrHsSyn.hs
- compiler/prelude/THNames.hs 6 additions, 3 deletionscompiler/prelude/THNames.hs
- compiler/prelude/TysWiredIn.hs 2 additions, 2 deletionscompiler/prelude/TysWiredIn.hs
- compiler/rename/RnBinds.hs 4 additions, 4 deletionscompiler/rename/RnBinds.hs
- compiler/rename/RnSource.hs 127 additions, 38 deletionscompiler/rename/RnSource.hs
- compiler/rename/RnTypes.hs 12 additions, 7 deletionscompiler/rename/RnTypes.hs
- compiler/rename/RnUtils.hs 2 additions, 0 deletionscompiler/rename/RnUtils.hs
- compiler/typecheck/TcDeriv.hs 13 additions, 5 deletionscompiler/typecheck/TcDeriv.hs
Loading
Please register or sign in to comment