[Git][ghc/ghc][wip/T25647] Refactor documentation on wildcards in type families and clarify...
Patrick (@soulomoon)
gitlab at gitlab.haskell.org
Wed Mar 5 13:59:14 UTC 2025
Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC
Commits:
92486dbd by Patrick at 2025-03-05T21:59:01+08:00
Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules
- - - - -
4 changed files:
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/Language/Haskell/Syntax/Type.hs
Changes:
=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -2979,14 +2979,17 @@ tyConSkolem = isHoleName . tyConName
-- not whether it is abstract or not.
-{- Note [WildCards in type families]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Implementation tweak for wildCards in family instances]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Wildcards in type families are used to represent type/kind information that
-are not specified by the user. It is controversial how to interpret wildcards
-in type families. Hence We classify kinds of wildcards in type families into
-three categories represented by the FamArgFlavour data type: ClassArg, FreeArg,
-and SigArg, see Note [FamArgFlavour] for more detail. This flexibility allows
-us to flip the interpretation of wildcards in type families.
+are not specified by the user. See Note [Wildcards in family instances] for
+more intuition.
+
+It is controversial how to interpret wildcards in type families. Hence We
+classify kinds of wildcards in type families into three categories represented
+by the FamArgFlavour data type: ClassArg, FreeArg, and SigArg, see Note [FamArgFlavour]
+for more detail. This flexibility allows us to flip the interpretation of wildcards in
+type families.
Some common agreements:
@@ -3014,8 +3017,15 @@ If maintaining backward compatibility from 8.6.4 to 9.10.2, the picks would be:
- TauTv for ClassArg
- TauTv for SigArg
+<Implemenation Detail>
+The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent`
+field at `FamilyTyCon`. When typechecking type families, the `FamArgFlavour's passed
+in `tcAnonWildCardOcc` when dancing around inside `tcInferTyApps` and `SigArg` is
+passed down at `HsKindSig` branch of `tcHsType` in the dance.
+
See <More on SigArg> session in Note [FamArgFlavour] for why not just merge SigArg
and ClassArg.
+See also Note [Wildcards in family instances] for more intuition.
For more discussion, see #13908.
-}
@@ -3053,12 +3063,6 @@ For instance, for an instance declaration like
the first two underscores (free arguments) would yield TyVarTv’s while the last two
underscores (a class argument and a signature argument) would produce TauTv's.
-<Implemenation Detail>
-The ClassArg and FreeArg are generated in `mkFamilyTyCon` and store at `famTcParent`
-field at `FamilyTyCon`. When typechecking type families, the `FamArgFlavour's passed
-in `tcAnonWildCardOcc` when dancing around inside `tcInferTyApps` and `SigArg` is
-passed down at `HsKindSig` branch of `tcHsType` in the dance.
-
<More on SigArg>
Example from T14366
@@ -3070,10 +3074,9 @@ now let's consider _ here as a FreeArg then TyVarTv, then it would not match Typ
Say if we assign ClassArg to _ here, if we want to flip class arguments in associated
type family to only match Type variables. Then this example would not work.
-Another reason is that it is really hard for us to know if wildcard in signature in an
+More over, it is really hard for us to know if wildcard in signature in an
associated type family corresponding to a class argument or a free argument.
-For example, in the following
- code:
+For example, in the following code:
class C a b c where
type F a (d :: TYPE a) (e :: TYPE k) f
@@ -3102,6 +3105,8 @@ THe best way I can think of is to mark them as SigArg and treat them as TauTv.
Hence we maintain three different flavours of wildcards in type families. This provides
a flexibility to interpret wildcards in type families.
+See Note [Implementation tweak for wildCards in family instances] for how we can explore
+different design spaces.
For more discussion, see #13908.
-}
=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -910,10 +910,15 @@ This is implemented as follows: Unnamed wildcards remain unchanged after
the renamer, and then given fresh meta-variables during typechecking, and
it is handled pretty much the same way as the ones in partial type signatures.
We however don't want to emit hole constraints on wildcards in family
-instances, so we turn on PartialTypeSignatures and turn off warning flag to
-let typechecker know this.
+instances, We use special hole_mode `HM_FamPat` to indicate that.
+
See related Note [Wildcards in visible kind application] in GHC.Tc.Gen.HsType
+But over the develoment wildcards have became unintentionally more powerful
+in associated type family instances since it's relation to the parent class
+variables. It become confusing, See Note [Implementation tweak for wildCards in family instances]
+for how we can explore the design space to make it more consistent.
+
Note [Unused type variables in family instances]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When the flag -fwarn-unused-type-patterns is on, the compiler reports
=====================================
compiler/GHC/Tc/Gen/HsType.hs
=====================================
@@ -1295,7 +1295,7 @@ tcHsType mode rn_ty@(HsKindSig _ ty sig) exp_kind
-- to be fully determined (#14904)
; traceTc "tcHsType:sig" (ppr ty $$ ppr sig')
; ty' <- tcAddKindSigPlaceholders sig $
- tc_check_lhs_type mode' ty sig'
+ tc_check_lhs_type mode ty sig'
; checkExpKind rn_ty ty' sig' exp_kind }
-- See Note [Typechecking HsCoreTys]
@@ -2266,7 +2266,7 @@ tcAnonWildCardOcc is_extra (TcTyMode { mode_holes = Just (hole_lvl, hole_mode) }
HM_FamPat ClassArg -> newTauTvDetailsAtLevel
HM_FamPat SigArg -> newTauTvDetailsAtLevel
_ -> newTauTvDetailsAtLevel
- -- see Note [WildCards in type families]
+ -- see Note [Implementation tweak for wildCards in family instances]
emit_holes = case hole_mode of
HM_Sig -> True
HM_FamPat _ -> False
=====================================
compiler/Language/Haskell/Syntax/Type.hs
=====================================
@@ -216,7 +216,8 @@ A wildcard in a type can be
written '_'
In HsType this is represented by HsWildCardTy.
The renamer leaves it untouched, and it is later given a fresh
- meta tyvar in the typechecker.
+ meta tyvar in the typechecker. The wildcard in type families can
+ be cumbersome to deal with, See Note [Implementation tweak for wildCards in family instances].
* A named wildcard,
written '_a', '_foo', etc
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92486dbd8e5af2b7fc40f96b98118af5767e1ef0
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92486dbd8e5af2b7fc40f96b98118af5767e1ef0
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/20250305/39b1e97f/attachment-0001.html>
More information about the ghc-commits
mailing list