[Git][ghc/ghc][wip/no-mi-globals] Fix tests
Hannes Siebenhandl (@fendor)
gitlab at gitlab.haskell.org
Mon May 6 14:25:41 UTC 2024
Hannes Siebenhandl pushed to branch wip/no-mi-globals at Glasgow Haskell Compiler / GHC
Commits:
17e88156 by Fendor at 2024-05-06T16:25:33+02:00
Fix tests
- - - - -
1 changed file:
- compiler/GHC/Rename/Names.hs
Changes:
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -339,29 +339,31 @@ importSpec (L loc (ImportDecl { ideclName = loc_imp_mod_name
rnImportDecl :: Module -> (LImportDecl GhcPs, SDoc)
-> RnM (LImportDecl GhcRn, ImportUserSpec , GlobalRdrEnv, ImportAvails, AnyHpcUsage)
rnImportDecl this_mod
- ( ldecl@(L loc decl@(ImportDecl { ideclSafe = mod_safe
- , ideclExt = XImportDeclPass { ideclImplicit = implicit }}))
- , import_reason)
+ (L loc decl@(ImportDecl { ideclName = loc_imp_mod_name
+ , ideclPkgQual = raw_pkg_qual
+ , ideclSource = want_boot, ideclSafe = mod_safe
+ , ideclQualified = qual_style
+ , ideclExt = XImportDeclPass { ideclImplicit = implicit }
+ , ideclAs = as_mod, ideclImportList = imp_details }), import_reason)
= setSrcSpanA loc $ do
- (imp_spec,imp_details) <- importSpec ldecl
- let pkg_qual = is_pkg_qual imp_spec
- want_boot = is_isboot imp_spec
- case pkg_qual of
- NoPkgQual -> pure ()
- _ -> do
+ case raw_pkg_qual of
+ NoRawPkgQual -> pure ()
+ RawPkgQual _ -> do
pkg_imports <- xoptM LangExt.PackageImports
when (not pkg_imports) $ addErr TcRnPackageImportsDisabled
- let qual_only = is_qual imp_spec
+ let qual_only = isImportDeclQualified qual_style
-- If there's an error in loadInterface, (e.g. interface
-- file not found) we get lots of spurious errors from 'filterImports'
- let imp_mod_name = moduleName $ is_mod imp_spec
+ let imp_mod_name = unLoc loc_imp_mod_name
doc = ppr imp_mod_name <+> import_reason
hsc_env <- getTopEnv
+ unit_env <- hsc_unit_env <$> getTopEnv
+ let pkg_qual = renameRawPkgQual unit_env imp_mod_name raw_pkg_qual
-- Check for self-import, which confuses the typechecker (#9032)
-- ghc --make rejects self-import cycles already, but batch-mode may not
@@ -414,6 +416,12 @@ rnImportDecl this_mod
when (mod_safe && not (safeImportsOn dflags)) $
addErr (TcRnSafeImportsDisabled imp_mod_name)
+ 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_dloc = locA loc, is_as = qual_mod_name,
+ is_pkg_qual = pkg_qual, is_isboot = want_boot }
+
-- filter the imports according to the import declaration
(new_imp_details, imp_user_list, gbl_env) <- filterImports hsc_env iface imp_spec imp_details
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17e8815659bcf054661c63fc6521e66dbc4d4952
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17e8815659bcf054661c63fc6521e66dbc4d4952
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/20240506/21fd5d86/attachment-0001.html>
More information about the ghc-commits
mailing list