[Git][ghc/ghc][wip/amg/T21625] Allow imports to reference multiple fields with the same name (#21625)

Adam Gundry (@adamgundry) gitlab at gitlab.haskell.org
Wed Aug 24 20:27:52 UTC 2022



Adam Gundry pushed to branch wip/amg/T21625 at Glasgow Haskell Compiler / GHC


Commits:
7f03aae6 by Adam Gundry at 2022-08-24T21:27:24+01:00
Allow imports to reference multiple fields with the same name (#21625)

If a module `M` exports two fields `f` (using DuplicateRecordFields), we can
still accept

    import M (f)
    import M hiding (f)

and treat `f` as referencing both of them.  This was accepted in GHC 9.0, but gave
rise to an ambiguity error in GHC 9.2.  See #21625.

This patch also documents this behaviour in the user's guide, and updates the
test for #16745 which is now treated differently.

- - - - -


7 changed files:

- compiler/GHC/Rename/Names.hs
- docs/users_guide/exts/duplicate_record_fields.rst
- + testsuite/tests/overloadedrecflds/should_compile/T21625.hs
- + testsuite/tests/overloadedrecflds/should_compile/T21625B.hs
- testsuite/tests/overloadedrecflds/should_compile/all.T
- testsuite/tests/overloadedrecflds/should_fail/T16745.stderr
- testsuite/tests/overloadedrecflds/should_fail/T16745A.hs


Changes:

=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -1165,7 +1165,7 @@ Suppose we have:
     data T = mkT { foo :: Int }
 
   module N where
-    import M (foo)    -- this is an ambiguity error (A)
+    import M (foo)    -- this is allowed (A)
     import M (S(foo)) -- this is allowed (B)
 
 Here M exports the OccName 'foo' twice, so we get an imp_occ_env where 'foo'
@@ -1176,8 +1176,8 @@ names (see Note [FieldLabel] in GHC.Types.FieldLabel).
          , $sel:foo:MKT -> (foo, T(foo), Nothing)
          ]
 
-Then when we look up 'foo' in lookup_name for case (A) we get both entries and
-hence report an ambiguity error.  Whereas in case (B) we reach the lookup_ie
+Then when we look up 'foo' in lookup_names for case (A) we get both entries and
+hence two Avails.  Whereas in case (B) we reach the lookup_ie
 case for IEThingWith, which looks up 'S' and then finds the unique 'foo' amongst
 its children.
 
@@ -1252,13 +1252,21 @@ filterImports iface decl_spec (Just (want_hiding, L l import_items))
     isAvailTC AvailTC{} = True
     isAvailTC _ = False
 
+    -- Look up a RdrName used in an import, failing if it is ambiguous
+    -- (e.g. because it refers to multiple record fields)
     lookup_name :: IE GhcPs -> RdrName -> IELookupM (Name, AvailInfo, Maybe Name)
-    lookup_name ie rdr
+    lookup_name ie rdr = do
+        xs <- lookup_names ie rdr
+        case xs of
+          [cax] -> return cax
+          _     -> failLookupWith (AmbiguousImport rdr (map sndOf3 xs))
+
+    -- Look up a RdrName used in an import, returning multiple values if there
+    -- are several fields with the same name exposed by the module
+    lookup_names :: IE GhcPs -> RdrName -> IELookupM [(Name, AvailInfo, Maybe Name)]
+    lookup_names ie rdr
        | isQual rdr              = failLookupWith (QualImportError rdr)
-       | Just succ <- mb_success = case nonDetNameEnvElts succ of
-                                     -- See Note [Importing DuplicateRecordFields]
-                                     [(c,a,x)] -> return (greNameMangledName c, a, x)
-                                     xs -> failLookupWith (AmbiguousImport rdr (map sndOf3 xs))
+       | Just succ <- mb_success = return $ map (\ (c,a,x) -> (greNameMangledName c, a, x)) (nonDetNameEnvElts succ)
        | otherwise               = failLookupWith (BadImport ie)
       where
         mb_success = lookupOccEnv imp_occ_env (rdrNameOcc rdr)
@@ -1311,9 +1319,11 @@ filterImports iface decl_spec (Just (want_hiding, L l import_items))
     lookup_ie ie = handle_bad_import $
       case ie of
         IEVar _ (L l n) -> do
-            (name, avail, _) <- lookup_name ie $ ieWrappedName n
+            -- See Note [Importing DuplicateRecordFields]
+            xs <- lookup_names ie (ieWrappedName n)
             return ([(IEVar noExtField (L l (replaceWrappedName n name)),
-                                                  trimAvail avail name)], [])
+                                                  trimAvail avail name)
+                    | (name, avail, _) <- xs ], [])
 
         IEThingAll _ (L l tc) -> do
             (name, avail, mb_parent) <- lookup_name ie $ ieWrappedName tc


