[Git][ghc/ghc][master] Add a hint to enable ExplicitNamespaces for type operator imports (Fixes/Enhances #20007)
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Jul 10 20:59:07 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
8e11630e by jade at 2023-07-10T16:58:40-04:00
Add a hint to enable ExplicitNamespaces for type operator imports (Fixes/Enhances #20007)
As suggested in #20007 and implemented in !8895, trying to import type operators
will suggest a fix to use the 'type' keyword, without considering whether
ExplicitNamespaces is enabled. This patch will query whether ExplicitNamespaces
is enabled and add a hint to suggest enabling ExplicitNamespaces if it isn't enabled,
alongside the suggestion of adding the 'type' keyword.
- - - - -
7 changed files:
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Types/Hint/Ppr.hs
- + testsuite/tests/module/T20007.hs
- + testsuite/tests/module/T20007.stderr
- testsuite/tests/module/all.T
Changes:
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -2139,11 +2139,12 @@ badImportItemErr
-> TcRn ImportLookupReason
badImportItemErr iface decl_spec ie sub avails = do
patsyns_enabled <- xoptM LangExt.PatternSynonyms
- pure (ImportLookupBad importErrorKind iface decl_spec ie patsyns_enabled)
+ expl_ns_enabled <- xoptM LangExt.ExplicitNamespaces
+ pure (ImportLookupBad (importErrorKind expl_ns_enabled) iface decl_spec ie patsyns_enabled)
where
- importErrorKind
+ importErrorKind expl_ns_enabled
| any checkIfTyCon avails = case sub of
- BadImportIsParent -> BadImportAvailTyCon
+ BadImportIsParent -> BadImportAvailTyCon expl_ns_enabled
BadImportIsSubordinate -> BadImportNotExportedSubordinates unavailableChildren
| any checkIfVarName avails = BadImportAvailVar
| Just con <- find checkIfDataCon avails = BadImportAvailDataCon (availOccName con)
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -3108,7 +3108,9 @@ instance Diagnostic TcRnMessage where
in case k of
BadImportAvailVar -> [ImportSuggestion occ $ CouldRemoveTypeKeyword mod_name]
BadImportNotExported -> noHints
- BadImportAvailTyCon -> [ImportSuggestion occ $ CouldAddTypeKeyword mod_name]
+ BadImportAvailTyCon ex_ns ->
+ [useExtensionInOrderTo empty LangExt.ExplicitNamespaces | not ex_ns]
+ ++ [ImportSuggestion occ $ CouldAddTypeKeyword mod_name]
BadImportAvailDataCon par -> [ImportSuggestion occ $ ImportDataCon (Just (mod_name, patsyns_enabled)) par]
BadImportNotExportedSubordinates{} -> noHints
TcRnImportLookup{}
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -5263,7 +5263,9 @@ data BadImportKind
-- | Module does not export...
= BadImportNotExported
-- | Missing @type@ keyword when importing a type.
- | BadImportAvailTyCon
+ -- e.g. `import TypeLits( (+) )`, where TypeLits exports a /type/ (+), not a /term/ (+)
+ -- Then we want to suggest using `import TypeLits( type (+) )`
+ | BadImportAvailTyCon Bool -- ^ is ExplicitNamespaces enabled?
-- | Trying to import a data constructor directly, e.g.
-- @import Data.Maybe (Just)@ instead of @import Data.Maybe (Maybe(Just))@
| BadImportAvailDataCon OccName
=====================================
compiler/GHC/Types/Hint/Ppr.hs
=====================================
@@ -310,12 +310,12 @@ pprImportSuggestion occ_name (CouldUnhideFrom mods)
| (mod,imv) <- NE.toList mods
])
pprImportSuggestion occ_name (CouldAddTypeKeyword mod)
- = vcat [ text "Add the" <+> quotes (text "type")
+ = vcat [ text "Add the" <+> quotes (text "type")
<+> text "keyword to the import statement:"
- , nest 2 $ text "import"
+ , nest 2 $ text "import"
<+> ppr mod
<+> parens_sp (text "type" <+> pprPrefixOcc occ_name)
- ]
+ ]
where
parens_sp d = parens (space <> d <> space)
pprImportSuggestion occ_name (CouldRemoveTypeKeyword mod)
=====================================
testsuite/tests/module/T20007.hs
=====================================
@@ -0,0 +1 @@
+import Data.Type.Equality ( (~) )
=====================================
testsuite/tests/module/T20007.stderr
=====================================
@@ -0,0 +1,8 @@
+
+T20007.hs:1:29: [GHC-56449]
+ In the import of ‘Data.Type.Equality’:
+ an item called ‘(~)’ is exported, but it is a type.
+ Suggested fixes:
+ Use ExplicitNamespaces
+ Add the ‘type’ keyword to the import statement:
+ import Data.Type.Equality ( type (~) )
=====================================
testsuite/tests/module/all.T
=====================================
@@ -298,3 +298,4 @@ test('T21752', [extra_files(['T21752A.hs', 'T21752.hs'])], multimod_compile, ['T
test('TupleTyConUserSyntax', [extra_files(['TupleTyConUserSyntaxA.hs', 'TupleTyConUserSyntax.hs'])], multimod_compile, ['TupleTyConUserSyntax', '-v0'])
test('T21826', normal, compile_fail, [''])
+test('T20007', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8e11630ec9669414b0b37a3097fb509d60702b0a
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8e11630ec9669414b0b37a3097fb509d60702b0a
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/20230710/60c3a4a1/attachment-0001.html>
More information about the ghc-commits
mailing list