X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRename.lhs;h=d9a4dcb27d53dd15ad75e84baaf56d6c40f82705;hb=0e8e53db37d75d506d3a5b2804342442a5142d59;hp=c3a1e3209a47bf9a0fe2beed758de151e47af416;hpb=88f315a135bd00d2efa00d991bb9487929562d91;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs index c3a1e32..d9a4dcb 100644 --- a/ghc/compiler/rename/Rename.lhs +++ b/ghc/compiler/rename/Rename.lhs @@ -4,74 +4,267 @@ \section[Rename]{Renaming and dependency analysis passes} \begin{code} -module Rename ( renameModule, closeIfaceDecls, checkOldIface ) where +module Rename ( + renameModule, RnResult(..), renameStmt, renameRdrName, mkGlobalContext, + closeIfaceDecls, checkOldIface, slurpIface + ) where #include "HsVersions.h" import HsSyn import RdrHsSyn ( RdrNameHsModule, RdrNameHsDecl, RdrNameDeprecation, - RdrNameTyClDecl, RdrNameRuleDecl, RdrNameInstDecl, RdrNameImportDecl + RdrNameTyClDecl, RdrNameRuleDecl, RdrNameInstDecl, RdrNameImportDecl, + RdrNameStmt ) import RnHsSyn ( RenamedHsDecl, RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl, - extractHsTyNames, + RenamedStmt, instDeclFVs, tyClDeclFVs, ruleDeclFVs ) -import CmdLineOpts ( DynFlags, DynFlag(..), dopt ) +import CmdLineOpts ( DynFlags, DynFlag(..), opt_InPackage ) import RnMonad -import RnNames ( getGlobalNames ) +import RnExpr ( rnStmt ) +import RnNames ( getGlobalNames, exportsFromAvail ) import RnSource ( rnSourceDecls, rnTyClDecl, rnIfaceRuleDecl, rnInstDecl ) -import RnIfaces ( slurpImpDecls, mkImportInfo, - getInterfaceExports, closeDecls, +import RnIfaces ( slurpImpDecls, mkImportInfo, recordLocalSlurps, + closeDecls, RecompileRequired, outOfDate, recompileRequired ) -import RnHiFiles ( readIface, removeContext, - loadExports, loadFixDecls, loadDeprecs ) -import RnEnv ( availName, - emptyAvailEnv, unitAvailEnv, availEnvElts, plusAvailEnv, groupAvails, - warnUnusedImports, warnUnusedLocalBinds, warnUnusedModules, - lookupOrigNames, lookupGlobalRn, newGlobalName +import RnHiFiles ( readIface, loadInterface, + loadExports, loadFixDecls, loadDeprecs, + ) +import RnEnv ( availsToNameSet, + unitAvailEnv, availEnvElts, availNames, + plusAvailEnv, groupAvails, warnUnusedImports, + warnUnusedLocalBinds, warnUnusedModules, + lookupSrcName, getImplicitStmtFVs, + getImplicitModuleFVs, newGlobalName, unQualInScope, + ubiquitousNames, lookupOccRn, checkMain, + plusGlobalRdrEnv, mkGlobalRdrEnv ) import Module ( Module, ModuleName, WhereFrom(..), moduleNameUserString, moduleName, - mkModuleInThisPackage, mkModuleName, moduleEnvElts - ) -import Name ( Name, NamedThing(..), getSrcLoc, - nameIsLocalOrFrom, - nameOccName, nameModule, - mkNameEnv, nameEnvElts, extendNameEnv + moduleEnvElts ) -import RdrName ( elemRdrEnv ) -import OccName ( occNameFlavour ) +import Name ( Name, nameModule, isExternalName ) +import NameEnv import NameSet -import TysWiredIn ( unitTyCon, intTyCon, boolTyCon ) -import PrelNames ( mAIN_Name, pREL_MAIN_Name, pRELUDE_Name, - ioTyCon_RDR, main_RDR, - unpackCString_RDR, unpackCStringFoldr_RDR, unpackCStringUtf8_RDR, - eqString_RDR - ) -import PrelInfo ( derivingOccurrences ) -import Type ( funTyCon ) -import ErrUtils ( dumpIfSet ) +import RdrName ( foldRdrEnv, isQual ) +import PrelNames ( iNTERACTIVE, pRELUDE_Name ) +import ErrUtils ( dumpIfSet, dumpIfSet_dyn, showPass, + printErrorsAndWarnings, errorsFound ) import Bag ( bagToList ) import FiniteMap ( FiniteMap, fmToList, emptyFM, lookupFM, addToFM_C, elemFM, addToFM ) -import UniqFM ( lookupUFM ) import Maybes ( maybeToBool, catMaybes ) import Outputable import IO ( openFile, IOMode(..) ) -import HscTypes ( PersistentCompilerState, HomeIfaceTable, HomeSymbolTable, - ModIface(..), WhatsImported(..), - VersionInfo(..), ImportVersion, IfaceDecls(..), - GlobalRdrEnv, AvailEnv, GenAvailInfo(..), AvailInfo, - Provenance(..), ImportReason(..), initialVersionInfo, - Deprecations(..), lookupDeprec, lookupIface - ) +import HscTypes -- lots of it import List ( partition, nub ) \end{code} +%********************************************************* +%* * +\subsection{The main wrappers} +%* * +%********************************************************* + +\begin{code} +renameModule :: DynFlags -> GhciMode + -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> Module -> RdrNameHsModule + -> IO (PersistentCompilerState, PrintUnqualified, + Maybe (IsExported, ModIface, RnResult)) + -- Nothing => some error occurred in the renamer + +renameModule dflags ghci_mode hit hst pcs this_module rdr_module + = renameSource dflags hit hst pcs this_module $ + rename ghci_mode this_module rdr_module +\end{code} + +\begin{code} +renameStmt :: DynFlags + -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> InteractiveContext + -> RdrNameStmt -- parsed stmt + -> IO ( PersistentCompilerState, + PrintUnqualified, + Maybe ([Name], (RenamedStmt, [RenamedHsDecl])) + ) + +renameStmt dflags hit hst pcs ic stmt + = renameSource dflags hit hst pcs iNTERACTIVE $ + + -- load the context module + let InteractiveContext{ ic_rn_gbl_env = rdr_env, + ic_print_unqual = print_unqual, + ic_rn_local_env = local_rdr_env, + ic_type_env = type_env } = ic + in + + extendTypeEnvRn type_env $ + + -- Rename the stmt + initRnMS rdr_env emptyAvailEnv local_rdr_env emptyLocalFixityEnv CmdLineMode ( + rnStmt stmt $ \ stmt' -> + returnRn (([], stmt'), emptyFVs) + ) `thenRn` \ ((binders, stmt), fvs) -> + + -- Bale out if we fail + checkErrsRn `thenRn` \ no_errs_so_far -> + if not no_errs_so_far then + doDump dflags [] stmt [] `thenRn_` returnRn (print_unqual, Nothing) + else + + -- Add implicit free vars, and close decls + getImplicitStmtFVs `thenRn` \ implicit_fvs -> + slurpImpDecls (fvs `plusFV` implicit_fvs) `thenRn` \ decls -> + -- NB: an earlier version deleted (rdrEnvElts local_env) from + -- the fvs. But (a) that isn't necessary, because previously + -- bound things in the local_env will be in the TypeEnv, and + -- the renamer doesn't re-slurp such things, and + -- (b) it's WRONG to delete them. Consider in GHCi: + -- Mod> let x = e :: T + -- Mod> let y = x + 3 + -- We need to pass 'x' among the fvs to slurpImpDecls, so that + -- the latter can see that T is a gate, and hence import the Num T + -- instance decl. (See the InTypEnv case in RnIfaces.slurpSourceRefs.) + + doDump dflags binders stmt decls `thenRn_` + returnRn (print_unqual, Just (binders, (stmt, decls))) + + where + doDump :: DynFlags -> [Name] -> RenamedStmt -> [RenamedHsDecl] + -> RnMG (Either IOError ()) + doDump dflags bndrs stmt decls + = ioToRnM (dumpIfSet_dyn dflags Opt_D_dump_rn "Renamer:" + (vcat [text "Binders:" <+> ppr bndrs, + ppr stmt, text "", + vcat (map ppr decls)])) + + +renameRdrName + :: DynFlags + -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> InteractiveContext + -> [RdrName] -- name to rename + -> IO ( PersistentCompilerState, + PrintUnqualified, + Maybe ([Name], [RenamedHsDecl]) + ) + +renameRdrName dflags hit hst pcs ic rdr_names = + renameSource dflags hit hst pcs iNTERACTIVE $ + + -- load the context module + let InteractiveContext{ ic_rn_gbl_env = rdr_env, + ic_print_unqual = print_unqual, + ic_rn_local_env = local_rdr_env, + ic_type_env = type_env } = ic + in + + extendTypeEnvRn type_env $ + + -- rename the rdr_name + initRnMS rdr_env emptyAvailEnv local_rdr_env emptyLocalFixityEnv CmdLineMode + (mapRn (tryRn.lookupOccRn) rdr_names) `thenRn` \ maybe_names -> + let + ok_names = [ a | Right a <- maybe_names ] + in + if null ok_names + then let errs = head [ e | Left e <- maybe_names ] + in setErrsRn errs `thenRn_` + doDump dflags ok_names [] `thenRn_` + returnRn (print_unqual, Nothing) + else + + slurpImpDecls (mkNameSet ok_names) `thenRn` \ decls -> + + doDump dflags ok_names decls `thenRn_` + returnRn (print_unqual, Just (ok_names, decls)) + where + doDump :: DynFlags -> [Name] -> [RenamedHsDecl] -> RnMG (Either IOError ()) + doDump dflags names decls + = ioToRnM (dumpIfSet_dyn dflags Opt_D_dump_rn "Renamer:" + (vcat [ppr names, text "", + vcat (map ppr decls)])) +\end{code} + +%********************************************************* +%* * +\subsection{Make up an interactive context} +%* * +%********************************************************* + +\begin{code} +mkGlobalContext + :: DynFlags -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> [Module] -> [Module] + -> IO (PersistentCompilerState, PrintUnqualified, Maybe GlobalRdrEnv) +mkGlobalContext dflags hit hst pcs toplevs exports + = renameSource dflags hit hst pcs iNTERACTIVE $ + + mapRn getTopLevScope toplevs `thenRn` \ toplev_envs -> + mapRn getModuleExports exports `thenRn` \ export_envs -> + let full_env = foldr plusGlobalRdrEnv emptyRdrEnv + (toplev_envs ++ export_envs) + print_unqual = unQualInScope full_env + in + checkErrsRn `thenRn` \ no_errs_so_far -> + if not no_errs_so_far then + returnRn (print_unqual, Nothing) + else + returnRn (print_unqual, Just full_env) + +contextDoc = text "context for compiling statements" + +getTopLevScope :: Module -> RnM d GlobalRdrEnv +getTopLevScope mod = + loadInterface contextDoc (moduleName mod) ImportByUser `thenRn` \ iface -> + case mi_globals iface of + Nothing -> panic "getTopLevScope" + Just env -> returnRn env + +getModuleExports :: Module -> RnM d GlobalRdrEnv +getModuleExports mod = + loadInterface contextDoc (moduleName mod) ImportByUser `thenRn` \ iface -> + returnRn (foldl add emptyRdrEnv (mi_exports iface)) + where + prov_fn n = NonLocalDef ImplicitImport + add env (mod,avails) = + plusGlobalRdrEnv env (mkGlobalRdrEnv mod True prov_fn avails NoDeprecs) +\end{code} + +%********************************************************* +%* * +\subsection{Slurp in a whole module eagerly} +%* * +%********************************************************* + +\begin{code} +slurpIface + :: DynFlags -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState -> Module + -> IO (PersistentCompilerState, PrintUnqualified, + Maybe ([Name], [RenamedHsDecl])) +slurpIface dflags hit hst pcs mod = + renameSource dflags hit hst pcs iNTERACTIVE $ + + let mod_name = moduleName mod + in + loadInterface contextDoc mod_name ImportByUser `thenRn` \ iface -> + let fvs = availsToNameSet [ avail | (mn,avails) <- mi_exports iface, + avail <- avails ] + in + slurpImpDecls fvs `thenRn` \ rn_imp_decls -> + returnRn (alwaysQualify, Just (nameSetToList fvs, rn_imp_decls)) +\end{code} %********************************************************* %* * @@ -80,44 +273,87 @@ import List ( partition, nub ) %********************************************************* \begin{code} -renameModule :: DynFlags +renameSource :: DynFlags -> HomeIfaceTable -> HomeSymbolTable -> PersistentCompilerState - -> Module -> RdrNameHsModule - -> IO (PersistentCompilerState, Maybe (ModIface, [RenamedHsDecl])) + -> Module + -> RnMG (PrintUnqualified, Maybe r) + -> IO (PersistentCompilerState, PrintUnqualified, Maybe r) -- Nothing => some error occurred in the renamer -renameModule dflags hit hst old_pcs this_module rdr_module - = -- Initialise the renamer monad - do { - (new_pcs, errors_found, maybe_rn_stuff) - <- initRn dflags hit hst old_pcs this_module (rename this_module rdr_module) ; - - -- Return results. No harm in updating the PCS - if errors_found then - return (new_pcs, Nothing) - else - return (new_pcs, maybe_rn_stuff) +renameSource dflags hit hst old_pcs this_module thing_inside + = do { showPass dflags "Renamer" + + -- Initialise the renamer monad + ; (new_pcs, msgs, (print_unqual, maybe_rn_stuff)) + <- initRn dflags hit hst old_pcs this_module thing_inside + + -- Print errors from renaming + ; printErrorsAndWarnings print_unqual msgs ; + + -- Return results. No harm in updating the PCS + ; if errorsFound msgs then + return (new_pcs, print_unqual, Nothing) + else + return (new_pcs, print_unqual, maybe_rn_stuff) } \end{code} \begin{code} -rename :: Module -> RdrNameHsModule -> RnMG (Maybe (ModIface, [RenamedHsDecl])) -rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc) +data RnResult -- A RenamedModule ia passed from renamer to typechecker + = RnResult { rr_mod :: Module, -- Same as in the ModIface, + rr_fixities :: FixityEnv, -- but convenient to have it here + + rr_main :: Maybe Name, -- Just main, for module Main, + -- Nothing for other modules + + rr_decls :: [RenamedHsDecl] + -- The other declarations of the module + -- Fixity and deprecations have already been slurped out + } -- and are now in the ModIface for the module + +rename :: GhciMode -> Module -> RdrNameHsModule + -> RnMG (PrintUnqualified, Maybe (IsExported, ModIface, RnResult)) +rename ghci_mode this_module + contents@(HsModule _ _ exports imports local_decls mod_deprec loc) = pushSrcLocRn loc $ -- FIND THE GLOBAL NAME ENVIRONMENT - getGlobalNames this_module contents `thenRn` \ (gbl_env, local_gbl_env, - export_avails, global_avail_env) -> - + getGlobalNames this_module contents `thenRn` \ (gbl_env, local_gbl_env, + (mod_avail_env, global_avail_env)) -> + let + print_unqualified = unQualInScope gbl_env + + full_avail_env :: NameEnv AvailInfo + -- The domain of global_avail_env is just the 'major' things; + -- variables, type constructors, classes. + -- E.g. Functor |-> Functor( Functor, fmap ) + -- The domain of full_avail_env is everything in scope + -- E.g. Functor |-> Functor( Functor, fmap ) + -- fmap |-> Functor( Functor, fmap ) + -- + -- This filled-out avail_env is needed to generate + -- exports (mkExportAvails), and for generating minimal + -- exports (reportUnusedNames) + full_avail_env = mkNameEnv [ (name,avail) + | avail <- availEnvElts global_avail_env, + name <- availNames avail] + in -- Exit if we've found any errors checkErrsRn `thenRn` \ no_errs_so_far -> if not no_errs_so_far then -- Found errors already, so exit now rnDump [] [] `thenRn_` - returnRn Nothing + returnRn (print_unqualified, Nothing) else + -- PROCESS EXPORT LIST + exportsFromAvail mod_name exports mod_avail_env + full_avail_env gbl_env `thenRn` \ export_avails -> + + traceRn (text "Local top-level environment" $$ + nest 4 (pprGlobalRdrEnv local_gbl_env)) `thenRn_` + -- DEAL WITH DEPRECATIONS rnDeprecs local_gbl_env mod_deprec [d | DeprecD d <- local_decls] `thenRn` \ my_deprecs -> @@ -126,41 +362,47 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc) fixitiesFromLocalDecls local_gbl_env local_decls `thenRn` \ local_fixity_env -> -- RENAME THE SOURCE - initRnMS gbl_env local_fixity_env SourceMode ( - rnSourceDecls local_decls - ) `thenRn` \ (rn_local_decls, source_fvs) -> - - -- CHECK THAT main IS DEFINED, IF REQUIRED - checkMain this_module local_gbl_env `thenRn_` + rnSourceDecls gbl_env global_avail_env + local_fixity_env local_decls `thenRn` \ (rn_local_decls, source_fvs) -> - -- SLURP IN ALL THE NEEDED DECLARATIONS - implicitFVs mod_name rn_local_decls `thenRn` \ implicit_fvs -> + -- GET ANY IMPLICIT FREE VARIALBES + getImplicitModuleFVs rn_local_decls `thenRn` \ implicit_fvs -> + checkMain ghci_mode mod_name gbl_env `thenRn` \ (maybe_main_name, main_fvs, implicit_main_fvs) -> let + export_fvs = availsToNameSet export_avails + used_fvs = source_fvs `plusFV` export_fvs `plusFV` main_fvs -- The export_fvs make the exported names look just as if they -- occurred in the source program. For the reasoning, see the - -- comments with RnIfaces.getImportVersions. - -- We only need the 'parent name' of the avail; - -- that's enough to suck in the declaration. - export_fvs = mkNameSet (map availName export_avails) - real_source_fvs = source_fvs `plusFV` export_fvs + -- comments with RnIfaces.mkImportInfo + -- It also helps reportUnusedNames, which of course must not complain + -- that 'f' isn't mentioned if it is mentioned in the export list - slurp_fvs = implicit_fvs `plusFV` real_source_fvs + needed_fvs = implicit_fvs `plusFV` implicit_main_fvs `plusFV` used_fvs -- It's important to do the "plus" this way round, so that -- when compiling the prelude, locally-defined (), Bool, etc -- override the implicit ones. + in - slurpImpDecls slurp_fvs `thenRn` \ rn_imp_decls -> + traceRn (text "Needed FVs:" <+> fsep (map ppr (nameSetToList needed_fvs))) `thenRn_` -- EXIT IF ERRORS FOUND - rnDump rn_imp_decls rn_local_decls `thenRn_` + -- We exit here if there are any errors in the source, *before* + -- we attempt to slurp the decls from the interfaces, otherwise + -- the slurped decls may get lost when we return up the stack + -- to hscMain/hscExpr. checkErrsRn `thenRn` \ no_errs_so_far -> if not no_errs_so_far then -- Found errors already, so exit now - returnRn Nothing + rnDump [] rn_local_decls `thenRn_` + returnRn (print_unqualified, Nothing) else + -- SLURP IN ALL THE NEEDED DECLARATIONS + slurpImpDecls needed_fvs `thenRn` \ rn_imp_decls -> + rnDump rn_imp_decls rn_local_decls `thenRn_` + -- GENERATE THE VERSION/USAGE INFO - mkImportInfo mod_name imports `thenRn` \ my_usages -> + mkImportInfo mod_name imports `thenRn` \ my_usages -> -- BUILD THE MODULE INTERFACE let @@ -174,112 +416,51 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc) my_exports = groupAvails this_module export_avails final_decls = rn_local_decls ++ rn_imp_decls - is_orphan = any (isOrphanDecl this_module) rn_local_decls + + -- In interactive mode, we don't want to discard any top-level + -- entities at all (eg. do not inline them away during + -- simplification), and retain them all in the TypeEnv so they are + -- available from the command line. + -- + -- isExternalName separates the user-defined top-level names from those + -- introduced by the type checker. + dont_discard :: Name -> Bool + dont_discard | ghci_mode == Interactive = isExternalName + | otherwise = (`elemNameSet` exported_names) + + exported_names = availsToNameSet export_avails mod_iface = ModIface { mi_module = this_module, + mi_package = opt_InPackage, mi_version = initialVersionInfo, - mi_usages = my_usages, + mi_usages = my_usages, mi_boot = False, - mi_orphan = is_orphan, + mi_orphan = panic "is_orphan", mi_exports = my_exports, - mi_globals = gbl_env, + mi_globals = Just gbl_env, mi_fixities = fixities, mi_deprecs = my_deprecs, mi_decls = panic "mi_decls" } + + rn_result = RnResult { rr_mod = this_module, + rr_fixities = fixities, + rr_decls = final_decls, + rr_main = maybe_main_name } in -- REPORT UNUSED NAMES, AND DEBUG DUMP - reportUnusedNames mod_iface imports global_avail_env - real_source_fvs rn_imp_decls `thenRn_` + reportUnusedNames mod_iface print_unqualified + imports full_avail_env gbl_env + used_fvs rn_imp_decls `thenRn_` + -- NB: used_fvs: include exports (else we get bogus + -- warnings of unused things) but not implicit FVs. - returnRn (Just (mod_iface, final_decls)) + returnRn (print_unqualified, Just (dont_discard, mod_iface, rn_result)) where mod_name = moduleName this_module \end{code} -Checking that main is defined - -\begin{code} -checkMain :: Module -> GlobalRdrEnv -> RnMG () -checkMain this_mod local_env - | moduleName this_mod == mAIN_Name - = checkRn (main_RDR `elemRdrEnv` local_env) noMainErr - | otherwise - = returnRn () -\end{code} - -@implicitFVs@ forces the renamer to slurp in some things which aren't -mentioned explicitly, but which might be needed by the type checker. - -\begin{code} -implicitFVs mod_name decls - = lookupOrigNames implicit_occs `thenRn` \ implicit_names -> - returnRn (mkNameSet (map getName default_tycons) `plusFV` - implicit_names) - where - -- Add occurrences for Int, and (), because they - -- are the types to which ambigious type variables may be defaulted by - -- the type checker; so they won't always appear explicitly. - -- [The () one is a GHC extension for defaulting CCall results.] - -- ALSO: funTyCon, since it occurs implicitly everywhere! - -- (we don't want to be bothered with making funTyCon a - -- free var at every function application!) - -- Double is dealt with separately in getGates - default_tycons = [unitTyCon, funTyCon, boolTyCon, intTyCon] - - -- Add occurrences for IO or PrimIO - implicit_main | mod_name == mAIN_Name - || mod_name == pREL_MAIN_Name = [ioTyCon_RDR] - | otherwise = [] - - -- Now add extra "occurrences" for things that - -- the deriving mechanism, or defaulting, will later need in order to - -- generate code - implicit_occs = string_occs ++ foldr ((++) . get) implicit_main decls - - -- Virtually every program has error messages in it somewhere - string_occs = [unpackCString_RDR, unpackCStringFoldr_RDR, unpackCStringUtf8_RDR, - eqString_RDR] - - get (TyClD (TyData _ _ _ _ _ _ (Just deriv_classes) _ _ _)) - = concat (map get_deriv deriv_classes) - get other = [] - - get_deriv cls = case lookupUFM derivingOccurrences cls of - Nothing -> [] - Just occs -> occs -\end{code} - -\begin{code} -isOrphanDecl this_mod (InstD (InstDecl inst_ty _ _ _ _)) - = not (foldNameSet ((||) . nameIsLocalOrFrom this_mod) False - (extractHsTyNames (removeContext inst_ty))) - -- The 'removeContext' is because of - -- instance Foo a => Baz T where ... - -- The decl is an orphan if Baz and T are both not locally defined, - -- even if Foo *is* locally defined - -isOrphanDecl this_mod (RuleD (HsRule _ _ _ lhs _ _)) - = check lhs - where - -- At the moment we just check for common LHS forms - -- Expand as necessary. Getting it wrong just means - -- more orphans than necessary - check (HsVar v) = not (nameIsLocalOrFrom this_mod v) - check (HsApp f a) = check f && check a - check (HsLit _) = False - check (HsOverLit _) = False - check (OpApp l o _ r) = check l && check o && check r - check (NegApp e _) = check e - check (HsPar e) = check e - check (SectionL e o) = check e && check o - check (SectionR o e) = check e && check o - - check other = True -- Safe fall through - -isOrphanDecl _ _ = False -\end{code} %********************************************************* @@ -291,39 +472,31 @@ isOrphanDecl _ _ = False \begin{code} fixitiesFromLocalDecls :: GlobalRdrEnv -> [RdrNameHsDecl] -> RnMG LocalFixityEnv fixitiesFromLocalDecls gbl_env decls - = doptRn Opt_WarnUnusedBinds `thenRn` \ warn_unused -> - foldlRn (getFixities warn_unused) emptyNameEnv decls `thenRn` \ env -> - traceRn (text "fixity env" <+> vcat (map ppr (nameEnvElts env))) - `thenRn_` + = foldlRn getFixities emptyNameEnv decls `thenRn` \ env -> + traceRn (text "fixity env" <+> vcat (map ppr (nameEnvElts env))) `thenRn_` returnRn env where - getFixities :: Bool -> LocalFixityEnv -> RdrNameHsDecl -> RnMG LocalFixityEnv - getFixities warn_uu acc (FixD fix) - = fix_decl warn_uu acc fix + getFixities :: LocalFixityEnv -> RdrNameHsDecl -> RnMG LocalFixityEnv + getFixities acc (FixD fix) + = fix_decl acc fix - getFixities warn_uu acc (TyClD (ClassDecl _ _ _ _ sigs _ _ _ )) - = foldlRn (fix_decl warn_uu) acc [sig | FixSig sig <- sigs] + getFixities acc (TyClD (ClassDecl { tcdSigs = sigs})) + = foldlRn fix_decl acc [sig | FixSig sig <- sigs] -- Get fixities from class decl sigs too. - getFixities warn_uu acc other_decl + getFixities acc other_decl = returnRn acc - fix_decl warn_uu acc sig@(FixitySig rdr_name fixity loc) + fix_decl acc sig@(FixitySig rdr_name fixity loc) = -- Check for fixity decl for something not declared pushSrcLocRn loc $ - lookupGlobalRn gbl_env rdr_name `thenRn` \ maybe_name -> - case maybe_name of { - Nothing -> checkRn (not warn_uu) (unusedFixityDecl rdr_name fixity) `thenRn_` - returnRn acc ; - - Just name -> + lookupSrcName gbl_env rdr_name `thenRn` \ name -> -- Check for duplicate fixity decl - case lookupNameEnv acc name of { - Just (FixitySig _ _ loc') -> addErrRn (dupFixityDecl rdr_name loc loc') - `thenRn_` returnRn acc ; + case lookupNameEnv acc name of + Just (FixitySig _ _ loc') -> addErrRn (dupFixityDecl rdr_name loc loc') `thenRn_` + returnRn acc ; - Nothing -> returnRn (extendNameEnv acc name (FixitySig name fixity loc)) - }} + Nothing -> returnRn (extendNameEnv acc name (FixitySig name fixity loc)) \end{code} @@ -352,11 +525,9 @@ rnDeprecs gbl_env Nothing decls returnRn (DeprecSome (mkNameEnv (catMaybes pairs))) where rn_deprec (Deprecation rdr_name txt loc) - = pushSrcLocRn loc $ - lookupGlobalRn gbl_env rdr_name `thenRn` \ maybe_name -> - case maybe_name of - Just n -> returnRn (Just (n,(n,txt))) - Nothing -> returnRn Nothing + = pushSrcLocRn loc $ + lookupSrcName gbl_env rdr_name `thenRn` \ name -> + returnRn (Just (name, (name,txt))) \end{code} @@ -367,53 +538,77 @@ rnDeprecs gbl_env Nothing decls %************************************************************************ \begin{code} -checkOldIface :: DynFlags +checkOldIface :: GhciMode + -> DynFlags -> HomeIfaceTable -> HomeSymbolTable -> PersistentCompilerState + -> Module -> FilePath -> Bool -- Source unchanged -> Maybe ModIface -- Old interface from compilation manager, if any -> IO (PersistentCompilerState, Bool, (RecompileRequired, Maybe ModIface)) -- True <=> errors happened -checkOldIface dflags hit hst pcs iface_path source_unchanged maybe_iface - = case maybe_iface of +checkOldIface ghci_mode dflags hit hst pcs mod iface_path source_unchanged maybe_iface + = runRn dflags hit hst pcs (panic "Bogus module") $ + + -- CHECK WHETHER THE SOURCE HAS CHANGED + ( if not source_unchanged then + traceHiDiffsRn (nest 4 (text "Source file changed or recompilation check turned off")) + else returnRn () ) `thenRn_` + + -- If the source has changed and we're in interactive mode, avoid reading + -- an interface; just return the one we might have been supplied with. + if ghci_mode == Interactive && not source_unchanged then + returnRn (outOfDate, maybe_iface) + else + + setModuleRn mod $ + case maybe_iface of Just old_iface -> -- Use the one we already have - startRn (mi_module old_iface) $ check_versions old_iface + Nothing -- try and read it from a file - -> do read_result <- readIface do_traceRn iface_path - case read_result of - Left err -> -- Old interface file not found, or garbled; give up - return (pcs, False, (outOfDate, Nothing)) - Right parsed_iface - -> startRn (pi_mod parsed_iface) $ - loadOldIface parsed_iface `thenRn` \ m_iface -> + -> readIface iface_path `thenRn` \ read_result -> + case read_result of + Left err -> -- Old interface file not found, or garbled; give up + traceHiDiffsRn ( + text "Cannot read old interface file:" + $$ nest 4 err) `thenRn_` + returnRn (outOfDate, Nothing) + + Right parsed_iface -> + let read_mod_name = pi_mod parsed_iface + wanted_mod_name = moduleName mod + in + if (wanted_mod_name /= read_mod_name) then + traceHiDiffsRn ( + text "Existing interface file has wrong module name: " + <> quotes (ppr read_mod_name) + ) `thenRn_` + returnRn (outOfDate, Nothing) + else + loadOldIface mod parsed_iface `thenRn` \ m_iface -> check_versions m_iface where check_versions :: ModIface -> RnMG (RecompileRequired, Maybe ModIface) check_versions iface + | not source_unchanged + = returnRn (outOfDate, Just iface) + | otherwise = -- Check versions - recompileRequired iface_path source_unchanged iface - `thenRn` \ recompile -> + recompileRequired iface_path iface `thenRn` \ recompile -> returnRn (recompile, Just iface) - - do_traceRn = dopt Opt_D_dump_rn_trace dflags - ioTraceRn sdoc = if do_traceRn then printErrs sdoc else return () - startRn mod = initRn dflags hit hst pcs mod \end{code} I think the following function should now have a more representative name, but what? \begin{code} -loadOldIface :: ParsedIface -> RnMG ModIface +loadOldIface :: Module -> ParsedIface -> RnMG ModIface -loadOldIface parsed_iface +loadOldIface mod parsed_iface = let iface = parsed_iface - in -- RENAME IT - let mod = pi_mod iface - doc_str = ptext SLIT("need usage info from") <+> ppr mod in initIfaceRnMS mod ( loadHomeDecls (pi_decls iface) `thenRn` \ decls -> @@ -433,16 +628,15 @@ loadOldIface parsed_iface vers_rules = rule_vers, vers_decls = decls_vers } - decls = IfaceDecls { dcl_tycl = new_decls, - dcl_rules = new_rules, - dcl_insts = new_insts } + decls = mkIfaceDecls new_decls new_rules new_insts - mod_iface = ModIface { mi_module = mod, mi_version = version, + mod_iface = ModIface { mi_module = mod, mi_package = pi_pkg parsed_iface, + mi_version = version, mi_exports = avails, mi_usages = usages, mi_boot = False, mi_orphan = pi_orphan iface, mi_fixities = fix_env, mi_deprecs = deprec_env, mi_decls = decls, - mi_globals = panic "No mi_globals in old interface" + mi_globals = Nothing } in returnRn mod_iface @@ -507,7 +701,7 @@ closeIfaceDecls :: DynFlags -- True <=> errors happened closeIfaceDecls dflags hit hst pcs mod_iface@(ModIface { mi_module = mod, mi_decls = iface_decls }) - = initRn dflags hit hst pcs mod $ + = runRn dflags hit hst pcs mod $ let rule_decls = dcl_rules iface_decls @@ -519,8 +713,20 @@ closeIfaceDecls dflags hit hst pcs needed = unionManyNameSets (map ruleDeclFVs rule_decls) `unionNameSets` unionManyNameSets (map instDeclFVs inst_decls) `unionNameSets` unionManyNameSets (map tyClDeclFVs tycl_decls) + local_names = foldl add emptyNameSet tycl_decls + add names decl = addListToNameSet names (map fst (tyClDeclSysNames decl ++ tyClDeclNames decl)) in - closeDecls decls needed + + recordLocalSlurps local_names `thenRn_` + + -- Do the transitive closure + closeDecls decls (needed `plusFV` implicit_fvs) `thenRn` \closed_decls -> + rnDump [] closed_decls `thenRn_` + returnRn closed_decls + where + implicit_fvs = ubiquitousNames -- Data type decls with record selectors, + -- which may appear in the decls, need unpackCString + -- and friends. It's easier to just grab them right now. \end{code} %********************************************************* @@ -530,24 +736,21 @@ closeIfaceDecls dflags hit hst pcs %********************************************************* \begin{code} -reportUnusedNames :: ModIface -> [RdrNameImportDecl] +reportUnusedNames :: ModIface -> PrintUnqualified + -> [RdrNameImportDecl] -> AvailEnv - -> NameSet + -> GlobalRdrEnv + -> NameSet -- Used in this module -> [RenamedHsDecl] -> RnMG () -reportUnusedNames my_mod_iface imports avail_env +reportUnusedNames my_mod_iface unqual imports avail_env gbl_env used_names imported_decls = warnUnusedModules unused_imp_mods `thenRn_` warnUnusedLocalBinds bad_locals `thenRn_` warnUnusedImports bad_imp_names `thenRn_` - printMinimalImports this_mod minimal_imports `thenRn_` - warnDeprecations this_mod my_deprecs really_used_names `thenRn_` - returnRn () - + printMinimalImports this_mod unqual minimal_imports where this_mod = mi_module my_mod_iface - gbl_env = mi_globals my_mod_iface - my_deprecs = mi_deprecs my_mod_iface -- Now, a use of C implies a use of T, -- if C was brought into scope by T(..) or T(C) @@ -568,17 +771,23 @@ reportUnusedNames my_mod_iface imports avail_env other -> Nothing] ] - defined_names, defined_and_used, defined_but_not_used :: [(Name,Provenance)] - defined_names = concat (rdrEnvElts gbl_env) + -- Collect the defined names from the in-scope environment + -- Look for the qualified ones only, else get duplicates + defined_names :: [GlobalRdrElt] + defined_names = foldRdrEnv add [] gbl_env + add rdr_name ns acc | isQual rdr_name = ns ++ acc + | otherwise = acc + + defined_and_used, defined_but_not_used :: [GlobalRdrElt] (defined_and_used, defined_but_not_used) = partition used defined_names - used (name,_) = not (name `elemNameSet` really_used_names) + used (GRE name _ _) = name `elemNameSet` really_used_names -- Filter out the ones only defined implicitly bad_locals :: [Name] - bad_locals = [n | (n,LocalDef) <- defined_but_not_used] + bad_locals = [n | (GRE n LocalDef _) <- defined_but_not_used] bad_imp_names :: [(Name,Provenance)] - bad_imp_names = [(n,p) | (n,p@(NonLocalDef (UserImport mod _ True) _)) <- defined_but_not_used, + bad_imp_names = [(n,p) | GRE n p@(NonLocalDef (UserImport mod _ True)) _ <- defined_but_not_used, not (module_unused mod)] -- inst_mods are directly-imported modules that @@ -611,9 +820,12 @@ reportUnusedNames my_mod_iface imports avail_env minimal_imports1 = foldr add_name minimal_imports0 defined_and_used minimal_imports = foldr add_inst_mod minimal_imports1 inst_mods - add_name (n,NonLocalDef (UserImport m _ _) _) acc = addToFM_C plusAvailEnv acc (moduleName (nameModule n)) - (unitAvailEnv (mk_avail n)) - add_name (n,other_prov) acc = acc + -- We've carefully preserved the provenance so that we can + -- construct minimal imports that import the name by (one of) + -- the same route(s) as the programmer originally did. + add_name (GRE n (NonLocalDef (UserImport m _ _)) _) acc = addToFM_C plusAvailEnv acc (moduleName m) + (unitAvailEnv (mk_avail n)) + add_name (GRE n other_prov _) acc = acc mk_avail n = case lookupNameEnv avail_env n of Just (AvailTC m _) | n==m -> AvailTC n [n] @@ -640,37 +852,17 @@ reportUnusedNames my_mod_iface imports avail_env module_unused mod = moduleName mod `elem` unused_imp_mods -warnDeprecations this_mod my_deprecs used_names - = doptRn Opt_WarnDeprecations `thenRn` \ warn_drs -> - if not warn_drs then returnRn () else - - getIfacesRn `thenRn` \ ifaces -> - getHomeIfaceTableRn `thenRn` \ hit -> - let - pit = iPIT ifaces - deprecs = [ (n,txt) - | n <- nameSetToList used_names, - Just txt <- [lookup_deprec hit pit n] ] - in - mapRn_ warnDeprec deprecs - - where - lookup_deprec hit pit n - | nameIsLocalOrFrom this_mod n - = lookupDeprec my_deprecs n - | otherwise - = case lookupIface hit pit this_mod n of - Just iface -> lookupDeprec (mi_deprecs iface) n - Nothing -> pprPanic "warnDeprecations:" (ppr n) - -- ToDo: deal with original imports with 'qualified' and 'as M' clauses -printMinimalImports this_mod imps - = doptRn Opt_D_dump_minimal_imports `thenRn` \ dump_minimal -> - if not dump_minimal then returnRn () else +printMinimalImports :: Module -- This module + -> PrintUnqualified + -> FiniteMap ModuleName AvailEnv -- Minimal imports + -> RnMG () +printMinimalImports this_mod unqual imps + = ifOptRn Opt_D_dump_minimal_imports $ mapRn to_ies (fmToList imps) `thenRn` \ mod_ies -> ioToRnM (do { h <- openFile filename WriteMode ; - printForUser h (vcat (map ppr_mod_ie mod_ies)) + printForUser h unqual (vcat (map ppr_mod_ie mod_ies)) }) `thenRn_` returnRn () where @@ -686,12 +878,16 @@ printMinimalImports this_mod imps returnRn (mod, ies) to_ie :: AvailInfo -> RnMG (IE Name) + -- The main trick here is that if we're importing all the constructors + -- we want to say "T(..)", but if we're importing only a subset we want + -- to say "T(A,B,C)". So we have to find out what the module exports. to_ie (Avail n) = returnRn (IEVar n) to_ie (AvailTC n [m]) = ASSERT( n==m ) returnRn (IEThingAbs n) to_ie (AvailTC n ns) - = getInterfaceExports n_mod ImportBySystem `thenRn` \ (_, avails_by_module) -> - case [xs | (m,as) <- avails_by_module, + = loadInterface (text "Compute minimal imports from" <+> ppr n_mod) + n_mod ImportBySystem `thenRn` \ iface -> + case [xs | (m,as) <- mi_exports iface, m == n_mod, AvailTC x xs <- as, x == n] of @@ -736,52 +932,31 @@ getRnStats imported_decls ifaces where n_mods = length [() | _ <- moduleEnvElts (iPIT ifaces)] -- This is really only right for a one-shot compile + + (decls_map, n_decls_slurped) = iDecls ifaces - decls_read = [decl | (avail, True, (_,decl)) <- nameEnvElts (iDecls ifaces) + n_decls_left = length [decl | (avail, True, (_,decl)) <- nameEnvElts decls_map -- Data, newtype, and class decls are in the decls_fm -- under multiple names; the tycon/class, and each -- constructor/class op too. -- The 'True' selects just the 'main' decl ] - (cd_rd, dd_rd, nd_rd, sd_rd, vd_rd) = countTyClDecls decls_read - (cd_sp, dd_sp, nd_sp, sd_sp, vd_sp, id_sp) = count_decls imported_decls + (insts_left, n_insts_slurped) = iInsts ifaces + n_insts_left = length (bagToList insts_left) - unslurped_insts = iInsts ifaces - inst_decls_unslurped = length (bagToList unslurped_insts) - inst_decls_read = id_sp + inst_decls_unslurped + (rules_left, n_rules_slurped) = iRules ifaces + n_rules_left = length (bagToList rules_left) stats = vcat [int n_mods <+> text "interfaces read", - hsep [ int cd_sp, text "class decls imported, out of", - int cd_rd, text "read"], - hsep [ int dd_sp, text "data decls imported, out of", - int dd_rd, text "read"], - hsep [ int nd_sp, text "newtype decls imported, out of", - int nd_rd, text "read"], - hsep [int sd_sp, text "type synonym decls imported, out of", - int sd_rd, text "read"], - hsep [int vd_sp, text "value signatures imported, out of", - int vd_rd, text "read"], - hsep [int id_sp, text "instance decls imported, out of", - int inst_decls_read, text "read"], - text "cls dcls slurp" <+> fsep (map (ppr . tyClDeclName) - [d | TyClD d <- imported_decls, isClassDecl d]), - text "cls dcls read" <+> fsep (map (ppr . tyClDeclName) - [d | d <- decls_read, isClassDecl d])] - -count_decls decls - = (class_decls, - data_decls, - newtype_decls, - syn_decls, - val_decls, - inst_decls) - where - tycl_decls = [d | TyClD d <- decls] - (class_decls, data_decls, newtype_decls, syn_decls, val_decls) = countTyClDecls tycl_decls - - inst_decls = length [() | InstD _ <- decls] + hsep [ int n_decls_slurped, text "type/class/variable imported, out of", + int (n_decls_slurped + n_decls_left), text "read"], + hsep [ int n_insts_slurped, text "instance decls imported, out of", + int (n_insts_slurped + n_insts_left), text "read"], + hsep [ int n_rules_slurped, text "rule decls imported, out of", + int (n_rules_slurped + n_rules_left), text "read"] + ] \end{code} @@ -792,17 +967,6 @@ count_decls decls %************************************************************************ \begin{code} -warnDeprec :: (Name, DeprecTxt) -> RnM d () -warnDeprec (name, txt) - = pushSrcLocRn (getSrcLoc name) $ - addWarnRn $ - sep [ text (occNameFlavour (nameOccName name)) <+> ppr name <+> - text "is deprecated:", nest 4 (ppr txt) ] - - -unusedFixityDecl rdr_name fixity - = hsep [ptext SLIT("Unused fixity declaration for"), quotes (ppr rdr_name)] - dupFixityDecl rdr_name loc1 loc2 = vcat [ptext SLIT("Multiple fixity declarations for") <+> quotes (ppr rdr_name), ptext SLIT("at ") <+> ppr loc1, @@ -811,10 +975,6 @@ dupFixityDecl rdr_name loc1 loc2 badDeprec d = sep [ptext SLIT("Illegal deprecation when whole module is deprecated"), nest 4 (ppr d)] - -noMainErr - = hsep [ptext SLIT("Module"), quotes (ppr mAIN_Name), - ptext SLIT("must include a definition for"), quotes (ptext SLIT("main"))] \end{code}