=====================================
docs/users_guide/exts/duplicate_record_fields.rst
=====================================
@@ -57,4 +57,11 @@ However, this would not be permitted, because ``x`` is ambiguous: ::
 
     module M (x) where ...
 
-The same restrictions apply on imports.
+For ``import`` statements, it is possible to import multiple fields with the
+same name, as well as importing individual fields as part of their datatypes.
+For example, the following imports are allowed: ::
+
+    import M (S(x))        -- imports the type S and the 'x' field of S (but not the field of T)
+    import M (x)           -- imports both 'x' fields
+    import M hiding (S(x)) -- imports everything except the type S and its 'x' field
+    import M hiding (x)    -- imports everything except the two 'x' fields


=====================================
testsuite/tests/overloadedrecflds/should_compile/T21625.hs
=====================================
@@ -0,0 +1,5 @@
+module T21625 where
+
+import T21625B hiding (B, f)
+
+c = C 'x'


=====================================
testsuite/tests/overloadedrecflds/should_compile/T21625B.hs
=====================================
@@ -0,0 +1,6 @@
+{-# LANGUAGE DuplicateRecordFields #-}
+
+module T21625B where
+
+data B = B {f :: Int}
+data C = C {f :: Char}


=====================================
testsuite/tests/overloadedrecflds/should_compile/all.T
=====================================
@@ -11,3 +11,4 @@ test('T18999_FieldSelectors', normal, compile, [''])
 test('T19154', normal, compile, [''])
 test('T20723', normal, compile, [''])
 test('T20989', normal, compile, [''])
+test('T21625', [], multimod_compile, ['T21625', '-v0'])


=====================================
testsuite/tests/overloadedrecflds/should_fail/T16745.stderr
=====================================
@@ -3,12 +3,12 @@
 [3 of 4] Compiling T16745D          ( T16745D.hs, T16745D.o )
 [4 of 4] Compiling T16745A          ( T16745A.hs, T16745A.o )
 
-T16745A.hs:3:24: error:
-    Ambiguous name ‘field’ in import item. It could refer to:
-      T16745C.field
-      T16745B.R(field)
-
-T16745A.hs:4:24: error:
-    Ambiguous name ‘foo’ in import item. It could refer to:
-      T16745D.T(foo)
-      T16745D.S(foo)
+T16745A.hs:8:9: error:
+    Ambiguous occurrence ‘field’
+    It could refer to
+       either the field ‘field’ of record ‘T16745B.R’,
+              imported from ‘T16745B’ at T16745A.hs:3:24-28
+              (and originally defined at T16745B.hs:11:14-18)
+           or ‘T16745B.field’,
+              imported from ‘T16745B’ at T16745A.hs:3:24-28
+              (and originally defined in ‘T16745C’ at T16745C.hs:2:1-5)


=====================================
testsuite/tests/overloadedrecflds/should_fail/T16745A.hs
=====================================
@@ -1,6 +1,8 @@
 module T16745A where
 
-import T16745B hiding (field)
-import T16745D hiding (foo)
+import T16745B        (field)  -- imports both 'field's
+import T16745D hiding (foo)    -- allowed, hides both 'foo' fields
 
-wrong = foo -- should not be in scope
+foo = foo
+
+wrong = field -- ambiguous which 'field' is meant



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f03aae6ca06d8ef304f9a6d70f2f1650b86d69b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f03aae6ca06d8ef304f9a6d70f2f1650b86d69b
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/20220824/e63bedaf/attachment-0001.html>


More information about the ghc-commits mailing list