X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Frename%2FRnNames.lhs;h=39ec541610ee5ec88d2623d9f5bf26c5c3ff3ab9;hb=e27a63d87e12d0ad1491ee372e025c65fcfd3d36;hp=c30fdd9fcf8a88f0d84715a5bef1adb2b93e3491;hpb=1e50fd4185479a62e02d987bdfcb1c62712859ca;p=ghc-hetmet.git diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs index c30fdd9..39ec541 100644 --- a/compiler/rename/RnNames.lhs +++ b/compiler/rename/RnNames.lhs @@ -6,7 +6,8 @@ \begin{code} module RnNames ( rnImports, getLocalNonValBinders, - rnExports, extendGlobalRdrEnvRn, + rnExports, extendGlobalRdrEnvRn, + gresFromAvails, reportUnusedNames, finishWarnings, ) where @@ -21,6 +22,7 @@ import IfaceEnv ( ifaceExportNames ) import LoadIface ( loadSrcInterface, loadSysInterface ) import TcRnMonad hiding (LIE) +import HeaderInfo ( mkPrelImports ) import PrelNames import Module import Name @@ -60,7 +62,7 @@ rnImports imports -- warning for {- SOURCE -} ones that are unnecessary = do this_mod <- getModule implicit_prelude <- doptM Opt_ImplicitPrelude - let prel_imports = mkPrelImports this_mod implicit_prelude imports + let prel_imports = mkPrelImports (moduleName this_mod) implicit_prelude imports (source, ordinary) = partition is_source_import imports is_source_import (L _ (ImportDecl _ _ is_boot _ _ _)) = is_boot @@ -68,10 +70,11 @@ rnImports imports when (notNull prel_imports) $ addWarn (implicitPreludeWarn) ) - stuff1 <- mapM (rnImportDecl this_mod) (prel_imports ++ ordinary) - stuff2 <- mapM (rnImportDecl this_mod) source - let (decls, rdr_env, imp_avails,hpc_usage) = combine (stuff1 ++ stuff2) - return (decls, rdr_env, imp_avails,hpc_usage) + stuff1 <- mapM (rnImportDecl this_mod True) prel_imports + stuff2 <- mapM (rnImportDecl this_mod False) ordinary + stuff3 <- mapM (rnImportDecl this_mod False) source + let (decls, rdr_env, imp_avails, hpc_usage) = combine (stuff1 ++ stuff2 ++ stuff3) + return (decls, rdr_env, imp_avails, hpc_usage) where combine :: [(LImportDecl Name, GlobalRdrEnv, ImportAvails,AnyHpcUsage)] @@ -84,41 +87,11 @@ rnImports imports imp_avails1 `plusImportAvails` imp_avails2, hpc_usage1 || hpc_usage2) -mkPrelImports :: Module -> Bool -> [LImportDecl RdrName] -> [LImportDecl RdrName] --- Consruct the implicit declaration "import Prelude" (or not) --- --- NB: opt_NoImplicitPrelude is slightly different to import Prelude (); --- because the former doesn't even look at Prelude.hi for instance --- declarations, whereas the latter does. -mkPrelImports this_mod implicit_prelude import_decls - | this_mod == pRELUDE - || explicit_prelude_import - || not implicit_prelude - = [] - | otherwise = [preludeImportDecl] - where - explicit_prelude_import - = notNull [ () | L _ (ImportDecl mod Nothing _ _ _ _) <- import_decls, - unLoc mod == pRELUDE_NAME ] - - preludeImportDecl :: LImportDecl RdrName - preludeImportDecl - = L loc $ - ImportDecl (L loc pRELUDE_NAME) - Nothing {- no specific package -} - False {- Not a boot interface -} - False {- Not qualified -} - Nothing {- No "as" -} - Nothing {- No import list -} - - loc = mkGeneralSrcSpan (fsLit "Implicit import declaration") - - -rnImportDecl :: Module +rnImportDecl :: Module -> Bool -> LImportDecl RdrName -> RnM (LImportDecl Name, GlobalRdrEnv, ImportAvails,AnyHpcUsage) -rnImportDecl this_mod (L loc (ImportDecl loc_imp_mod_name mb_pkg want_boot +rnImportDecl this_mod implicit_prelude (L loc (ImportDecl loc_imp_mod_name mb_pkg want_boot qual_only as_mod imp_details)) = setSrcSpan loc $ do @@ -132,6 +105,11 @@ rnImportDecl this_mod (L loc (ImportDecl loc_imp_mod_name mb_pkg want_boot imp_mod_name = unLoc loc_imp_mod_name doc = ppr imp_mod_name <+> ptext (sLit "is directly imported") + case imp_details of + Just _ -> return () + Nothing -> unless implicit_prelude $ + ifOptM Opt_WarnMissingImportList (addWarn (missingImportListWarn imp_mod_name)) + iface <- loadSrcInterface doc imp_mod_name want_boot mb_pkg -- Compiler sanity check: if the import didn't say @@ -423,8 +401,7 @@ get_local_binders gbl_env (HsGroup {hs_valds = ValBindsIn _ val_sigs, = do { -- separate out the family instance declarations let (tyinst_decls1, tycl_decls_noinsts) = partition (isFamInstDecl . unLoc) tycl_decls - tyinst_decls = tyinst_decls1 ++ - concatMap (instDeclATs . unLoc) inst_decls + tyinst_decls = tyinst_decls1 ++ instDeclATs inst_decls -- process all type/class decls except family instances ; tc_names <- mapM new_tc tycl_decls_noinsts @@ -440,7 +417,6 @@ get_local_binders gbl_env (HsGroup {hs_valds = ValBindsIn _ val_sigs, ; val_names <- mapM new_simple val_bndrs ; return (val_names ++ tc_names ++ ti_names) } where - mod = tcg_mod gbl_env is_hs_boot = isHsBoot (tcg_src gbl_env) ; for_hs_bndrs :: [Located RdrName] @@ -454,23 +430,23 @@ get_local_binders gbl_env (HsGroup {hs_valds = ValBindsIn _ val_sigs, new_simple :: Located RdrName -> RnM (GenAvailInfo Name) new_simple rdr_name = do - nm <- newTopSrcBinder mod rdr_name + nm <- newTopSrcBinder rdr_name return (Avail nm) new_tc tc_decl -- NOT for type/data instances - = do { main_name <- newTopSrcBinder mod main_rdr - ; sub_names <- mapM (newTopSrcBinder mod) sub_rdrs + = do { main_name <- newTopSrcBinder main_rdr + ; sub_names <- mapM newTopSrcBinder sub_rdrs ; return (AvailTC main_name (main_name : sub_names)) } where - (main_rdr : sub_rdrs) = tyClDeclNames (unLoc tc_decl) + (main_rdr : sub_rdrs) = hsTyClDeclBinders tc_decl new_ti tc_name_env ti_decl -- ONLY for type/data instances = do { main_name <- lookupFamInstDeclBndr tc_name_env main_rdr - ; sub_names <- mapM (newTopSrcBinder mod) sub_rdrs + ; sub_names <- mapM newTopSrcBinder sub_rdrs ; return (AvailTC main_name sub_names) } -- main_name is not bound here! where - (main_rdr : sub_rdrs) = tyClDeclNames (unLoc ti_decl) + (main_rdr : sub_rdrs) = hsTyClDeclBinders ti_decl get_local_binders _ g = pprPanic "get_local_binders" (ppr g) \end{code} @@ -580,10 +556,10 @@ filterImports iface decl_spec (Just (want_hiding, import_items)) all_avails lookup_ie opt_typeFamilies ie = let bad_ie = Failed (badImportItemErr iface decl_spec ie) - lookup_name rdrName = - case lookupOccEnv occ_env (rdrNameOcc rdrName) of - Nothing -> bad_ie - Just n -> return n + lookup_name rdr + | isQual rdr = Failed (qualImportItemErr rdr) + | Just nm <- lookupOccEnv occ_env (rdrNameOcc rdr) = return nm + | otherwise = bad_ie in case ie of IEVar n -> do @@ -722,7 +698,7 @@ gresFromIE decl_spec (L loc ie, avail) mkChildEnv :: [GlobalRdrElt] -> NameEnv [Name] mkChildEnv gres = foldr add emptyNameEnv gres where - add (GRE { gre_name = n, gre_par = ParentIs p }) env = extendNameEnv_C (++) env p [n] + add (GRE { gre_name = n, gre_par = ParentIs p }) env = extendNameEnv_Acc (:) singleton env p n add _ env = env findChildren :: NameEnv [Name] -> Name -> [Name] @@ -1304,20 +1280,20 @@ isImpAll _other = False \begin{code} warnUnusedImport :: ImportDeclUsage -> RnM () -warnUnusedImport (L loc decl, used, unused) - | Just (False,[]) <- ideclHiding decl - = return () -- Do not warn for 'import M()' +warnUnusedImport (L loc decl, used, unused) + | Just (False,[]) <- ideclHiding decl + = return () -- Do not warn for 'import M()' | null used = addWarnAt loc msg1 -- Nothing used; drop entire decl - | null unused = return () -- Everything imported is used; nop + | null unused = return () -- Everything imported is used; nop | otherwise = addWarnAt loc msg2 -- Some imports are unused where msg1 = vcat [pp_herald <+> quotes pp_mod <+> pp_not_used, - nest 2 (ptext (sLit "except perhaps to import instances from") - <+> quotes pp_mod), - ptext (sLit "To import instances alone, use:") - <+> ptext (sLit "import") <+> pp_mod <> parens empty ] + nest 2 (ptext (sLit "except perhaps to import instances from") + <+> quotes pp_mod), + ptext (sLit "To import instances alone, use:") + <+> ptext (sLit "import") <+> pp_mod <> parens empty ] msg2 = sep [pp_herald <+> quotes (pprWithCommas ppr unused), - text "from module" <+> quotes pp_mod <+> pp_not_used] + text "from module" <+> quotes pp_mod <+> pp_not_used] pp_herald = text "The import of" pp_mod = ppr (unLoc (ideclName decl)) pp_not_used = text "is redundant" @@ -1386,6 +1362,11 @@ printMinimalImports imports_w_usage %************************************************************************ \begin{code} +qualImportItemErr :: RdrName -> SDoc +qualImportItemErr rdr + = hang (ptext (sLit "Illegal qualified name in import item:")) + 2 (ppr rdr) + badImportItemErr :: ModIface -> ImpDeclSpec -> IE RdrName -> SDoc badImportItemErr iface decl_spec ie = sep [ptext (sLit "Module"), quotes (ppr (is_mod decl_spec)), source_import, @@ -1472,14 +1453,18 @@ nullModuleExport :: ModuleName -> SDoc nullModuleExport mod = ptext (sLit "The export item `module") <+> ppr mod <> ptext (sLit "' exports nothing") +missingImportListWarn :: ModuleName -> SDoc +missingImportListWarn mod + = ptext (sLit "The module") <+> quotes (ppr mod) <+> ptext (sLit "is missing an import list") + moduleWarn :: ModuleName -> WarningTxt -> SDoc moduleWarn mod (WarningTxt txt) = sep [ ptext (sLit "Module") <+> quotes (ppr mod) <> ptext (sLit ":"), - nest 4 (ppr txt) ] + nest 2 (vcat (map ppr txt)) ] moduleWarn mod (DeprecatedTxt txt) = sep [ ptext (sLit "Module") <+> quotes (ppr mod) <+> ptext (sLit "is deprecated:"), - nest 4 (ppr txt) ] + nest 2 (vcat (map ppr txt)) ] implicitPreludeWarn :: SDoc implicitPreludeWarn