Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
6 changed files:
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Tc/Gen/Expr.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
Changes:
| ... | ... | @@ -112,7 +112,7 @@ import Control.Arrow ( first ) |
| 112 | 112 | import Control.Monad
|
| 113 | 113 | import Data.Either ( partitionEithers )
|
| 114 | 114 | import Data.Function ( on )
|
| 115 | -import Data.List ( find, partition, groupBy, sortBy )
|
|
| 115 | +import Data.List ( find, partition, sortBy )
|
|
| 116 | 116 | import qualified Data.List.NonEmpty as NE
|
| 117 | 117 | import qualified Data.Semigroup as Semi
|
| 118 | 118 | import System.IO.Unsafe ( unsafePerformIO )
|
| ... | ... | @@ -1455,6 +1455,12 @@ lookupFieldGREs env (L loc rdr) |
| 1455 | 1455 | do { let (env_fld_gres, env_var_gres) =
|
| 1456 | 1456 | partition isRecFldGRE $
|
| 1457 | 1457 | lookupGRE env (LookupRdrName rdr (RelevantGREsFOS WantBoth))
|
| 1458 | + -- Make sure to use 'LookupRdrName': if a record update contains
|
|
| 1459 | + -- a qualified field name, only look up GREs which are in scope
|
|
| 1460 | + -- with that same qualification.
|
|
| 1461 | + --
|
|
| 1462 | + -- See Wrinkle [Qualified names in record updates]
|
|
| 1463 | + -- in Note [Disambiguating record updates] in GHC.Rename.Pat.
|
|
| 1458 | 1464 | |
| 1459 | 1465 | -- Handle implicit qualified imports in GHCi. See T10439.
|
| 1460 | 1466 | ; ghci_gres <- lookupQualifiedNameGHCi WantBoth rdr
|
| ... | ... | @@ -1532,10 +1538,10 @@ lookupRecUpdFields :: NE.NonEmpty (LHsRecUpdField GhcPs GhcPs) |
| 1532 | 1538 | -> RnM (NE.NonEmpty (HsRecUpdParent GhcRn))
|
| 1533 | 1539 | lookupRecUpdFields flds
|
| 1534 | 1540 | -- See Note [Disambiguating record updates] in GHC.Rename.Pat.
|
| 1535 | - = do { -- Retrieve the possible GlobalRdrElts that each field could refer to.
|
|
| 1541 | + = do { -- (1) Retrieve the possible GlobalRdrElts that each field could refer to.
|
|
| 1536 | 1542 | ; gre_env <- getGlobalRdrEnv
|
| 1537 | 1543 | ; fld1_gres NE.:| other_flds_gres <- mapM (lookupFieldGREs gre_env . getFieldUpdLbl) flds
|
| 1538 | - -- Take an intersection: we are only interested in constructors
|
|
| 1544 | + -- (2) Take an intersection: we are only interested in constructors
|
|
| 1539 | 1545 | -- which have all of the fields.
|
| 1540 | 1546 | ; let possible_GREs = intersect_by_cons fld1_gres other_flds_gres
|
| 1541 | 1547 | |
| ... | ... | @@ -1546,15 +1552,16 @@ lookupRecUpdFields flds |
| 1546 | 1552 | |
| 1547 | 1553 | ; case possible_GREs of
|
| 1548 | 1554 | |
| 1549 | - -- There is at least one parent: we can proceed.
|
|
| 1555 | + -- (3) (a) There is at least one parent: we can proceed.
|
|
| 1550 | 1556 | -- The typechecker might be able to finish disambiguating.
|
| 1551 | 1557 | -- See Note [Type-directed record disambiguation] in GHC.Rename.Pat.
|
| 1552 | 1558 | { p1:ps -> return (p1 NE.:| ps)
|
| 1553 | 1559 | |
| 1554 | - -- There are no possible parents for the record update: compute
|
|
| 1555 | - -- a minimum set of fields which does not belong to any data constructor,
|
|
| 1556 | - -- to report an informative error to the user.
|
|
| 1557 | - ; _ ->
|
|
| 1560 | + -- (3) (b) There are no possible parents for the record update:
|
|
| 1561 | + -- compute a minimal set of fields which does not belong to any
|
|
| 1562 | + -- data constructor, to report an informative error to the user.
|
|
| 1563 | + ; _ -> do
|
|
| 1564 | + hsc_env <- getTopEnv
|
|
| 1558 | 1565 | let
|
| 1559 | 1566 | -- The constructors which have the first field.
|
| 1560 | 1567 | fld1_cons :: UniqSet ConLikeName
|
| ... | ... | @@ -1564,9 +1571,9 @@ lookupRecUpdFields flds |
| 1564 | 1571 | -- The field labels of the constructors which have the first field.
|
| 1565 | 1572 | fld1_cons_fields :: UniqFM ConLikeName [FieldLabel]
|
| 1566 | 1573 | fld1_cons_fields
|
| 1567 | - = fmap (lkp_con_fields gre_env)
|
|
| 1574 | + = fmap (lkp_con_fields hsc_env gre_env)
|
|
| 1568 | 1575 | $ getUniqSet fld1_cons
|
| 1569 | - in failWithTc $ badFieldsUpd (NE.toList flds) fld1_cons_fields } }
|
|
| 1576 | + failWithTc $ badFieldsUpd (NE.toList flds) fld1_cons_fields } }
|
|
| 1570 | 1577 | |
| 1571 | 1578 | where
|
| 1572 | 1579 | intersect_by_cons :: NE.NonEmpty FieldGlobalRdrElt
|
| ... | ... | @@ -1585,13 +1592,22 @@ lookupRecUpdFields flds |
| 1585 | 1592 | , not $ isEmptyUniqSet both_cons
|
| 1586 | 1593 | ]
|
| 1587 | 1594 | |
| 1588 | - lkp_con_fields :: GlobalRdrEnv -> ConLikeName -> [FieldLabel]
|
|
| 1589 | - lkp_con_fields gre_env con =
|
|
| 1595 | + -- Look up all in-scope fields of a 'ConLike'.
|
|
| 1596 | + lkp_con_fields :: HscEnv -> GlobalRdrEnv -> ConLikeName -> [FieldLabel]
|
|
| 1597 | + lkp_con_fields hsc_env gre_env con =
|
|
| 1590 | 1598 | [ fl
|
| 1591 | - | let nm = conLikeName_Name con
|
|
| 1592 | - , gre <- maybeToList $ lookupGRE_Name gre_env nm
|
|
| 1593 | - , con_info <- maybeToList $ recFieldConLike_maybe gre
|
|
| 1594 | - , fl <- conInfoFields con_info ]
|
|
| 1599 | + | let con_nm = conLikeName_Name con
|
|
| 1600 | + gre_info =
|
|
| 1601 | + (greInfo <$> lookupGRE_Name gre_env con_nm)
|
|
| 1602 | + `orElse`
|
|
| 1603 | + lookupGREInfo hsc_env con_nm
|
|
| 1604 | + -- See Wrinkle [Out of scope constructors]
|
|
| 1605 | + -- in Note [Disambiguating record updates] in GHC.Rename.Pat.
|
|
| 1606 | + , IAmConLike con_info <- [ gre_info ]
|
|
| 1607 | + , fl <- conInfoFields con_info
|
|
| 1608 | + , isJust $ lookupGRE_FieldLabel gre_env fl
|
|
| 1609 | + -- Ensure the fields are in scope.
|
|
| 1610 | + ]
|
|
| 1595 | 1611 | |
| 1596 | 1612 | {-**********************************************************************
|
| 1597 | 1613 | * *
|
| ... | ... | @@ -1615,8 +1631,9 @@ getUpdFieldLbls |
| 1615 | 1631 | -- aren't really relevant to the problem.
|
| 1616 | 1632 | --
|
| 1617 | 1633 | -- NB: this error message should only be triggered when all the field names
|
| 1618 | --- are in scope (i.e. each individual field name does belong to some
|
|
| 1634 | +-- are in scope. It's OK if the constructors themselves are not in scope
|
|
| 1635 | +-- (see Wrinkle [Out of scope constructors] in Note [Disambiguating record updates]
|
|
| 1636 | +-- in GHC.Rename.Pat).
|
|
| 1619 | 1637 | badFieldsUpd
|
| 1620 | 1638 | :: (OutputableBndrId p)
|
| 1621 | 1639 | => [LHsRecUpdField (GhcPass p) q]
|
| ... | ... | @@ -1649,7 +1666,7 @@ badFieldsUpd rbinds fld1_cons_fields |
| 1649 | 1666 | in
|
| 1650 | 1667 | -- Fields that don't change the membership status of the set
|
| 1651 | 1668 | -- are redundant and can be dropped.
|
| 1652 | - map (fst . head) $ groupBy ((==) `on` snd) growingSets
|
|
| 1669 | + map (fst . NE.head) $ NE.groupBy ((==) `on` snd) growingSets
|
|
| 1653 | 1670 | |
| 1654 | 1671 | aMember = assert (not (null members) ) fst (head members)
|
| 1655 | 1672 | (members, nonMembers) = partition (or . snd) membership
|
| ... | ... | @@ -1047,25 +1047,90 @@ In a record update, the `lookupRecUpdFields` function tries to determine |
| 1047 | 1047 | the parent datatype by computing the parents (TyCon/PatSyn) which have
|
| 1048 | 1048 | at least one constructor (DataCon/PatSyn) with all of the fields.
|
| 1049 | 1049 | |
| 1050 | -For example, in the (non-overloaded) record update
|
|
| 1050 | +To do this, given the (non-empty) set of fields in the record update,
|
|
| 1051 | +lookupRecUpdFields proceeds as follows:
|
|
| 1051 | 1052 | |
| 1052 | - r { fld1 = 3, fld2 = 'x' }
|
|
| 1053 | + (1) For each field, retrieve all the in-scope GREs that it could possibly
|
|
| 1054 | + refer to.
|
|
| 1053 | 1055 | |
| 1054 | -only the TyCon R contains at least one DataCon which has both of the fields
|
|
| 1055 | -being updated: in this case, MkR1 and MkR2 have both of the updated fields.
|
|
| 1056 | -The TyCon S also has both fields fld1 and fld2, but no single constructor
|
|
| 1057 | -has both of those fields, so S is not a valid parent for this record update.
|
|
| 1056 | + (2) Take an intersection to compute the possible parent data constructors.
|
|
| 1057 | + For example, for an update
|
|
| 1058 | 1058 | |
| 1059 | -Note that this check is namespace-aware, so that a record update such as
|
|
| 1059 | + r { fld1 = 3, fld2 = 'x' }
|
|
| 1060 | + |
|
| 1061 | + the possible parents for each field are:
|
|
| 1062 | + |
|
| 1063 | + fld1: [MkR1 |-> R.fld1, MkR2 |-> R.fld1, MkS1 |> S.fld1]
|
|
| 1064 | + fld2: [MkR1 |-> R.fld2, MkR2 |-> R.fld2, MkS2 |> S.fld2]
|
|
| 1065 | + |
|
| 1066 | + after intersecting by constructor, we get:
|
|
| 1067 | + |
|
| 1068 | + fld1: [MkR1 |-> R.fld1, MkR2 |-> R.fld1]
|
|
| 1069 | + fld2: [MkR1 |-> R.fld2, MkR2 |-> R.fld2]
|
|
| 1070 | + |
|
| 1071 | + This reflects the fact that only the TyCon R contains at least one DataCon
|
|
| 1072 | + which has both of the fields being updated: MkR1 and MkR2.
|
|
| 1073 | + The TyCon S also has both fields fld1 and fld2, but no single constructor
|
|
| 1074 | + has both of those fields, so S is not a valid parent for this record update.
|
|
| 1075 | + |
|
| 1076 | + (3)
|
|
| 1077 | + (a)
|
|
| 1078 | + If there is at least one possible parent TyCon, succeed. The typechecker
|
|
| 1079 | + might still be able to disambiguate if there remains more than one
|
|
| 1080 | + candidate parent TyCon (see Note [Type-directed record disambiguation]).
|
|
| 1081 | + (b)
|
|
| 1082 | + Otherwise, report an error saying "No constructor has all these fields".
|
|
| 1083 | + This is the job of GHC.Rename.Env.badFieldsUpd. This function tries
|
|
| 1084 | + to report a minimal set of fields, so that in a record update like
|
|
| 1085 | + |
|
| 1086 | + r { fld1 = x1, fld2 = x2, [...], fld99 = x99 }
|
|
| 1087 | + |
|
| 1088 | + we don't report a massive error message saying "No constructor has all
|
|
| 1089 | + the fields fld1, ..., fld99" and instead report e.g. "No constructor
|
|
| 1090 | + has all the fields { fld3, fld17 }".
|
|
| 1091 | + |
|
| 1092 | +Wrinkle [Qualified names in record updates]
|
|
| 1093 | + |
|
| 1094 | + Note that we must take into account qualified names in (1), so that a record
|
|
| 1095 | + update such as
|
|
| 1060 | 1096 | |
| 1061 | 1097 | import qualified M ( R (fld1, fld2) )
|
| 1062 | 1098 | f r = r { M.fld1 = 3 }
|
| 1063 | 1099 | |
| 1064 | -is unambiguous, as only R contains the field fld1 in the M namespace.
|
|
| 1065 | -(See however #22122 for issues relating to the usage of exact Names in
|
|
| 1066 | -record fields.)
|
|
| 1100 | + is unambiguous: only R contains the field fld1 with the M qualifier.
|
|
| 1101 | + |
|
| 1102 | + The function that looks up the GREs for the record update is 'lookupFieldGREs',
|
|
| 1103 | + which uses 'lookupGRE env (LookupRdrName ...)', ensuring that we correctly
|
|
| 1104 | + filter the GREs with the correct module qualification (with 'pickGREs').
|
|
| 1105 | + |
|
| 1106 | + (See however #22122 for issues relating to the usage of exact Names in
|
|
| 1107 | + record fields.)
|
|
| 1108 | + |
|
| 1109 | +Wrinkle [Out of scope constructors]
|
|
| 1110 | + |
|
| 1111 | + For (3)(b), we have an invalid record update because no constructor has
|
|
| 1112 | + all of the fields of the record update. The 'badFieldsUpd' then tries to
|
|
| 1113 | + compute a minimal set of fields which are not children of any single
|
|
| 1114 | + constructor. The way this is done is explained in
|
|
| 1115 | + Note [Finding the conflicting fields] in GHC.Rename.Env, but in short that
|
|
| 1116 | + function needs a mapping from ConLike to all of its fields to do its business.
|
|
| 1117 | + (You may remark that we did not need such a mapping for step (2).)
|
|
| 1118 | + |
|
| 1119 | + This means we need to look up each constructor and find its fields; this
|
|
| 1120 | + information is stored in the GREInfo field of a constructor GRE.
|
|
| 1121 | + We need this information even if the constructor itself is not in scope, so
|
|
| 1122 | + we proceed as follows:
|
|
| 1123 | + |
|
| 1124 | + 1. First look up the constructor in the GlobalRdrEnv, using lookupGRE_Name.
|
|
| 1125 | + This handles constructors defined in the current module being renamed,
|
|
| 1126 | + as well as in-scope imported constructors.
|
|
| 1127 | + 2. If that fails (e.g. the field is imported but the constructor is not),
|
|
| 1128 | + then look up the GREInfo of the constructor in the TypeEnv, using
|
|
| 1129 | + lookupGREInfo. This makes sure we give the right error message even when
|
|
| 1130 | + the constructors are not in scope (#26391).
|
|
| 1067 | 1131 | |
| 1068 | -See also Note [Type-directed record disambiguation] in GHC.Tc.Gen.Expr.
|
|
| 1132 | + Note that we do need (1), as (2) does not handle constructors defined in the
|
|
| 1133 | + current module being renamed (as those have not yet been added to the TypeEnv).
|
|
| 1069 | 1134 | |
| 1070 | 1135 | Note [Using PatSyn FreeVars]
|
| 1071 | 1136 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
| ... | ... | @@ -1200,13 +1200,34 @@ Wrinkle [Using IdSig] |
| 1200 | 1200 | |
| 1201 | 1201 | Note [Type-directed record disambiguation]
|
| 1202 | 1202 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
| 1203 | -GHC currently supports an additional type-directed disambiguation
|
|
| 1204 | -mechanism, which is deprecated and scheduled for removal as part of
|
|
| 1205 | -GHC proposal #366 https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0366-no-ambiguous-field-access.rst.
|
|
| 1206 | - |
|
| 1207 | -To perform this disambiguation, when there are multiple possible parents for
|
|
| 1208 | -a record update, the renamer defers to the typechecker.
|
|
| 1209 | -See GHC.Tc.Gen.Expr.disambiguateRecordBinds, and in particular the auxiliary
|
|
| 1203 | +Deprecation notice:
|
|
| 1204 | + The type-directed disambiguation mechanism for record updates described in
|
|
| 1205 | + this Note is deprecated, as per GHC proposal #366 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0366-no-ambiguous-field-access.rst).
|
|
| 1206 | + The removal of type-directed disambiguation for record updates is tracked
|
|
| 1207 | + in GHC ticket #19461, but progress towards this goal has stalled.
|
|
| 1208 | + |
|
| 1209 | + Why? There are several suggested replacement mechanisms, such as:
|
|
| 1210 | + 1. using module qualification to disambiguate,
|
|
| 1211 | + 2. using OverloadedRecordUpdate for type-directed disambiguation
|
|
| 1212 | + (as described in Note [Overview of record dot syntax] in GHC.Hs.Expr).
|
|
| 1213 | + However, these solutions do not work in all situations:
|
|
| 1214 | + 1. Module qualification doesn't work for fields defined in the current module,
|
|
| 1215 | + nor to disambiguate between constructors of different data family instances
|
|
| 1216 | + of a given parent data family TyCon.
|
|
| 1217 | + 2. OverloadedRecordUpdate does not allow for type-changing record update,
|
|
| 1218 | + nor can it deal with fields with existentials or polytypes.
|
|
| 1219 | + There are also some avenues to improve the renamer's ability to disambiguate:
|
|
| 1220 | + - GHC ticket #23032 suggests using as-patterns to disambiguate in the renamer.
|
|
| 1221 | + - GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/537
|
|
| 1222 | + suggests a syntactic form of type-directed disambiguation that could be
|
|
| 1223 | + carried out in the renamer.
|
|
| 1224 | + Neither of these have been accepted/implemented at the time of writing (Sept 2025).
|
|
| 1225 | + This means that removal of type-directed disambiguation is currently stalled.
|
|
| 1226 | + |
|
| 1227 | +GHC tries to disambiguate record updates in the renamer, as described in
|
|
| 1228 | +Note [Disambiguating record updates] in GHC.Rename.Pat. However, if the renamer
|
|
| 1229 | +is unable to disambiguate, the renamer will defer to the typechecker: see
|
|
| 1230 | +GHC.Tc.Gen.Expr.disambiguateRecordBinds, and in particular the auxiliary
|
|
| 1210 | 1231 | function identifyParentLabels, which picks a parent for the record update
|
| 1211 | 1232 | using the following additional mechanisms:
|
| 1212 | 1233 |
| 1 | +module T26391 where
|
|
| 2 | + |
|
| 3 | +import Data.Semigroup (getSum, getProduct)
|
|
| 4 | + |
|
| 5 | +-- This record update is invalid (no constructor has both 'getSum' and 'getProduct').
|
|
| 6 | +--
|
|
| 7 | +-- This test makes sure that GHC can handle reporting a good error even when
|
|
| 8 | +-- the parent constructors (here, Sum and Product) are out of scope.
|
|
| 9 | +a = undefined { getSum = undefined, getProduct = undefined } |
| 1 | +T26391.hs:9:5: error: [GHC-14392]
|
|
| 2 | + Invalid record update.
|
|
| 3 | + No constructor in scope has all of the following fields:
|
|
| 4 | + ‘getSum’, ‘getProduct’
|
|
| 5 | + |
| ... | ... | @@ -39,6 +39,7 @@ test('T17420', [extra_files(['T17420A.hs'])], multimod_compile_fail, |
| 39 | 39 | test('T17469', [extra_files(['T17469A.hs'])], multimod_compile_fail,
|
| 40 | 40 | ['T17469', ''])
|
| 41 | 41 | test('T17965', normal, compile_fail, [''])
|
| 42 | +test('T26391', normal, compile_fail, [''])
|
|
| 42 | 43 | test('DRFHoleFits', extra_files(['DRFHoleFits_A.hs']), multimod_compile_fail, ['DRFHoleFits', '-v0'])
|
| 43 | 44 | test('DRFPartialFields', normal, compile_fail, [''])
|
| 44 | 45 | test('T16745', extra_files(['T16745C.hs', 'T16745B.hs']), multimod_compile_fail, ['T16745A', ''])
|