[Git][ghc/ghc][wip/T25281] Comments
Simon Peyton Jones (@simonpj)
gitlab at gitlab.haskell.org
Thu Sep 26 14:11:45 UTC 2024
Simon Peyton Jones pushed to branch wip/T25281 at Glasgow Haskell Compiler / GHC
Commits:
8156fe53 by Simon Peyton Jones at 2024-09-26T15:11:27+01:00
Comments
- - - - -
3 changed files:
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/Tc/Instance/Class.hs
Changes:
=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -558,6 +558,20 @@ dsExpr (SectionR x _ _) = dataConCantHappen x
* *
********************************************************************* -}
+{- Note [Desugaring applications]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+When we come across an application (f e1 .. en) we collect up
+all the desugared arguments, and then dispatch on the function f.
+(Including the nullary case where n=0.)
+
+There are several special cases to handle
+
+* HsRecSel: a record selector gets warnings if it might fail.
+* HsVar: special magic for `noinline`
+* HsVar: special magic for `seq`
+
+-}
+
dsApp :: HsExpr GhcTc -> DsM CoreExpr
dsApp e = ds_app e [] []
@@ -621,8 +635,8 @@ ds_app (HsRecSel _ fld_occ@(FieldOcc { foExt = fun_id })) hs_args core_args
diagnosticDs $ DsIncompleteRecordSelector (idName fun_id) cons_trimmed
(cons_trimmed /= cons_wo_field)
- -- Type-based check
- -- ToDo: explain
+ -- Type-based check. See GHC.HsToCore.Pmc (IRS4)
+ -- in Note [Detecting incomplete record selectors]
; case filterOut isTypeArg core_args of
(arg:_) -> pmcRecSel fun_id arg
_ -> return ()
=====================================
compiler/GHC/HsToCore/Pmc.hs
=====================================
@@ -198,9 +198,8 @@ pmcMatches origin ctxt vars matches = {-# SCC "pmcMatches" #-} do
formatReportWarnings ReportMatchGroup ctxt vars result)
return (NE.toList (ldiMatchGroup (cr_ret result)))
-{-
-Note [Detecting incomplete record selectors]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+{- Note [Detecting incomplete record selectors]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A record selector occurrence is incomplete iff. it could fail due to
being applied to a data type constructor not present for this record field.
@@ -211,16 +210,16 @@ e.g.
There are 4 parts to detecting and warning about
incomplete record selectors to consider:
- - Computing which constructors a general application of a record field will succeed on,
- and which ones it will fail on. This is stored in the `sel_cons` field of
- `IdDetails` datatype, which is a part of an `Id` and calculated when renaming a
- record selector in `mkOneRecordSelector`
+(IRS1) Computing which constructors a general application of a record field will
+ succeed on, and which ones it will fail on. This is stored in the `sel_cons`
+ field of `IdDetails` datatype, which is a part of an `Id` and calculated
+ when renaming a record selector in `mkOneRecordSelector`
- - Emitting a warning whenever a `HasField` constraint is solved.
+(IRS2) Emitting a warning whenever a `HasField` constraint is solved.
This is checked in `matchHasField` and emitted only for when
the constraint is resolved with an implicit instance rather than a
custom one (since otherwise the warning will be emitted in
- the custom implementation anyways)
+ the custom implementation anyways)
e.g.
g :: HasField "x" t Int => t -> Int
@@ -229,7 +228,7 @@ incomplete record selectors to consider:
f :: T -> Int
f = g -- warning will be emitted here
- - Emitting a warning for a general occurrence of the record selector
+(IRS3) Emitting a warning for a general occurrence of the record selector
This is done during the renaming of a `HsRecSel` expression in `dsExpr`
and simply pulls the information about incompleteness from the `Id`
@@ -237,7 +236,7 @@ incomplete record selectors to consider:
l :: T -> Int
l a = x a -- warning will be emitted here
- - Emitting a warning for a record selector `sel` applied to a variable `y`.
+(IRS4) Emitting a warning for a record selector `sel` applied to a variable `y`.
In that case we want to use the long-distance information from the
pattern match checker to rule out impossible constructors
(See Note [Long-distance information]). We first add constraints to
@@ -255,6 +254,7 @@ incomplete record selectors to consider:
pmcRecSel :: Id -- ^ Id of the selector
-> CoreExpr -- ^ Core expression of the argument to the selector
-> DsM ()
+-- See (IRS4) in Note [Detecting incomplete record selectors]
pmcRecSel sel_id arg
| RecSelId{ sel_cons = (cons_w_field, _ : _) } <- idDetails sel_id = do
!missing <- getLdiNablas
=====================================
compiler/GHC/Tc/Instance/Class.hs
=====================================
@@ -1298,7 +1298,8 @@ matchHasField dflags short_cut clas tys
; unless (null $ snd $ sel_cons $ idDetails sel_id)
$ addDiagnostic $ TcRnHasFieldResolvedIncomplete name
-- Only emit an incomplete selector warning if it's an implicit instance
- -- See Note [Detecting incomplete record selectors] in GHC.HsToCore.Pmc
+ -- See (IRS2) in Note [Detecting incomplete record selectors]
+ -- in GHC.HsToCore.Pmc
; return OneInst { cir_new_theta = theta
, cir_mk_ev = mk_ev
, cir_canonical = EvCanonical
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8156fe535b2318c6720ed9260b209756369309f5
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8156fe535b2318c6720ed9260b209756369309f5
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/20240926/1f133cea/attachment-0001.html>
More information about the ghc-commits
mailing list