[Git][ghc/ghc][wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593] include constructor in kind-checking for data family instance

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Fri Jan 3 06:07:59 UTC 2025



Patrick pushed to branch wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593 at Glasgow Haskell Compiler / GHC


Commits:
a27926ba by Patrick at 2025-01-03T14:07:45+08:00
include constructor in kind-checking for data family instance

- - - - -


1 changed file:

- compiler/GHC/Tc/TyCl/Instance.hs


Changes:

=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -717,7 +717,7 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env
        ; let new_or_data = dataDefnConsNewOrData hs_cons
        ; (qtvs, non_user_tvs, pats, tc_res_kind, stupid_theta)
              <- tcDataFamInstHeader mb_clsinfo skol_info fam_tc outer_bndrs fixity
-                                    hs_ctxt hs_pats m_ksig new_or_data
+                                    hs_ctxt hs_pats m_ksig hs_cons new_or_data
 
        -- Eta-reduce the axiom if possible
        -- Quite tricky: see Note [Implementing eta reduction for data families]
@@ -917,7 +917,7 @@ TyVarEnv will simply be empty, and there is nothing to worry about.
 tcDataFamInstHeader
     :: AssocInstInfo -> SkolemInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn
     -> LexicalFixity -> Maybe (LHsContext GhcRn)
-    -> HsFamEqnPats GhcRn -> Maybe (LHsKind GhcRn)
+    -> HsFamEqnPats GhcRn -> Maybe (LHsKind GhcRn) -> DataDefnCons (LConDecl GhcRn)
     -> NewOrData
     -> TcM ([TcTyVar], TyVarSet, [TcType], TcKind, TcThetaType)
          -- All skolem TcTyVars, all zonked so it's clear what the free vars are
@@ -926,7 +926,7 @@ tcDataFamInstHeader
 --    e.g.  data instance D [a] :: * -> * where ...
 -- Here the "header" is the bit before the "where"
 tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity
-                    hs_ctxt hs_pats m_ksig new_or_data
+                    hs_ctxt hs_pats m_ksig hs_cons new_or_data
   = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats)
        ; (tclvl, wanted, (outer_bndrs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind)))
             <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $
@@ -948,6 +948,10 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity
                   -- Do not add constraints from the data constructors
                   -- See Note [Kind inference for data family instances]
 
+                  -- Add constraints from the data constructors
+                  ; kcConDecls new_or_data res_kind hs_cons
+
+
                   -- Check that the result kind of the TyCon applied to its args
                   -- is compatible with the explicit signature (or Type, if there
                   -- is none)



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a27926ba7af5654df1e6eb95a9eeb2953f128d7e
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/20250103/7282d1fb/attachment-0001.html>


More information about the ghc-commits mailing list