[Git][ghc/ghc][wip/T21730-import] Unify im_implicitImports + im_generatedImports

Brandon Chinn pushed to branch wip/T21730-import at Glasgow Haskell Compiler / GHC Commits: 768dc8b0 by Brandon Chinn at 2025-08-02T09:02:04-07:00 Unify im_implicitImports + im_generatedImports - - - - - 6 changed files: - compiler/GHC/Driver/Session/Inspect.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Types/Name/Reader.hs Changes: ===================================== compiler/GHC/Driver/Session/Inspect.hs ===================================== @@ -132,7 +132,7 @@ availsToGlobalRdrEnv hsc_env mod avails -- all the specified modules into the global interactive module imp_spec = ImpSpec { is_decl = decl, is_item = ImpAll} decl = ImpDeclSpec { is_mod = mod, is_as = moduleName mod, - is_qual = False, is_implicit = False, + is_qual = False, is_isboot = NotBoot, is_pkg_qual = NoPkgQual, is_dloc = srcLocSpan interactiveSrcLoc, is_level = NormalLevel } ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -1982,7 +1982,6 @@ lookupQualifiedNameGHCi fos rdr_name , is_as = moduleName mod , is_pkg_qual = NoPkgQual , is_qual = True - , is_implicit = False , is_isboot = NotBoot , is_dloc = noSrcSpan , is_level = NormalLevel } ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -391,7 +391,7 @@ rnImportDecl this_mod let imp_mod = mi_module iface qual_mod_name = fmap unLoc as_mod `orElse` imp_mod_name - imp_spec = ImpDeclSpec { is_mod = imp_mod, is_qual = qual_only, is_implicit = implicit, + imp_spec = ImpDeclSpec { is_mod = imp_mod, is_qual = qual_only, is_dloc = locA loc, is_as = qual_mod_name, is_pkg_qual = pkg_qual, is_isboot = want_boot, is_level = convImportLevel import_level } @@ -2105,7 +2105,6 @@ data ImportMap = ImportMap -- ^ See [The ImportMap] -- If loc :-> gres, then -- 'loc' = the end loc of the bestImport of each GRE in 'gres' - , im_implicitImports :: Map ModuleName [GlobalRdrElt] , im_generatedImports :: Map ModuleName [GlobalRdrElt] } @@ -2113,12 +2112,10 @@ mkImportMap :: [GlobalRdrElt] -> ImportMap -- For each of a list of used GREs, find all the import decls that brought -- it into scope; choose one of them (bestImport), and record -- the RdrName in that import decl's entry in the ImportMap -mkImportMap = foldr insertImportMap $ ImportMap Map.empty Map.empty Map.empty +mkImportMap = foldr insertImportMap $ ImportMap Map.empty Map.empty insertImportMap :: GlobalRdrElt -> ImportMap -> ImportMap insertImportMap gre@(GRE { gre_imp = imp_specs }) importMap - | is_implicit best_imp_spec = - importMap{im_implicitImports = insertElem (moduleName $ is_mod best_imp_spec) gre $ im_implicitImports importMap} | RealSrcSpan importSpan _ <- is_dloc best_imp_spec = importMap{im_imports = insertElem importSpan gre $ im_imports importMap} | UnhelpfulSpan UnhelpfulGenerated <- is_dloc best_imp_spec = @@ -2141,7 +2138,6 @@ lookupImportMap (L srcSpan ImportDecl{ideclName = L _ modName}) importMap = fromMaybe [] $ -- should match logic in insertImportMap case locA srcSpan of - _ | Just gres <- modName `Map.lookup` im_implicitImports importMap -> Just gres RealSrcSpan realSrcSpan _ -> realSrcSpan `Map.lookup` im_imports importMap UnhelpfulSpan UnhelpfulGenerated -> modName `Map.lookup` im_generatedImports importMap _ -> Nothing ===================================== compiler/GHC/Runtime/Loader.hs ===================================== @@ -354,7 +354,7 @@ lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do Just iface -> do -- Try and find the required name in the exports let decl_spec = ImpDeclSpec { is_mod = mod, is_as = mod_name, is_pkg_qual = NoPkgQual - , is_qual = False, is_implicit = False + , is_qual = False , is_dloc = noSrcSpan, is_isboot = NotBoot, is_level = SpliceLevel } imp_spec = ImpSpec decl_spec ImpAll env = mkGlobalRdrEnv ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -633,7 +633,6 @@ mergeSignatures is_as = mod_name, is_pkg_qual = NoPkgQual, is_qual = False, - is_implicit = False, is_isboot = NotBoot, is_dloc = locA loc, is_level = NormalLevel ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -1821,7 +1821,6 @@ shadowNames drop_only_qualified env new_gres = minusOccEnv_C_Ns do_shadowing env , is_as = old_mod_name , is_pkg_qual = NoPkgQual , is_qual = True - , is_implicit = False , is_level = NormalLevel -- MP: Not 100% sure this is correct , is_isboot = NotBoot , is_dloc = greDefinitionSrcSpan old_gre } @@ -1984,7 +1983,6 @@ data ImpDeclSpec is_as :: !ModuleName, -- ^ Import alias, e.g. from @as M@ (or @Muggle@ if there is no @as@ clause) is_pkg_qual :: !PkgQual, -- ^ Was this a package import? is_qual :: !Bool, -- ^ Was this import qualified? - is_implicit :: !Bool, -- ^ Was this import implicit? See Note [Implicit imports] in GHC.Hs.ImpExp is_dloc :: !SrcSpan, -- ^ The location of the entire import declaration is_isboot :: !IsBootInterface, -- ^ Was this a SOURCE import? is_level :: !ImportLevel -- ^ Was this import level modified? splice/quote +-1 @@ -1997,12 +1995,11 @@ instance NFData ImpDeclSpec where instance Binary ImpDeclSpec where - put_ bh (ImpDeclSpec mod as pkg_qual qual implicit _dloc isboot isstage) = do + put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot isstage) = do put_ bh mod put_ bh as put_ bh pkg_qual put_ bh qual - put_ bh implicit put_ bh isboot put_ bh (fromEnum isstage) @@ -2011,10 +2008,9 @@ instance Binary ImpDeclSpec where as <- get bh pkg_qual <- get bh qual <- get bh - implicit <- get bh isboot <- get bh isstage <- toEnum <$> get bh - return (ImpDeclSpec mod as pkg_qual qual implicit noSrcSpan isboot isstage) + return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot isstage) -- | Import Item Specification -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/768dc8b0be17b8995e9ea1d0733dd4a6... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/768dc8b0be17b8995e9ea1d0733dd4a6... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Brandon Chinn (@brandonchinn178)