Repository : ssh://g...@git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7fad107f61313f11cb0b40e0310ede4c119467fd/ghc
>--------------------------------------------------------------- commit 7fad107f61313f11cb0b40e0310ede4c119467fd Author: Austin Seipp <aus...@well-typed.com> Date: Wed Oct 9 03:02:29 2013 -0500 Clean up some outdated comments (#8418) Authored-by: Gergely Risko <gerg...@risko.hu> Signed-off-by: Austin Seipp <aus...@well-typed.com> >--------------------------------------------------------------- 7fad107f61313f11cb0b40e0310ede4c119467fd compiler/main/DynamicLoading.hs | 9 ++++++--- compiler/main/HscTypes.lhs | 8 ++++---- compiler/simplCore/SimplCore.lhs | 4 ++-- compiler/typecheck/TcRnDriver.lhs | 7 +++++-- 4 files changed, 17 insertions(+), 11 deletions(-) diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs index f262212..0498464 100644 --- a/compiler/main/DynamicLoading.hs +++ b/compiler/main/DynamicLoading.hs @@ -7,7 +7,7 @@ module DynamicLoading ( forceLoadTyCon, -- * Finding names - lookupRdrNameInModule, + lookupRdrNameInModuleForPlugins, -- * Loading values getValueSafely, @@ -141,8 +141,11 @@ lessUnsafeCoerce dflags context what = do -- -- * If the module could not be found -- * If we could not determine the imports of the module -lookupRdrNameInModule :: HscEnv -> ModuleName -> RdrName -> IO (Maybe Name) -lookupRdrNameInModule hsc_env mod_name rdr_name = do +-- +-- Can only be used for lookuping up names while handling plugins. +-- This was introduced by 57d6798. +lookupRdrNameInModuleForPlugins :: HscEnv -> ModuleName -> RdrName -> IO (Maybe Name) +lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do -- First find the package the module resides in by searching exposed packages and home modules found_module <- findImportedModule hsc_env mod_name Nothing case found_module of diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs index 390ac45..265f7f2 100644 --- a/compiler/main/HscTypes.lhs +++ b/compiler/main/HscTypes.lhs @@ -505,10 +505,10 @@ lookupIfaceByModule dflags hpt pit mod -- of its own, but it doesn't seem worth the bother. --- | Find all the instance declarations (of classes and families) that are in --- modules imported by this one, directly or indirectly, and are in the Home --- Package Table. This ensures that we don't see instances from modules @--make@ --- compiled before this one, but which are not below this one. +-- | Find all the instance declarations (of classes and families) from +-- the Home Package Table filtered by the provided predicate function. +-- Used in @tcRnImports@, to select the instances that are in the +-- transitive closure of imports from the currently compiled module. hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst]) hptInstances hsc_env want_this_module = let (insts, famInsts) = unzip $ flip hptAllThings hsc_env $ \mod_info -> do diff --git a/compiler/simplCore/SimplCore.lhs b/compiler/simplCore/SimplCore.lhs index 4b07d3b..7adee7d 100644 --- a/compiler/simplCore/SimplCore.lhs +++ b/compiler/simplCore/SimplCore.lhs @@ -53,7 +53,7 @@ import Type ( mkTyConTy ) import RdrName ( mkRdrQual ) import OccName ( mkVarOcc ) import PrelNames ( pluginTyConName ) -import DynamicLoading ( forceLoadTyCon, lookupRdrNameInModule, getValueSafely ) +import DynamicLoading ( forceLoadTyCon, lookupRdrNameInModuleForPlugins, getValueSafely ) import Module ( ModuleName ) import Panic #endif @@ -335,7 +335,7 @@ loadPlugin :: HscEnv -> ModuleName -> IO Plugin loadPlugin hsc_env mod_name = do { let plugin_rdr_name = mkRdrQual mod_name (mkVarOcc "plugin") dflags = hsc_dflags hsc_env - ; mb_name <- lookupRdrNameInModule hsc_env mod_name plugin_rdr_name + ; mb_name <- lookupRdrNameInModuleForPlugins hsc_env mod_name plugin_rdr_name ; case mb_name of { Nothing -> throwGhcExceptionIO (CmdLineError $ showSDoc dflags $ hsep diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs index 314d50f..8e5e7f2 100644 --- a/compiler/typecheck/TcRnDriver.lhs +++ b/compiler/typecheck/TcRnDriver.lhs @@ -241,7 +241,7 @@ implicitPreludeWarn tcRnImports :: HscEnv -> Module -> [LImportDecl RdrName] -> TcM TcGblEnv tcRnImports hsc_env this_mod import_decls - = do { (rn_imports, rdr_env, imports,hpc_info) <- rnImports import_decls ; + = do { (rn_imports, rdr_env, imports, hpc_info) <- rnImports import_decls ; ; let { dep_mods :: ModuleNameEnv (ModuleName, IsBootInterface) -- Make sure we record the dependencies from the DynFlags in the EPS or we @@ -257,7 +257,10 @@ tcRnImports hsc_env this_mod import_decls -- We want instance declarations from all home-package -- modules below this one, including boot modules, except -- ourselves. The 'except ourselves' is so that we don't - -- get the instances from this module's hs-boot file + -- get the instances from this module's hs-boot file. This + -- filtering also ensures that we don't see instances from + -- modules batch (@--make@) compiled before this one, but + -- which are not below this one. ; want_instances :: ModuleName -> Bool ; want_instances mod = mod `elemUFM` dep_mods && mod /= moduleName this_mod _______________________________________________ ghc-commits mailing list ghc-commits@haskell.org http://www.haskell.org/mailman/listinfo/ghc-commits