diff options
author | Vladislav Zavialov <vlad.z.4096@gmail.com> | 2019-03-29 10:18:03 +0300 |
---|---|---|
committer | Vladislav Zavialov <vlad.z.4096@gmail.com> | 2019-09-25 21:06:04 +0300 |
commit | 0b5eede97804ec3dfbfa9df9f97bcfe2aa369f6b (patch) | |
tree | c6f6452ba5ae3a3d9f2986c79e054ea55a601884 /libraries/template-haskell | |
parent | 795986aaf33e2ffc233836b86a92a77366c91db2 (diff) | |
download | haskell-0b5eede97804ec3dfbfa9df9f97bcfe2aa369f6b.tar.gz |
Standalone kind signatures (#16794)wip/top-level-kind-signatures
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.
Diffstat (limited to 'libraries/template-haskell')
4 files changed, 6 insertions, 1 deletions
diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib.hs b/libraries/template-haskell/Language/Haskell/TH/Lib.hs index 86311762a3..7bb4eb50dd 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Lib.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Lib.hs @@ -85,7 +85,7 @@ module Language.Haskell.TH.Lib ( viaStrategy, DerivStrategy(..), -- **** Class classD, instanceD, instanceWithOverlapD, Overlap(..), - sigD, standaloneDerivD, standaloneDerivWithStrategyD, defaultSigD, + sigD, kiSigD, standaloneDerivD, standaloneDerivWithStrategyD, defaultSigD, -- **** Role annotations roleAnnotD, diff --git a/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs b/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs index 5ec59b3737..4d3887baf2 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs @@ -435,6 +435,9 @@ instanceWithOverlapD o ctxt ty decs = sigD :: Name -> TypeQ -> DecQ sigD fun ty = liftM (SigD fun) $ ty +kiSigD :: Name -> KindQ -> DecQ +kiSigD fun ki = liftM (KiSigD fun) $ ki + forImpD :: Callconv -> Safety -> String -> Name -> TypeQ -> DecQ forImpD cc s str n ty = do ty' <- ty diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 792a78b606..98ddd1c2ca 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -341,6 +341,7 @@ ppr_dec _ (InstanceD o ctxt i ds) = text "instance" <+> maybe empty ppr_overlap o <+> pprCxt ctxt <+> ppr i $$ where_clause ds ppr_dec _ (SigD f t) = pprPrefixOcc f <+> dcolon <+> ppr t +ppr_dec _ (KiSigD f k) = text "type" <+> pprPrefixOcc f <+> dcolon <+> ppr k ppr_dec _ (ForeignD f) = ppr f ppr_dec _ (InfixD fx n) = pprFixity n fx ppr_dec _ (PragmaD p) = ppr p diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index 72eadbff91..59cc5dceef 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -2029,6 +2029,7 @@ data Dec -- ^ @{ instance {\-\# OVERLAPS \#-\} -- Show w => Show [w] where ds }@ | SigD Name Type -- ^ @{ length :: [a] -> Int }@ + | KiSigD Name Kind -- ^ @{ type TypeRep :: k -> Type }@ | ForeignD Foreign -- ^ @{ foreign import ... } --{ foreign export ... }@ |