[Git][ghc/ghc][wip/soulomoon/suggest-UnliftedNewtypes-unlifted-data-family-25593] rename etaExpandAlgTyCon -> maybeEtaExpandAlgTyCon and introduce...

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Wed Jan 8 15:45:43 UTC 2025



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


Commits:
17e8b4e5 by Patrick at 2025-01-08T23:45:32+08:00
rename etaExpandAlgTyCon -> maybeEtaExpandAlgTyCon and introduce etaExpandAlgTyCon to expand unconditionally

- - - - -


3 changed files:

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


Changes:

=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -42,7 +42,8 @@ module GHC.Tc.Gen.HsType (
         -- Type checking type and class decls, and instances thereof
         bindTyClTyVars, bindTyClTyVarsAndZonk,
         tcFamTyPats,
-        etaExpandAlgTyCon, tcbVisibilities,
+        maybeEtaExpandAlgTyCon, tcbVisibilities,
+        etaExpandAlgTyCon,
 
           -- tyvars
         zonkAndScopedSort,
@@ -2467,7 +2468,7 @@ kcCheckDeclHeader_cusk name flav
                       ++ map (mkExplicitTyConBinder mentioned_kv_set) tc_bndrs
 
        -- Eta expand if necessary; we are building a PolyTyCon
-       ; (eta_tcbs, res_kind) <- etaExpandAlgTyCon flav skol_info all_tcbs res_kind
+       ; (eta_tcbs, res_kind) <- maybeEtaExpandAlgTyCon flav skol_info all_tcbs res_kind
 
        ; let all_tv_prs = mkTyVarNamePairs (scoped_kvs ++ binderVars tc_bndrs)
              final_tcbs = all_tcbs `chkAppend` eta_tcbs
@@ -3920,14 +3921,20 @@ Hence using zonked_kinds when forming tvs'.
 -}
 
 -----------------------------------
-etaExpandAlgTyCon :: TyConFlavour tc  -> SkolemInfo
+maybeEtaExpandAlgTyCon :: TyConFlavour tc  -> SkolemInfo
                   -> [TcTyConBinder] -> Kind
                   -> TcM ([TcTyConBinder], Kind)
-etaExpandAlgTyCon flav skol_info tcbs res_kind
+maybeEtaExpandAlgTyCon flav skol_info tcbs res_kind
   | needsEtaExpansion flav
-  = splitTyConKind skol_info in_scope avoid_occs res_kind
+  = etaExpandAlgTyCon skol_info tcbs res_kind
   | otherwise
   = return ([], res_kind)
+
+etaExpandAlgTyCon :: SkolemInfo
+                  -> [TcTyConBinder] -> Kind
+                  -> TcM ([TcTyConBinder], Kind)
+etaExpandAlgTyCon skol_info tcbs res_kind
+  = splitTyConKind skol_info in_scope avoid_occs res_kind
   where
     tyvars     = binderVars tcbs
     in_scope   = mkInScopeSetList tyvars


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -1135,7 +1135,7 @@ generaliseTcTyCon (tc, skol_info, scoped_prs, tc_res_kind)
              flav = tyConFlavour tc
 
        -- Eta expand
-       ; (eta_tcbs, tc_res_kind) <- etaExpandAlgTyCon flav skol_info all_tcbs tc_res_kind
+       ; (eta_tcbs, tc_res_kind) <- maybeEtaExpandAlgTyCon flav skol_info all_tcbs tc_res_kind
 
        -- Step 6: Make the result TcTyCon
        ; let final_tcbs = all_tcbs `chkAppend` eta_tcbs
@@ -1252,7 +1252,7 @@ paths for
 
 Note that neither code path worries about point (4) above, as this
 is nicely handled by not mangling the res_kind. (Mangling res_kinds is done
-*after* all this stuff, in tcDataDefn's call to etaExpandAlgTyCon.)
+*after* all this stuff, in tcDataDefn's call to maybeEtaExpandAlgTyCon.)
 
 We can tell Inferred apart from Specified by looking at the scoped
 tyvars; Specified are always included there.
@@ -2123,7 +2123,7 @@ DT3 Eta-expansion: Any forall-bound variables and function arguments in a result
      data T a :: Type -> Type where ...
 
     we really mean for T to have two parameters. The second parameter
-    is produced by processing the return kind in etaExpandAlgTyCon,
+    is produced by processing the return kind in maybeEtaExpandAlgTyCon,
     called in tcDataDefn.
 
     See also Note [splitTyConKind] in GHC.Tc.Gen.HsType.


=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -742,8 +742,7 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env
        --     we did it before the "extra" tvs from etaExpandAlgTyCon
        --     would always be eta-reduced
        --
-       ; let flav = newOrDataToFlavour $ dataDefnConsNewOrData hs_cons
-       ; (extra_tcbs, tc_res_kind) <- etaExpandAlgTyCon flav skol_info full_tcbs tc_res_kind
+       ; (extra_tcbs, tc_res_kind) <- etaExpandAlgTyCon skol_info full_tcbs tc_res_kind
 
        -- Check the result kind; it may come from a user-written signature.
        -- See Note [Datatype return kinds] in GHC.Tc.TyCl point 4(a)



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17e8b4e5e94172ee266ab2f6ceba219ce76cce4c
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/20250108/25edc9d0/attachment-0001.html>


More information about the ghc-commits mailing list