[Git][ghc/ghc][wip/T25647] enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging
Patrick (@soulomoon)
gitlab at gitlab.haskell.org
Tue Mar 4 22:19:37 UTC 2025
Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC
Commits:
d8258877 by Patrick at 2025-03-05T06:19:27+08:00
enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging
- - - - -
3 changed files:
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Utils/TcMType.hs
Changes:
=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -3409,9 +3409,10 @@ without treating the explicitly-quantified ones specially. Wrinkles:
In step 1 we do /not/ want to get
newtype instance forall r . Fix2 (f :: TYPE r -> TYPE r) :: TYPE r where
If we do, we'll get that same "newtype must not be GADT" error as for N above.
- Rather, we want to default the RuntimeRep variable r := LiftedRep. The key thing
- is that we must make the /same/ choice here as we do in kind-checking the data
- constructor's type.
+ Rather, we want to default the RuntimeRep variable r := LiftedRep. See the call
+ to `quantifyTyVars` in `tcDataFamInstHeader`. The key thing is that we must make
+ the /same/ choice here as we do in kind-checking the data constructor's type
+ in `kindGeneralizeAll` in `tcConDecl`.
See also Note [Re-quantify type variables in rules] in GHC.Tc.Gen.Rule, which
explains a /very/ similar design when generalising over the type of a rewrite
@@ -4034,10 +4035,10 @@ tcConArg :: ConArgKind -- expected kind for args; always OpenKind for datatype
-- but might be an unlifted type with UnliftedNewtypes
-> HsScaled GhcRn (LHsType GhcRn) -> TcM (Scaled TcType, HsSrcBang)
tcConArg exp_kind (HsScaled w bty)
- = do { traceTc "tcConArg 1" (ppr bty)
+ = do { traceTc "tcConArg 1: " (ppr bty <+> ppr exp_kind)
; arg_ty <- tcCheckLHsTypeInContext (getBangType bty) exp_kind
; w' <- tcDataConMult w
- ; traceTc "tcConArg 2" (ppr bty)
+ ; traceTc "tcConArg 2: " (ppr bty <+> ppr arg_ty)
; return (Scaled w' arg_ty, getBangStrictness bty) }
tcRecConDeclFields :: ConArgKind
=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -977,6 +977,8 @@ tcDataFamInstHeader mb_clsinfo skol_info fam_tc hs_outer_bndrs fixity
-- See GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts]
; dvs <- candidateQTyVarsWithBinders outer_tvs lhs_ty
; qtvs <- quantifyTyVars skol_info dvs
+ -- Have to make a same defaulting choice for reuslt kind here
+ -- and the `kindGeneralizeAll` in `tcConDecl`.
-- see (GT4) in
-- GHC.Tc.TyCl Note [Generalising in tcTyFamInstEqnGuts]
=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -827,7 +827,7 @@ cloneAnonMetaTyVar info tv kind
= do { details <- newMetaDetails info
; name <- cloneMetaTyVarName (tyVarName tv)
; let tyvar = mkTcTyVar name kind details
- ; traceTc "cloneAnonMetaTyVar" (ppr tyvar <+> dcolon <+> ppr (tyVarKind tyvar))
+ ; traceTc "cloneAnonMetaTyVar" (ppr tyvar <+> dcolon <+> ppr (tyVarKind tyvar) <+> text "from" <+> ppr tv)
; return tyvar }
-- Make a new CycleBreakerTv. See Note [Type equality cycles]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d82588777cc57efd47036da3568197616cf07908
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d82588777cc57efd47036da3568197616cf07908
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/20250304/ac8ee0d0/attachment-0001.html>
More information about the ghc-commits
mailing list