X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRnIfaces.lhs;h=7a27d290f11c323253ee6159c72facffbfa2265f;hb=624ff0c75af86ee06e1ada7b1944bba49832943d;hp=ddf4e4ef242d1341d66ff87b2f30bbc8f92bc930;hpb=451a8613203721d344e26eb043e8af827c58cd7b;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/RnIfaces.lhs b/ghc/compiler/rename/RnIfaces.lhs index ddf4e4e..7a27d29 100644 --- a/ghc/compiler/rename/RnIfaces.lhs +++ b/ghc/compiler/rename/RnIfaces.lhs @@ -13,7 +13,8 @@ module RnIfaces ( checkUpToDate, - getDeclBinders + getDeclBinders, getDeclSysBinders, + removeContext -- removeContext probably belongs somewhere else ) where #include "HsVersions.h" @@ -21,24 +22,25 @@ module RnIfaces ( import CmdLineOpts ( opt_NoPruneDecls, opt_IgnoreIfacePragmas ) import HsSyn ( HsDecl(..), TyClDecl(..), InstDecl(..), IfaceSig(..), HsType(..), ConDecl(..), IE(..), ConDetails(..), Sig(..), + ForeignDecl(..), ForKind(..), isDynamicExtName, FixitySig(..), RuleDecl(..), - isClassOpSig + isClassOpSig, Deprecation(..) ) import BasicTypes ( Version, NewOrData(..), defaultFixity ) import RdrHsSyn ( RdrNameHsDecl, RdrNameInstDecl, RdrNameTyClDecl, RdrNameRuleDecl, - extractHsTyRdrNames + extractHsTyRdrNames, RdrNameDeprecation ) import RnEnv ( mkImportedGlobalName, newImportedBinder, mkImportedGlobalFromRdrName, - lookupOccRn, + lookupOccRn, lookupImplicitOccRn, pprAvail, - availName, availNames, addAvailToNameSet, + availName, availNames, addAvailToNameSet, addSysAvails, FreeVars, emptyFVs ) import RnMonad -import RnHsSyn ( RenamedHsDecl ) +import RnHsSyn ( RenamedHsDecl, RenamedDeprecation ) import ParseIface ( parseIface, IfaceStuff(..) ) -import FiniteMap ( FiniteMap, sizeFM, emptyFM, delFromFM, +import FiniteMap ( FiniteMap, sizeFM, emptyFM, delFromFM, listToFM, lookupFM, addToFM, addToFM_C, addListToFM, fmToList, elemFM, foldFM ) @@ -48,7 +50,7 @@ import Name ( Name {-instance NamedThing-}, ) import Module ( Module, moduleString, pprModule, mkVanillaModule, pprModuleName, - moduleUserString, moduleName, isLibModule, + moduleUserString, moduleName, isLocalModule, ModuleName, WhereFrom(..), ) import RdrName ( RdrName, rdrNameOcc ) @@ -56,7 +58,7 @@ import NameSet import Var ( Id ) import SrcLoc ( mkSrcLoc, SrcLoc ) import PrelMods ( pREL_GHC ) -import PrelInfo ( cCallishTyKeys, thinAirModules ) +import PrelInfo ( cCallishTyKeys ) import Bag import Maybes ( MaybeErr(..), maybeToBool, orElse ) import ListSetOps ( unionLists ) @@ -64,6 +66,8 @@ import Outputable import Unique ( Unique ) import StringBuffer ( StringBuffer, hGetStringBuffer ) import FastString ( mkFastString ) +import ErrUtils ( Message ) +import Lex import Outputable import IO ( isDoesNotExistError ) @@ -78,9 +82,19 @@ import List ( nub ) %********************************************************* \begin{code} -loadHomeInterface :: SDoc -> Name -> RnM d (Module, Ifaces) +loadHomeInterface :: SDoc -> Name -> RnM d Ifaces loadHomeInterface doc_str name - = loadInterface doc_str (moduleName (nameModule name)) ImportBySystem + = loadInterface doc_str (moduleName (nameModule name)) ImportBySystem `thenRn` \ (_, ifaces) -> + returnRn ifaces + +loadOrphanModules :: [ModuleName] -> RnM d () +loadOrphanModules mods + | null mods = returnRn () + | otherwise = traceRn (text "Loading orphan modules:" <+> fsep (map pprModuleName mods)) `thenRn_` + mapRn_ load mods `thenRn_` + returnRn () + where + load mod = loadInterface (pprModuleName mod <+> ptext SLIT("is a orphan-instance module")) mod ImportBySystem loadInterface :: SDoc -> ModuleName -> WhereFrom -> RnM d (Module, Ifaces) loadInterface doc_str mod_name from @@ -88,39 +102,54 @@ loadInterface doc_str mod_name from let mod_map = iImpModInfo ifaces mod_info = lookupFM mod_map mod_name - in_map = maybeToBool mod_info - in - - -- Issue a warning for a redundant {- SOURCE -} import - -- It's redundant if the moduld is in the iImpModInfo at all, - -- because we arrange to read all the ordinary imports before - -- any of the {- SOURCE -} imports - warnCheckRn (not (in_map && case from of {ImportByUserSource -> True; other -> False})) - (warnRedundantSourceImport mod_name) `thenRn_` + hi_boot_file = case from of { + ImportByUser -> False ; -- Not hi-boot + ImportByUserSource -> True ; -- hi-boot + ImportBySystem -> + case mod_info of + Just (_, _, is_boot, _) -> is_boot + + Nothing -> False + -- We're importing a module we know absolutely + -- nothing about, so we assume it's from + -- another package, where we aren't doing + -- dependency tracking. So it won't be a hi-boot file. + } + redundant_source_import + = case (from, mod_info) of + (ImportByUserSource, Just (_,_,False,_)) -> True + other -> False + in -- CHECK WHETHER WE HAVE IT ALREADY case mod_info of { - Just (_, _, Just (load_mod, _, _)) + Just (_, _, _, Just (load_mod, _, _)) -> -- We're read it already so don't re-read it returnRn (load_mod, ifaces) ; - mod_map_result -> + _ -> + + -- Issue a warning for a redundant {- SOURCE -} import + -- NB that we arrange to read all the ordinary imports before + -- any of the {- SOURCE -} imports + warnCheckRn (not redundant_source_import) + (warnRedundantSourceImport mod_name) `thenRn_` -- READ THE MODULE IN - findAndReadIface doc_str mod_name from in_map `thenRn` \ (hi_boot_read, read_result) -> + findAndReadIface doc_str mod_name hi_boot_file `thenRn` \ read_result -> case read_result of { Nothing -> -- Not found, so add an empty export env to the Ifaces map -- so that we don't look again - let - mod = mkVanillaModule mod_name - new_mod_map = addToFM mod_map mod_name (0, False, Just (mod, False, [])) - new_ifaces = ifaces { iImpModInfo = new_mod_map } - in - setIfacesRn new_ifaces `thenRn_` - failWithRn (mod, new_ifaces) (noIfaceErr mod hi_boot_read) ; + let + mod = mkVanillaModule mod_name + new_mod_map = addToFM mod_map mod_name (0, False, False, Just (mod, from, [])) + new_ifaces = ifaces { iImpModInfo = new_mod_map } + in + setIfacesRn new_ifaces `thenRn_` + failWithRn (mod, new_ifaces) (noIfaceErr mod hi_boot_file) ; -- Found and parsed! - Just (mod, iface) -> + Just iface -> -- LOAD IT INTO Ifaces @@ -132,50 +161,72 @@ loadInterface doc_str mod_name from getModuleRn `thenRn` \ this_mod_nm -> let rd_decls = pi_decls iface + mod = pi_mod iface in - foldlRn (loadDecl mod) (iDecls ifaces) rd_decls `thenRn` \ new_decls -> - foldlRn (loadInstDecl mod) (iInsts ifaces) (pi_insts iface) `thenRn` \ new_insts -> - foldlRn (loadRule mod) (iRules ifaces) (pi_rules iface) `thenRn` \ new_rules -> - foldlRn (loadFixDecl mod_name) (iFixes ifaces) rd_decls `thenRn` \ new_fixities -> - mapRn (loadExport this_mod_nm) (pi_exports iface) `thenRn` \ avails_s -> + -- Sanity check. If we're system-importing a module we know nothing at all + -- about, it should be from a different package to this one + WARN( not (maybeToBool mod_info) && + case from of { ImportBySystem -> True; other -> False } && + isLocalModule mod, + ppr mod ) + foldlRn (loadDecl mod) (iDecls ifaces) rd_decls `thenRn` \ new_decls -> + foldlRn (loadInstDecl mod) (iInsts ifaces) (pi_insts iface) `thenRn` \ new_insts -> + (if opt_IgnoreIfacePragmas + then returnRn emptyBag + else foldlRn (loadRule mod) (iRules ifaces) (pi_rules iface)) `thenRn` \ new_rules -> + (if opt_IgnoreIfacePragmas + then returnRn emptyNameEnv + else foldlRn (loadDeprec mod) (iDeprecs ifaces) (pi_deprecs iface)) `thenRn` \ new_deprecs -> + foldlRn (loadFixDecl mod_name) (iFixes ifaces) rd_decls `thenRn` \ new_fixities -> + mapRn (loadExport this_mod_nm) (pi_exports iface) `thenRn` \ avails_s -> let -- For an explicit user import, add to mod_map info about -- the things the imported module depends on, extracted -- from its usage info. mod_map1 = case from of - ImportByUser -> addModDeps mod mod_map (pi_usages iface) + ImportByUser -> addModDeps mod (pi_usages iface) mod_map other -> mod_map -- Now add info about this module mod_map2 = addToFM mod_map1 mod_name mod_details - mod_details = (pi_mod iface, pi_orphan iface, Just (mod, hi_boot_read, concat avails_s)) + cts = (pi_mod iface, from, concat avails_s) + mod_details = (pi_vers iface, pi_orphan iface, hi_boot_file, Just cts) new_ifaces = ifaces { iImpModInfo = mod_map2, iDecls = new_decls, iFixes = new_fixities, + iInsts = new_insts, iRules = new_rules, - iInsts = new_insts } + iDeprecs = new_deprecs } in setIfacesRn new_ifaces `thenRn_` returnRn (mod, new_ifaces) }} -addModDeps :: Module -> ImportedModuleInfo - -> [ImportVersion a] -> ImportedModuleInfo -addModDeps mod mod_deps new_deps - = foldr add mod_deps new_deps +addModDeps :: Module -> [ImportVersion a] + -> ImportedModuleInfo -> ImportedModuleInfo +-- (addModDeps M ivs deps) +-- We are importing module M, and M.hi contains 'import' decls given by ivs +addModDeps mod new_deps mod_deps + = foldr add mod_deps filtered_new_deps where - is_lib = isLibModule mod -- Don't record dependencies when importing a library module - add (imp_mod, version, has_orphans, _) deps - | is_lib && not has_orphans = deps - | otherwise = addToFM_C combine deps imp_mod (version, has_orphans, Nothing) - -- Record dependencies for modules that are - -- either are dependent via a non-library module - -- or contain orphan rules or instance decls - - -- Don't ditch a module that's already loaded!! - combine old@(_, _, Just _) new = old - combine old@(_, _, Nothing) new = new + -- Don't record dependencies when importing a module from another package + -- Except for its descendents which contain orphans, + -- and in that case, forget about the boot indicator + filtered_new_deps + | isLocalModule mod = [ (imp_mod, (version, has_orphans, is_boot, Nothing)) + | (imp_mod, version, has_orphans, is_boot, _) <- new_deps + ] + | otherwise = [ (imp_mod, (version, True, False, Nothing)) + | (imp_mod, version, has_orphans, _, _) <- new_deps, + has_orphans + ] + add (imp_mod, dep) deps = addToFM_C combine deps imp_mod dep + + combine old@(_, _, old_is_boot, cts) new + | maybeToBool cts || not old_is_boot = old -- Keep the old info if it's already loaded + -- or if it's a non-boot pending load + | otherwise = new -- Otherwise pick new info loadExport :: ModuleName -> ExportItem -> RnM d [AvailInfo] loadExport this_mod (mod, entities) @@ -239,10 +290,15 @@ loadDecl mod decls_map (version, decl) getDeclSysBinders new_name decl `thenRn` \ sys_bndrs -> let + full_avail = addSysAvails avail sys_bndrs + -- Add the sys-binders to avail. When we import the decl, + -- it's full_avail that will get added to the 'already-slurped' set (iSlurp) + -- If we miss out sys-binders, we'll read the decl multiple times! + main_name = availName avail new_decls_map = foldl add_decl decls_map - [ (name, (version, avail, name==main_name, (mod, decl'))) - | name <- sys_bndrs ++ availNames avail] + [ (name, (version, full_avail, name==main_name, (mod, decl'))) + | name <- availNames full_avail] add_decl decls_map (name, stuff) = WARN( name `elemNameEnv` decls_map, ppr name ) addToNameEnv decls_map name stuff @@ -272,8 +328,9 @@ loadDecl mod decls_map (version, decl) dates from a time where we picked up a .hi file first if it existed?] -} decl' = case decl of - SigD (IfaceSig name tp ls loc) | opt_IgnoreIfacePragmas -> SigD (IfaceSig name tp [] loc) - other -> decl + SigD (IfaceSig name tp ls loc) | opt_IgnoreIfacePragmas + -> SigD (IfaceSig name tp [] loc) + other -> decl loadInstDecl :: Module -> Bag GatedDecl @@ -318,6 +375,24 @@ loadRule mod rules decl@(IfaceRuleDecl var body src_loc) = setModuleRn (moduleName mod) $ mkImportedGlobalFromRdrName var `thenRn` \ var_name -> returnRn ((unitNameSet var_name, (mod, RuleD decl)) `consBag` rules) + +-- SUP: TEMPORARY HACK, ignoring module deprecations for now +loadDeprec :: Module -> DeprecationEnv -> RdrNameDeprecation -> RnM d DeprecationEnv +loadDeprec mod deprec_env (Deprecation (IEModuleContents _) txt) + = traceRn (text "module deprecation not yet implemented:" <+> ppr mod <> colon <+> ppr txt) `thenRn_` + returnRn deprec_env +loadDeprec mod deprec_env (Deprecation ie txt) + = setModuleRn (moduleName mod) $ + mapRn mkImportedGlobalFromRdrName (namesFromIE ie) `thenRn` \ names -> + traceRn (text "loaded deprecation(s) for" <+> hcat (punctuate comma (map ppr names)) <> colon <+> ppr txt) `thenRn_` + returnRn (extendNameEnv deprec_env (zip names (repeat txt))) + +namesFromIE :: IE a -> [a] +namesFromIE (IEVar n ) = [n] +namesFromIE (IEThingAbs n ) = [n] +namesFromIE (IEThingAll n ) = [n] +namesFromIE (IEThingWith n ns) = n:ns +namesFromIE (IEModuleContents _ ) = [] \end{code} @@ -328,52 +403,65 @@ loadRule mod rules decl@(IfaceRuleDecl var body src_loc) %******************************************************** \begin{code} -checkUpToDate :: ModuleName -> RnMG Bool -- True <=> no need to recompile +upToDate = True +outOfDate = False + +checkUpToDate :: ModuleName -> RnMG Bool -- True <=> no need to recompile + -- When this guy is called, we already know that the + -- source code is unchanged from last time checkUpToDate mod_name = getIfacesRn `thenRn` \ ifaces -> findAndReadIface doc_str mod_name - ImportByUser - (error "checkUpToDate") `thenRn` \ (_, read_result) -> + False {- Not hi-boot -} `thenRn` \ read_result -> -- CHECK WHETHER WE HAVE IT ALREADY case read_result of Nothing -> -- Old interface file not found, so we'd better bail out traceRn (sep [ptext SLIT("Didnt find old iface"), pprModuleName mod_name]) `thenRn_` - returnRn False + returnRn outOfDate - Just (_, iface) + Just iface -> -- Found it, so now check it checkModUsage (pi_usages iface) where -- Only look in current directory, with suffix .hi doc_str = sep [ptext SLIT("need usage info from"), pprModuleName mod_name] -checkModUsage [] = returnRn True -- Yes! Everything is up to date! +checkModUsage [] = returnRn upToDate -- Yes! Everything is up to date! + +checkModUsage ((mod_name, old_mod_vers, _, _, Specifically []) : rest) + -- If CurrentModule.hi contains + -- import Foo :: ; + -- then that simply records that Foo lies below CurrentModule in the + -- hierarchy, but CurrentModule doesn't depend in any way on Foo. + -- In this case we don't even want to open Foo's interface. + = traceRn (ptext SLIT("Nothing used from:") <+> ppr mod_name) `thenRn_` + checkModUsage rest -- This one's ok, so check the rest -checkModUsage ((mod_name, old_mod_vers, _, whats_imported) : rest) +checkModUsage ((mod_name, old_mod_vers, _, _, whats_imported) : rest) = loadInterface doc_str mod_name ImportBySystem `thenRn` \ (mod, ifaces) -> let maybe_mod_vers = case lookupFM (iImpModInfo ifaces) mod_name of - Just (version, _, Just (_, _, _)) -> Just version - other -> Nothing + Just (version, _, _, Just (_, _, _)) -> Just version + other -> Nothing in case maybe_mod_vers of { Nothing -> -- If we can't find a version number for the old module then -- bail out saying things aren't up to date traceRn (sep [ptext SLIT("Can't find version number for module"), - pprModuleName mod_name]) `thenRn_` - returnRn False ; + pprModuleName mod_name]) + `thenRn_` returnRn outOfDate ; Just new_mod_vers -> -- If the module version hasn't changed, just move on if new_mod_vers == old_mod_vers then - traceRn (sep [ptext SLIT("Module version unchanged:"), pprModuleName mod_name]) `thenRn_` - checkModUsage rest + traceRn (sep [ptext SLIT("Module version unchanged:"), pprModuleName mod_name]) + `thenRn_` checkModUsage rest else - traceRn (sep [ptext SLIT("Module version has changed:"), pprModuleName mod_name]) `thenRn_` - + traceRn (sep [ptext SLIT("Module version has changed:"), pprModuleName mod_name]) + `thenRn_` -- Module version changed, so check entities inside -- If the usage info wants to say "I imported everything from this module" @@ -381,7 +469,7 @@ checkModUsage ((mod_name, old_mod_vers, _, whats_imported) : rest) -- In that case, we must recompile case whats_imported of { Everything -> traceRn (ptext SLIT("...and I needed the whole module")) `thenRn_` - returnRn False; -- Bale out + returnRn outOfDate; -- Bale out Specifically old_local_vers -> @@ -391,22 +479,22 @@ checkModUsage ((mod_name, old_mod_vers, _, whats_imported) : rest) traceRn (ptext SLIT("...but the bits I use haven't.")) `thenRn_` checkModUsage rest -- This one's ok, so check the rest else - returnRn False -- This one failed, so just bail out now + returnRn outOfDate -- This one failed, so just bail out now }} where doc_str = sep [ptext SLIT("need version info for"), pprModuleName mod_name] checkEntityUsage mod decls [] - = returnRn True -- Yes! All up to date! + = returnRn upToDate -- Yes! All up to date! checkEntityUsage mod decls ((occ_name,old_vers) : rest) = mkImportedGlobalName mod occ_name `thenRn` \ name -> case lookupNameEnv decls name of Nothing -> -- We used it before, but it ain't there now - putDocRn (sep [ptext SLIT("No longer exported:"), ppr name]) `thenRn_` - returnRn False + traceRn (sep [ptext SLIT("No longer exported:"), ppr name]) + `thenRn_` returnRn outOfDate Just (new_vers,_,_,_) -- It's there, but is it up to date? | new_vers == old_vers @@ -415,8 +503,8 @@ checkEntityUsage mod decls ((occ_name,old_vers) : rest) | otherwise -- Out of date, so bale out - -> putDocRn (sep [ptext SLIT("Out of date:"), ppr name]) `thenRn_` - returnRn False + -> traceRn (sep [ptext SLIT("Out of date:"), ppr name]) `thenRn_` + returnRn outOfDate \end{code} @@ -441,13 +529,9 @@ importDecl name if name `elemNameSet` already_slurped then returnRn Nothing -- Already dealt with else - getModuleRn `thenRn` \ this_mod -> - let - mod = moduleName (nameModule name) - in - if mod == this_mod then -- Don't bring in decls from + if isLocallyDefined name then -- Don't bring in decls from -- the renamed module's own interface file - addWarnRn (importDeclWarn mod name) `thenRn_` + addWarnRn (importDeclWarn name) `thenRn_` returnRn Nothing else getNonWiredInDecl name @@ -457,7 +541,7 @@ importDecl name getNonWiredInDecl :: Name -> RnMG (Maybe (Module, RdrNameHsDecl)) getNonWiredInDecl needed_name = traceRn doc_str `thenRn_` - loadHomeInterface doc_str needed_name `thenRn` \ (_, ifaces) -> + loadHomeInterface doc_str needed_name `thenRn` \ ifaces -> case lookupNameEnv (iDecls ifaces) needed_name of Just (version,avail,_,decl) @@ -474,20 +558,20 @@ getNonWiredInDecl needed_name @getWiredInDecl@ maps a wired-in @Name@ to what it makes available. It behaves exactly as if the wired in decl were actually in an interface file. Specifically, - - * if the wired-in name is a data type constructor or a data constructor, +\begin{itemize} +\item if the wired-in name is a data type constructor or a data constructor, it brings in the type constructor and all the data constructors; and - marks as "occurrences" any free vars of the data con. + marks as ``occurrences'' any free vars of the data con. - * similarly for synonum type constructor +\item similarly for synonum type constructor - * if the wired-in name is another wired-in Id, it marks as "occurrences" +\item if the wired-in name is another wired-in Id, it marks as ``occurrences'' the free vars of the Id's type. - * it loads the interface file for the wired-in thing for the +\item it loads the interface file for the wired-in thing for the sole purpose of making sure that its instance declarations are available - -All this is necessary so that we know all types that are "in play", so +\end{itemize} +All this is necessary so that we know all types that are ``in play'', so that we know just what instances to bring into scope. @@ -499,20 +583,20 @@ that we know just what instances to bring into scope. %* * %********************************************************* -@getInterfaceExports@ is called only for directly-imported modules +@getInterfaceExports@ is called only for directly-imported modules. \begin{code} getInterfaceExports :: ModuleName -> WhereFrom -> RnMG (Module, Avails) getInterfaceExports mod_name from = loadInterface doc_str mod_name from `thenRn` \ (mod, ifaces) -> case lookupFM (iImpModInfo ifaces) mod_name of - Nothing -> -- Not there; it must be that the interface file wasn't found; - -- the error will have been reported already. - -- (Actually loadInterface should put the empty export env in there - -- anyway, but this does no harm.) - returnRn (mod, []) + Nothing -> -- Not there; it must be that the interface file wasn't found; + -- the error will have been reported already. + -- (Actually loadInterface should put the empty export env in there + -- anyway, but this does no harm.) + returnRn (mod, []) - Just (_, _, Just (mod, _, avails)) -> returnRn (mod, avails) + Just (_, _, _, Just (mod, _, avails)) -> returnRn (mod, avails) where doc_str = sep [pprModuleName mod_name, ptext SLIT("is directly imported")] \end{code} @@ -527,34 +611,41 @@ getInterfaceExports mod_name from \begin{code} getImportedInstDecls :: NameSet -> RnMG [(Module,RdrNameHsDecl)] getImportedInstDecls gates - = -- First load any orphan-instance modules that aren't aready loaded + = -- First, load any orphan-instance modules that aren't aready loaded -- Orphan-instance modules are recorded in the module dependecnies - getIfacesRn `thenRn` \ ifaces -> + getIfacesRn `thenRn` \ ifaces -> let - orphan_mods = [mod | (mod, (_, True, Nothing)) <- fmToList (iImpModInfo ifaces)] + orphan_mods = + [mod | (mod, (_, True, _, Nothing)) <- fmToList (iImpModInfo ifaces)] in - traceRn (text "Loading orphan modules" <+> fsep (map pprModuleName orphan_mods)) `thenRn_` - mapRn_ load_it orphan_mods `thenRn_` + loadOrphanModules orphan_mods `thenRn_` -- Now we're ready to grab the instance declarations -- Find the un-gated ones and return them, -- removing them from the bag kept in Ifaces - getIfacesRn `thenRn` \ ifaces -> + getIfacesRn `thenRn` \ ifaces -> let (decls, new_insts) = selectGated gates (iInsts ifaces) in setIfacesRn (ifaces { iInsts = new_insts }) `thenRn_` traceRn (sep [text "getImportedInstDecls:", - nest 4 (fsep (map ppr (nameSetToList gates))), - text "Slurped" <+> int (length decls) <+> text "instance declarations"]) `thenRn_` + nest 4 (fsep (map ppr gate_list)), + text "Slurped" <+> int (length decls) <+> text "instance declarations", + nest 4 (vcat (map ppr_brief_inst_decl decls))]) `thenRn_` returnRn decls where - load_it mod = loadInterface (doc_str mod) mod ImportBySystem - doc_str mod = sep [pprModuleName mod, ptext SLIT("is a orphan-instance module")] + gate_list = nameSetToList gates + +ppr_brief_inst_decl (mod, InstD (InstDecl inst_ty _ _ _ _)) + = case inst_ty of + HsForAllTy _ _ tau -> ppr tau + other -> ppr inst_ty getImportedRules :: RnMG [(Module,RdrNameHsDecl)] -getImportedRules +getImportedRules + | opt_IgnoreIfacePragmas = returnRn [] + | otherwise = getIfacesRn `thenRn` \ ifaces -> let gates = iSlurp ifaces -- Anything at all that's been slurped @@ -566,6 +657,7 @@ getImportedRules returnRn decls selectGated gates decl_bag + -- Select only those decls whose gates are *all* in 'gates' #ifdef DEBUG | opt_NoPruneDecls -- Just to try the effect of not gating at all = (foldrBag (\ (_,d) ds -> d:ds) [] decl_bag, emptyBag) -- Grab them all @@ -587,7 +679,14 @@ lookupFixity name Nothing -> returnRn defaultFixity | otherwise -- Imported - = loadHomeInterface doc name `thenRn` \ (_, ifaces) -> + -- For imported names, we have to get their fixities by doing a loadHomeInterface, + -- and consulting the Ifaces that comes back from that, because the interface + -- file for the Name might not have been loaded yet. Why not? Suppose you import module A, + -- which exports a function 'f', which is defined in module B. Then B isn't loaded + -- right away (after all, it's possible that nothing from B will be used). + -- When we come across a use of 'f', we need to know its fixity, and it's then, + -- and only then, that we load B.hi. That is what's happening here. + = loadHomeInterface doc name `thenRn` \ ifaces -> case lookupNameEnv (iFixes ifaces) name of Just (FixitySig _ fix _) -> returnRn fix Nothing -> returnRn defaultFixity @@ -602,93 +701,141 @@ lookupFixity name %* * %********************************************************* -getImportVersions figures out what the "usage information" for this moudule is; -that is, what it must record in its interface file as the things it uses. -It records: - - anything reachable from its body code - - any module exported with a "module Foo". +getImportVersions figures out what the ``usage information'' for this +moudule is; that is, what it must record in its interface file as the +things it uses. It records: + +\begin{itemize} +\item (a) anything reachable from its body code +\item (b) any module exported with a @module Foo@ +\item (c) anything reachable from an exported item +\end{itemize} -Why the latter? Because if Foo changes then this module's export list +Why (b)? Because if @Foo@ changes then this module's export list will change, so we must recompile this module at least as far as making a new interface file --- but in practice that means complete recompilation. -What about this? - module A( f, g ) where module B( f ) where - import B( f ) f = h 3 - g = ... h = ... - -Should we record B.f in A's usages? In fact we don't. Certainly, if -anything about B.f changes than anyone who imports A should be recompiled; -they'll get an early exit if they don't use B.f. However, even if B.f -doesn't change at all, B.h may do so, and this change may not be reflected -in f's version number. So there are two things going on when compiling module A: - -1. Are A.o and A.hi correct? Then we can bale out early. -2. Should modules that import A be recompiled? - -For (1) it is slightly harmful to record B.f in A's usages, because a change in -B.f's version will provoke full recompilation of A, producing an identical A.o, -and A.hi differing only in its usage-version of B.f (which isn't used by any importer). - -For (2), because of the tricky B.h question above, we ensure that A.hi is touched -(even if identical to its previous version) if A's recompilation was triggered by -an imported .hi file date change. Given that, there's no need to record B.f in -A's usages. - -On the other hand, if A exports "module B" then we *do* count module B among -A's usages, because we must recompile A to ensure that A.hi changes appropriately. +Why (c)? Consider this: +\begin{verbatim} + module A( f, g ) where | module B( f ) where + import B( f ) | f = h 3 + g = ... | h = ... +\end{verbatim} + +Here, @B.f@ isn't used in A. Should we nevertheless record @B.f@ in +@A@'s usages? Our idea is that we aren't going to touch A.hi if it is +*identical* to what it was before. If anything about @B.f@ changes +than anyone who imports @A@ should be recompiled in case they use +@B.f@ (they'll get an early exit if they don't). So, if anything +about @B.f@ changes we'd better make sure that something in A.hi +changes, and the convenient way to do that is to record the version +number @B.f@ in A.hi in the usage list. If B.f changes that'll force a +complete recompiation of A, which is overkill but it's the only way to +write a new, slightly different, A.hi. + +But the example is tricker. Even if @B.f@ doesn't change at all, +@B.h@ may do so, and this change may not be reflected in @f@'s version +number. But with -O, a module that imports A must be recompiled if +@B.h@ changes! So A must record a dependency on @B.h@. So we treat +the occurrence of @B.f@ in the export list *just as if* it were in the +code of A, and thereby haul in all the stuff reachable from it. + +[NB: If B was compiled with -O, but A isn't, we should really *still* +haul in all the unfoldings for B, in case the module that imports A *is* +compiled with -O. I think this is the case.] + +Even if B is used at all we get a usage line for B + import B :: ... ; +in A.hi, to record the fact that A does import B. This is used to decide +to look to look for B.hi rather than B.hi-boot when compiling a module that +imports A. This line says that A imports B, but uses nothing in it. +So we'll get an early bale-out when compiling A if B's version changes. \begin{code} getImportVersions :: ModuleName -- Name of this module - -> Maybe [IE any] -- Export list for this module + -> ExportEnv -- Info about exports -> RnMG (VersionInfo Name) -- Version info for these names -getImportVersions this_mod exports +getImportVersions this_mod (ExportEnv _ _ export_all_mods) = getIfacesRn `thenRn` \ ifaces -> let mod_map = iImpModInfo ifaces imp_names = iVSlurp ifaces -- mv_map groups together all the things imported from a particular module. - mv_map1, mv_map2 :: FiniteMap ModuleName (WhatsImported Name) - - -- mv_map1 records all the modules that have a "module M" - -- in this module's export list with an "Everything" - mv_map1 = foldr add_mod emptyFM export_mods - - -- mv_map2 adds the version numbers of things exported individually - mv_map2 = foldr add_mv mv_map1 imp_names - - -- Build the result list by adding info for each module, - -- *omitting* (a) library modules - -- (b) source-imported modules - mk_version_info mod_name (version, has_orphans, cts) so_far - | omit cts = so_far -- Don't record usage info for this module - | otherwise = (mod_name, version, has_orphans, whats_imported) : so_far - where - whats_imported = case lookupFM mv_map2 mod_name of - Just wi -> wi - Nothing -> Specifically [] - - omit (Just (mod, boot_import, _)) = isLibModule mod || boot_import - omit Nothing = False + mv_map :: FiniteMap ModuleName [(Name,Version)] + mv_map = foldr add_mv emptyFM imp_names + + -- Build the result list by adding info for each module. + -- For (a) a library module, we don't record it at all unless it contains orphans + -- (We must never lose track of orphans.) + -- + -- (b) a source-imported module, don't record the dependency at all + -- + -- (b) may seem a bit strange. The idea is that the usages in a .hi file records + -- *all* the module's dependencies other than the loop-breakers. We use + -- this info in findAndReadInterface to decide whether to look for a .hi file or + -- a .hi-boot file. + -- + -- This means we won't track version changes, or orphans, from .hi-boot files. + -- The former is potentially rather bad news. It could be fixed by recording + -- whether something is a boot file along with the usage info for it, but + -- I can't be bothered just now. + + mk_version_info mod_name (version, has_orphans, is_boot, contents) so_far + | mod_name == this_mod -- Check if M appears in the set of modules 'below' M + -- This seems like a convenient place to check + = WARN( not is_boot, ptext SLIT("Wierd:") <+> ppr this_mod <+> + ptext SLIT("imports itself (perhaps indirectly)") ) + so_far + + | otherwise + = let + go_for_it exports = (mod_name, version, has_orphans, is_boot, exports) + : so_far + in + case contents of + Nothing -> -- We didn't even open the interface + -- This happens when a module, Foo, that we explicitly imported has + -- 'import Baz' in its interface file, recording that Baz is below + -- Foo in the module dependency hierarchy. We want to propagate this + -- information. The Nothing says that we didn't even open the interface + -- file but we must still propagate the dependeny info. + -- The module in question must be a local module (in the same package) + go_for_it (Specifically []) + + Just (mod, how_imported, _) + | is_sys_import && is_lib_module && not has_orphans + -> so_far + + | is_lib_module -- Record the module but not detailed + || mod_name `elem` export_all_mods -- version information for the imports + -> go_for_it Everything + + | otherwise + -> case lookupFM mv_map mod_name of + Just whats_imported -> go_for_it (Specifically whats_imported) + Nothing -> go_for_it (Specifically []) + -- This happens if you have + -- import Foo + -- but don't actually *use* anything from Foo + -- In which case record an empty dependency list + where + is_lib_module = not (isLocalModule mod) + is_sys_import = case how_imported of + ImportBySystem -> True + other -> False + in + returnRn (foldFM mk_version_info [] mod_map) where - export_mods = case exports of - Nothing -> [] - Just es -> [mod | IEModuleContents mod <- es, mod /= this_mod] - add_mv v@(name, version) mv_map - = addToFM_C add_item mv_map mod (Specifically [v]) - where + = addToFM_C add_item mv_map mod [v] + where mod = moduleName (nameModule name) - - add_item Everything _ = Everything - add_item (Specifically xs) _ = Specifically (v:xs) - - add_mod mod mv_map = addToFM mv_map mod Everything + add_item vs _ = (v:vs) \end{code} \begin{code} @@ -697,6 +844,8 @@ getSlurped returnRn (iSlurp ifaces) recordSlurp maybe_version avail +-- Nothing for locally defined names +-- Just version for imported names = getIfacesRn `thenRn` \ ifaces@(Ifaces { iSlurp = slurped_names, iVSlurp = imp_names }) -> let @@ -721,8 +870,8 @@ recordSlurp maybe_version avail It's used for both source code (from @availsFromDecl@) and interface files (from @loadDecl@). -It doesn't deal with source-code specific things: ValD, DefD. They -are handled by the sourc-code specific stuff in RnNames. +It doesn't deal with source-code specific things: @ValD@, @DefD@. They +are handled by the sourc-code specific stuff in @RnNames@. \begin{code} getDeclBinders :: (RdrName -> SrcLoc -> RnM d Name) -- New-name function @@ -740,7 +889,7 @@ getDeclBinders new_name (TyClD (TySynonym tycon _ _ src_loc)) = new_name tycon src_loc `thenRn` \ tycon_name -> returnRn (Just (AvailTC tycon_name [tycon_name])) -getDeclBinders new_name (TyClD (ClassDecl _ cname _ sigs _ _ _ _ _ src_loc)) +getDeclBinders new_name (TyClD (ClassDecl _ cname _ _ sigs _ _ _ _ _ _ src_loc)) = new_name cname src_loc `thenRn` \ class_name -> -- Record the names for the class ops @@ -757,20 +906,34 @@ getDeclBinders new_name (SigD (IfaceSig var ty prags src_loc)) returnRn (Just (Avail var_name)) getDeclBinders new_name (FixD _) = returnRn Nothing -getDeclBinders new_name (ForD _) = returnRn Nothing + + -- foreign declarations +getDeclBinders new_name (ForD (ForeignDecl nm kind _ dyn _ loc)) + | binds_haskell_name kind dyn + = new_name nm loc `thenRn` \ name -> + returnRn (Just (Avail name)) + + | otherwise -- a foreign export + = lookupImplicitOccRn nm `thenRn_` + returnRn Nothing + getDeclBinders new_name (DefD _) = returnRn Nothing getDeclBinders new_name (InstD _) = returnRn Nothing getDeclBinders new_name (RuleD _) = returnRn Nothing +binds_haskell_name (FoImport _) _ = True +binds_haskell_name FoLabel _ = True +binds_haskell_name FoExport ext_nm = isDynamicExtName ext_nm + ---------------- -getConFieldNames new_name (ConDecl con _ _ (RecCon fielddecls) src_loc : rest) +getConFieldNames new_name (ConDecl con _ _ _ (RecCon fielddecls) src_loc : rest) = mapRn (\n -> new_name n src_loc) (con:fields) `thenRn` \ cfs -> getConFieldNames new_name rest `thenRn` \ ns -> returnRn (cfs ++ ns) where fields = concat (map fst fielddecls) -getConFieldNames new_name (ConDecl con _ _ condecl src_loc : rest) +getConFieldNames new_name (ConDecl con _ _ _ condecl src_loc : rest) = new_name con src_loc `thenRn` \ n -> (case condecl of NewCon _ (Just f) -> @@ -782,24 +945,24 @@ getConFieldNames new_name (ConDecl con _ _ condecl src_loc : rest) getConFieldNames new_name [] = returnRn [] -getClassOpNames new_name (ClassOpSig op _ _ src_loc) = new_name op src_loc +getClassOpNames new_name (ClassOpSig op _ _ _ src_loc) = new_name op src_loc \end{code} @getDeclSysBinders@ gets the implicit binders introduced by a decl. A the moment that's just the tycon and datacon that come with a class decl. -They aren'te returned by getDeclBinders because they aren't in scope; -but they *should* be put into the DeclsMap of this module. +They aren't returned by @getDeclBinders@ because they aren't in scope; +but they {\em should} be put into the @DeclsMap@ of this module. Note that this excludes the default-method names of a class decl, and the dict fun of an instance decl, because both of these have bindings of their own elsewhere. \begin{code} -getDeclSysBinders new_name (TyClD (ClassDecl _ cname _ sigs _ _ tname dname snames src_loc)) - = new_name dname src_loc `thenRn` \ datacon_name -> - new_name tname src_loc `thenRn` \ tycon_name -> - sequenceRn [new_name n src_loc | n <- snames] `thenRn` \ scsel_names -> - returnRn (tycon_name : datacon_name : scsel_names) +getDeclSysBinders new_name (TyClD (ClassDecl _ cname _ _ sigs _ _ tname dname dwname snames src_loc)) + = sequenceRn [new_name n src_loc | n <- (tname : dname : dwname : snames)] + +getDeclSysBinders new_name (TyClD (TyData _ _ _ _ cons _ _ _)) + = sequenceRn [new_name wkr_name src_loc | ConDecl _ wkr_name _ _ _ src_loc <- cons] getDeclSysBinders new_name other_decl = returnRn [] @@ -812,50 +975,35 @@ getDeclSysBinders new_name other_decl %********************************************************* \begin{code} -findAndReadIface :: SDoc -> ModuleName -> WhereFrom - -> Bool -- Only relevant for SystemImport - -- True <=> Look for a .hi file - -- False <=> Look for .hi-boot file unless there's - -- a library .hi file - -> RnM d (Bool, Maybe (Module, ParsedIface)) - -- Bool is True if the interface actually read was a .hi-boot one +findAndReadIface :: SDoc -> ModuleName + -> IsBootInterface -- True <=> Look for a .hi-boot file + -- False <=> Look for .hi file + -> RnM d (Maybe ParsedIface) -- Nothing <=> file not found, or unreadable, or illegible -- Just x <=> successfully found and parsed -findAndReadIface doc_str mod_name from hi_file +findAndReadIface doc_str mod_name hi_boot_file = traceRn trace_msg `thenRn_` -- we keep two maps for interface files, -- one for 'normal' ones, the other for .hi-boot files, -- hence the need to signal which kind we're interested. - getHiMaps `thenRn` \ hi_maps -> + getHiMaps `thenRn` \ (hi_map, hiboot_map) -> + let + relevant_map | hi_boot_file = hiboot_map + | otherwise = hi_map + in + case lookupFM relevant_map mod_name of + -- Found the file + Just fpath -> traceRn (ptext SLIT("...reading from") <+> text fpath) `thenRn_` + readIface mod_name fpath - case find_path from hi_maps of - -- Found the file - (hi_boot, Just (fpath, mod)) -> traceRn (ptext SLIT("...reading from") <+> text fpath) `thenRn_` - readIface mod fpath `thenRn` \ result -> - returnRn (hi_boot, result) - (hi_boot, Nothing) -> traceRn (ptext SLIT("...not found")) `thenRn_` - returnRn (hi_boot, Nothing) + -- Can't find it + Nothing -> traceRn (ptext SLIT("...not found")) `thenRn_` + returnRn Nothing where - find_path ImportByUser (hi_map, _) = (False, lookupFM hi_map mod_name) - find_path ImportByUserSource (_, hiboot_map) = (True, lookupFM hiboot_map mod_name) - - find_path ImportBySystem (hi_map, hiboot_map) - | hi_file - = -- If the module we seek is in our dependent set, - -- Look for a .hi file - (False, lookupFM hi_map mod_name) - - | otherwise - -- Check if there's a library module of that name - -- If not, look for an hi-boot file - = case lookupFM hi_map mod_name of - stuff@(Just (_, mod)) | isLibModule mod -> (False, stuff) - other -> (True, lookupFM hiboot_map mod_name) - trace_msg = sep [hsep [ptext SLIT("Reading"), - ppr from, + if hi_boot_file then ptext SLIT("[boot]") else empty, ptext SLIT("interface for"), pprModuleName mod_name <> semi], nest 4 (ptext SLIT("reason:") <+> doc_str)] @@ -864,23 +1012,31 @@ findAndReadIface doc_str mod_name from hi_file @readIface@ tries just the one file. \begin{code} -readIface :: Module -> String -> RnM d (Maybe (Module, ParsedIface)) +readIface :: ModuleName -> String -> RnM d (Maybe ParsedIface) -- Nothing <=> file not found, or unreadable, or illegible -- Just x <=> successfully found and parsed -readIface the_mod file_path - = ioToRnM (hGetStringBuffer file_path) `thenRn` \ read_result -> +readIface wanted_mod file_path + = ioToRnM (hGetStringBuffer False file_path) `thenRn` \ read_result -> case read_result of Right contents -> - case parseIface contents (mkSrcLoc (mkFastString file_path) 1) of - Failed err -> failWithRn Nothing err - Succeeded (PIface mod_nm iface) -> - warnCheckRn (mod_nm == moduleName the_mod) - (hsep [ ptext SLIT("Something is amiss; requested module name") - , pprModule the_mod - , ptext SLIT("differs from name found in the interface file ") - , pprModuleName mod_nm - ]) `thenRn_` - returnRn (Just (the_mod, iface)) + case parseIface contents + PState{ bol = 0#, atbol = 1#, + context = [], + glasgow_exts = 1#, + loc = mkSrcLoc (mkFastString file_path) 1 } of + POk _ (PIface iface) -> + warnCheckRn (read_mod == wanted_mod) + (hiModuleNameMismatchWarn wanted_mod read_mod) `thenRn_` + returnRn (Just iface) + where + read_mod = moduleName (pi_mod iface) + + PFailed err -> failWithRn Nothing err + other -> failWithRn Nothing (ptext SLIT("Unrecognisable interface file")) + -- This last case can happen if the interface file is (say) empty + -- in which case the parser thinks it looks like an IdInfo or + -- something like that. Just an artefact of the fact that the + -- parser is used for several purposes at once. Left err | isDoesNotExistError err -> returnRn Nothing @@ -908,19 +1064,32 @@ cannaeReadFile file err text (show err)] getDeclErr name - = ptext SLIT("Failed to find interface decl for") <+> quotes (ppr name) + = vcat [ptext SLIT("Failed to find interface decl for") <+> quotes (ppr name), + ptext SLIT("from module") <+> quotes (ppr (nameModule name)) + ] getDeclWarn name loc = sep [ptext SLIT("Failed to find (optional) interface decl for") <+> quotes (ppr name), ptext SLIT("desired at") <+> ppr loc] -importDeclWarn mod name - = sep [ptext SLIT("Compiler tried to import decl from interface file with same name as module."), - ptext SLIT("(possible cause: module name clashes with interface file already in scope.)") +importDeclWarn name + = sep [ptext SLIT( + "Compiler tried to import decl from interface file with same name as module."), + ptext SLIT( + "(possible cause: module name clashes with interface file already in scope.)") ] $$ - hsep [ptext SLIT("Interface:"), quotes (pprModuleName mod), - comma, ptext SLIT("name:"), quotes (ppr name)] + hsep [ptext SLIT("name:"), quotes (ppr name)] warnRedundantSourceImport mod_name - = ptext SLIT("Unnecessary {- SOURCE -} in the import of module") <+> quotes (pprModuleName mod_name) + = ptext SLIT("Unnecessary {- SOURCE -} in the import of module") + <+> quotes (pprModuleName mod_name) + +hiModuleNameMismatchWarn :: ModuleName -> ModuleName -> Message +hiModuleNameMismatchWarn requested_mod read_mod = + hsep [ ptext SLIT("Something is amiss; requested module name") + , pprModuleName requested_mod + , ptext SLIT("differs from name found in the interface file") + , pprModuleName read_mod + ] + \end{code}