[Git][ghc/ghc][wip/T21730-import] 2 commits: Rename implicit => generated

Brandon Chinn pushed to branch wip/T21730-import at Glasgow Haskell Compiler / GHC Commits: 4ac945d9 by Brandon Chinn at 2025-08-15T20:25:18-07:00 Rename implicit => generated - - - - - 17b879b3 by Brandon Chinn at 2025-08-15T20:52:09-07:00 Generated imports beat user imports for minimal imports - - - - - 8 changed files: - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Types/Name/Reader.hs - ghc/GHCi/UI.hs - testsuite/tests/parser/should_compile/T7476/T7476.stdout Changes: ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -878,14 +878,14 @@ hsModuleToModSummary home_keys pn hsc_src modname let (src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps implicit_prelude = xopt LangExt.ImplicitPrelude dflags - implicit_imports = mkPrelImports modname implicit_prelude imps + generated_imports = mkPrelImports modname implicit_prelude imps rn_pkg_qual = renameRawPkgQual (hsc_unit_env hsc_env) modname convImport (L _ i) = (convImportLevel (ideclLevelSpec i), rn_pkg_qual (ideclPkgQual i), reLoc $ ideclName i) extra_sig_imports <- liftIO $ findExtraSigImports hsc_env hsc_src modname - let normal_imports = map convImport (implicit_imports ++ ord_idecls) + let normal_imports = map convImport (generated_imports ++ ord_idecls) (implicit_sigs, inst_deps) <- liftIO $ implicitRequirementsShallow hsc_env normal_imports -- So that Finder can find it, even though it doesn't exist... ===================================== compiler/GHC/Hs/ImpExp.hs ===================================== @@ -80,16 +80,18 @@ type instance XCImportDecl GhcTc = DataConCantHappen data XImportDeclPass = XImportDeclPass { ideclAnn :: EpAnn EpAnnImportDecl , ideclSourceText :: SourceText -- Note [Pragma source text] in "GHC.Types.SourceText" - , ideclImplicit :: Bool -- ^ See Note [Implicit imports] + , ideclGenerated :: Bool -- ^ See Note [Generated imports] } deriving (Data) -{- Note [Implicit imports] -~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Generated imports] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ GHC generates an `ImportDecl` to represent the invisible `import Prelude` that appears in any file that omits `import Prelude`, setting this field to indicate that the import doesn't appear in the -original source. True => implicit import (of Prelude) +original source. + +Plugins may also introduce generated imports. -} type instance XXImportDecl (GhcPass _) = DataConCantHappen @@ -165,8 +167,8 @@ instance (OutputableBndrId p where pp_implicit ext = let implicit = case ghcPass @p of - GhcPs | XImportDeclPass { ideclImplicit = implicit } <- ext -> implicit - GhcRn | XImportDeclPass { ideclImplicit = implicit } <- ext -> implicit + GhcPs | XImportDeclPass { ideclGenerated = implicit } <- ext -> implicit + GhcRn | XImportDeclPass { ideclGenerated = implicit } <- ext -> implicit GhcTc -> dataConCantHappen ext in if implicit then text "(implicit)" else empty ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -348,7 +348,7 @@ enrichHie ts (hsGrp, imports, exports, docs, modName) ev_bs insts tcs tte = modName <- toHie (IEC Export <$> modName) tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts rasts <- processGrp hsGrp - imps <- toHie $ filter (not . ideclImplicit . ideclExt . unLoc) imports + imps <- toHie $ filter (not . ideclGenerated . ideclExt . unLoc) imports exps <- toHie $ fmap (map $ IEC Export . fst) exports docs <- toHie docs -- Add Instance bindings ===================================== compiler/GHC/Parser/Header.hs ===================================== @@ -100,12 +100,12 @@ getImports popts implicit_prelude buf filename source_filename = do mod = mb_mod `orElse` L (noAnnSrcSpan main_loc) mAIN_NAME (src_idecls, ord_idecls) = partition ((== IsBoot) . ideclSource . unLoc) imps - implicit_imports = mkPrelImports (unLoc mod) implicit_prelude imps + generated_imports = mkPrelImports (unLoc mod) implicit_prelude imps convImport (L _ (i :: ImportDecl GhcPs)) = (convImportLevel (ideclLevelSpec i), ideclPkgQual i, reLoc $ ideclName i) convImport_src (L _ (i :: ImportDecl GhcPs)) = (reLoc $ ideclName i) in return (map convImport_src src_idecls - , map convImport (implicit_imports ++ ord_idecls) + , map convImport (generated_imports ++ ord_idecls) , reLoc mod) @@ -146,7 +146,7 @@ mkPrelImports this_mod implicit_prelude import_decls = L loc $ ImportDecl { ideclExt = XImportDeclPass { ideclAnn = noAnn , ideclSourceText = NoSourceText - , ideclImplicit = True -- Implicit! + , ideclGenerated = True -- Generated! }, ideclName = L loc pRELUDE_NAME, ideclPkgQual = NoRawPkgQual, ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -317,7 +317,7 @@ rnImportDecl this_mod , ideclSafe = mod_safe , ideclLevelSpec = import_level , ideclQualified = qual_style - , ideclExt = XImportDeclPass { ideclImplicit = implicit } + , ideclExt = XImportDeclPass { ideclGenerated = implicit } , ideclAs = as_mod, ideclImportList = imp_details }), import_reason) = setSrcSpanA loc $ do @@ -1922,25 +1922,27 @@ type ImportDeclUsage warnUnusedImportDecls :: TcGblEnv -> HscSource -> RnM () warnUnusedImportDecls gbl_env hsc_src = do { uses <- readMutVar (tcg_used_gres gbl_env) - ; let user_imports = filterOut - (ideclImplicit . ideclExt . unLoc) - (tcg_rn_imports gbl_env) - -- This whole function deals only with *user* imports - -- both for warning about unnecessary ones, and for - -- deciding the minimal ones + ; let imports = tcg_rn_imports gbl_env rdr_env = tcg_rdr_env gbl_env - ; let usage :: [ImportDeclUsage] - usage = findImportUsage user_imports uses + -- We should only warn for unnecessary *user* imports, but deciding + -- minimal imports should take generated imports into account + ; let usageUserImports = findImportUsage (excludeGenerated imports) uses + usageAllImports = findImportUsage imports uses ; traceRn "warnUnusedImportDecls" $ (vcat [ text "Uses:" <+> ppr uses - , text "Import usage" <+> ppr usage]) + , text "Usage all user imports: " <+> ppr usageUserImports + , text "Usage all imports: " <+> ppr usageAllImports]) - ; mapM_ (warnUnusedImport rdr_env) usage + ; mapM_ (warnUnusedImport rdr_env) usageUserImports ; whenGOptM Opt_D_dump_minimal_imports $ - printMinimalImports hsc_src usage } + printMinimalImports hsc_src usageAllImports } + +-- | Exclude generated imports +excludeGenerated :: [LImportDecl GhcRn] -> [LImportDecl GhcRn] +excludeGenerated = filterOut (ideclGenerated . ideclExt . unLoc) findImportUsage :: [LImportDecl GhcRn] -> [GlobalRdrElt] @@ -2208,8 +2210,10 @@ x,y to avoid name-shadowing warnings. Example (#9061) Note [Printing minimal imports] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -To print the minimal imports we walk over the user-supplied import -decls, and simply trim their import lists. NB that +To print the minimal imports we walk over all import decls (both user-supplied +and generated), trim their import lists, then filter out generated decls. + +NB that * We do *not* change the 'qualified' or 'as' parts! @@ -2301,7 +2305,7 @@ classifyGREs = partition (not . isRecFldGRE) printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM () -- See Note [Printing minimal imports] printMinimalImports hsc_src imports_w_usage - = do { imports' <- getMinimalImports imports_w_usage + = do { imports' <- excludeGenerated <$> getMinimalImports imports_w_usage ; this_mod <- getModule ; dflags <- getDynFlags ; liftIO $ withFile (mkFilename dflags this_mod) WriteMode $ \h -> ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -2041,10 +2041,13 @@ bestImport iss = NE.head $ NE.sortBy best iss -- Less means better -- Unqualified always wins over qualified; then -- import-all wins over import-some; then + -- generated wins over user-specified; then -- earlier declaration wins over later best (ImpSpec { is_item = item1, is_decl = d1 }) (ImpSpec { is_item = item2, is_decl = d2 }) - = (is_qual d1 `compare` is_qual d2) S.<> best_item item1 item2 S.<> + = (is_qual d1 `compare` is_qual d2) S.<> + best_item item1 item2 S.<> + compareGenerated (is_dloc d1) (is_dloc d2) S.<> SrcLoc.leftmost_smallest (is_dloc d1) (is_dloc d2) best_item :: ImpItemSpec -> ImpItemSpec -> Ordering @@ -2055,6 +2058,11 @@ bestImport iss = NE.head $ NE.sortBy best iss (ImpSome { is_explicit = e2 }) = e1 `compare` e2 -- False < True, so if e1 is explicit and e2 is not, we get GT + compareGenerated UnhelpfulSpan{} UnhelpfulSpan{} = EQ + compareGenerated UnhelpfulSpan{} RealSrcSpan{} = LT + compareGenerated RealSrcSpan{} UnhelpfulSpan{} = GT + compareGenerated RealSrcSpan{} RealSrcSpan{} = EQ + {- Note [Choosing the best import declaration] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When reporting unused import declarations we use the following rules. ===================================== ghc/GHCi/UI.hs ===================================== @@ -527,7 +527,7 @@ interactiveUI config srcs maybe_exprs = do let prelude_import = case simpleImportDecl preludeModuleName of -- Set to True because Prelude is implicitly imported. - impDecl@ImportDecl{ideclExt=ext} -> impDecl{ideclExt = ext{ideclImplicit=True}} + impDecl@ImportDecl{ideclExt=ext} -> impDecl{ideclExt = ext{ideclGenerated=True}} empty_cache <- liftIO newIfaceCache startGHCi (runGHCi srcs maybe_exprs) GHCiState{ progname = default_progname, ===================================== testsuite/tests/parser/should_compile/T7476/T7476.stdout ===================================== @@ -1 +1 @@ -import Control.Applicative ( Applicative(pure), (<**>) ) +import Control.Applicative ( (<**>) ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bc29a798654f3452a23ce5ea019b881... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bc29a798654f3452a23ce5ea019b881... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Brandon Chinn (@brandonchinn178)