[Git][ghc/ghc][wip/soulomoon/25647-allow-newtype-instance-in-gadt-syntax] peek at the result kind

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Thu Jan 16 16:35:31 UTC 2025



Patrick pushed to branch wip/soulomoon/25647-allow-newtype-instance-in-gadt-syntax at Glasgow Haskell Compiler / GHC


Commits:
726e509f by Patrick at 2025-01-17T00:35:16+08:00
peek at the result kind

- - - - -


2 changed files:

- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl.hs


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -75,6 +75,7 @@ module GHC.Tc.Gen.HsType (
 
         -- Utils
         tyLitFromLit, tyLitFromOverloadedLit,
+        getTyConResultKind
 
    ) where
 
@@ -3947,6 +3948,12 @@ needsEtaExpansion DataTypeFlavour = True
 needsEtaExpansion ClassFlavour    = True
 needsEtaExpansion _               = False
 
+getTyConResultKind :: Kind -> TcKind
+getTyConResultKind kind
+  = case splitPiTy_maybe kind of
+      Just (_, kind') -> getTyConResultKind kind'
+      Nothing         -> kind
+
 splitTyConKind :: SkolemInfo
                -> InScopeSet
                -> [OccName]  -- Avoid these OccNames


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -1877,9 +1877,9 @@ kcConDecl new_or_data tc_res_kind
     bindOuterSigTKBndrs_Tv outer_bndrs $
         -- Why "_Tv"?  See Note [Using TyVarTvs for kind-checking GADTs]
     do { _ <- tcHsContext cxt
-       ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty)
+       ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty $$ ppr tc_res_kind)
        ; con_res_kind <-  if NewType == new_or_data
-                          then return tc_res_kind
+                          then return $ getTyConResultKind tc_res_kind
                           else newOpenTypeKind
        ; _ <- tcCheckLHsTypeInContext res_ty $ (TheKind con_res_kind)
        ; let arg_exp_kind = getArgExpKind new_or_data con_res_kind



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/726e509fab32d4bee45742b1596e30bfff47354c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/726e509fab32d4bee45742b1596e30bfff47354c
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250116/49f37e01/attachment-0001.html>


More information about the ghc-commits mailing list