[Git][ghc/ghc][master] Use lookupOccRn_maybe in TH.lookupName
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Jan 15 19:16:04 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00
Use lookupOccRn_maybe in TH.lookupName
When looking up a value, we want to be able to find both variables
and record fields. So we should not use the lookupSameOccRn_maybe
function, as we can't know ahead of time which record field namespace
a record field with the given textual name will belong to.
Fixes #24293
- - - - -
6 changed files:
- compiler/GHC/Tc/Gen/Splice.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293b.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293c.hs
- + testsuite/tests/overloadedrecflds/should_compile/T24293c.stderr
- testsuite/tests/overloadedrecflds/should_compile/all.T
Changes:
=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -1944,8 +1944,8 @@ lookupName :: Bool -- True <=> type namespace
-- False <=> value namespace
-> String -> TcM (Maybe TH.Name)
lookupName is_type_name s
- = do { mb_nm <- lookupSameOccRn_maybe rdr_name
- ; return (fmap reifyName mb_nm) }
+ = do { mb_nm <- lookupOccRn_maybe rdr_name
+ ; return (fmap (reifyName . greName) mb_nm) }
where
th_name = TH.mkName s -- Parses M.x into a base of 'x' and a module of 'M'
@@ -1960,6 +1960,12 @@ lookupName is_type_name s
| otherwise
= if isLexCon occ_fs then mkDataOccFS occ_fs
else mkVarOccFS occ_fs
+ -- NB: when we pick the variable namespace, we
+ -- might well obtain an identifier in a record
+ -- field namespace, as lookupOccRn_maybe looks in
+ -- record field namespaces when looking up variables.
+ -- This ensures we can look up record fields using
+ -- this function (#24293).
rdr_name = case TH.nameModule th_name of
Nothing -> mkRdrUnqual occ
=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T24293 where
+import Language.Haskell.TH
+
+data Cheval = Cheval { hibou :: Int }
+
+name = $(do
+ n <- lookupValueName "hibou"
+ pure $ LitE $ StringL $ show n)
=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293b.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE NoFieldSelectors #-}
+module T24293b where
+import Language.Haskell.TH
+
+data Cheval = Cheval { hibou :: Int }
+
+hibou :: Bool
+hibou = False
+
+name = $(do
+ n <- lookupValueName "hibou"
+ pure $ LitE $ StringL $ show n)
=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293c.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE DuplicateRecordFields #-}
+module T24293c where
+import Language.Haskell.TH
+
+data Cheval = Cheval { hibou :: Int }
+data Agneau = Agneau { hibou :: Bool }
+
+name = $(do
+ n <- lookupValueName "hibou"
+ pure $ LitE $ StringL $ show n)
=====================================
testsuite/tests/overloadedrecflds/should_compile/T24293c.stderr
=====================================
@@ -0,0 +1,11 @@
+
+T24293c.hs:9:9: error: [GHC-87543]
+ • Ambiguous occurrence ‘hibou’.
+ It could refer to
+ either the field ‘hibou’ of record ‘Cheval’,
+ defined at T24293c.hs:6:24,
+ or the field ‘hibou’ of record ‘Agneau’,
+ defined at T24293c.hs:7:24.
+ • In the untyped splice:
+ $(do n <- lookupValueName "hibou"
+ pure $ LitE $ StringL $ show n)
=====================================
testsuite/tests/overloadedrecflds/should_compile/all.T
=====================================
@@ -57,3 +57,6 @@ test('T22106_D', [extra_files(['T22106_aux.hs'])], multimod_compile, ['T22106_D'
test('T22424', req_th, compile, ['-this-unit-id="me"'])
test('T23279', [extra_files(['T23279_aux.hs'])], multimod_compile, ['T23279', '-v0'])
test('T23557', [extra_files(['T23557_aux.hs'])], multimod_compile, ['T23557', '-v0'])
+test('T24293', req_th, compile, [''])
+test('T24293b', req_th, compile, [''])
+test('T24293c', req_th, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5fc7304d56c7a1e0a7bc6e53e23b976772fc10e
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5fc7304d56c7a1e0a7bc6e53e23b976772fc10e
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/20240115/a80ed86a/attachment-0001.html>
More information about the ghc-commits
mailing list