X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRnIfaces.lhs;h=453fda3343de35598562102c82ff9a1fe466e75e;hb=2494407a750053daa61718fac371487d04818e57;hp=649391dd4d29a5a80e3f96eed6acc1a7a4ceee4a;hpb=7a3bd641457666e10d0a47be9f22762e03defbf0;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/RnIfaces.lhs b/ghc/compiler/rename/RnIfaces.lhs index 649391d..453fda3 100644 --- a/ghc/compiler/rename/RnIfaces.lhs +++ b/ghc/compiler/rename/RnIfaces.lhs @@ -10,8 +10,8 @@ module RnIfaces ( getInterfaceExports, getImportedInstDecls, getSpecialInstModules, - getDecl, getWiredInDecl, - getImportVersions, + importDecl, recordSlurp, + getImportVersions, checkUpToDate, @@ -22,25 +22,29 @@ module RnIfaces ( IMP_Ubiq() -import HsSyn ( HsDecl(..), TyDecl(..), ClassDecl(..), HsTyVar, Bind, HsExpr, Sig(..), - HsBinds(..), MonoBinds, DefaultDecl, ConDecl(..), HsType, BangType, IfaceSig(..), - FixityDecl(..), Fixity, Fake, InPat, InstDecl(..), SYN_IE(Version), HsIdInfo +import CmdLineOpts ( opt_HiSuffix, opt_HiSuffixPrelude ) +import HsSyn ( HsDecl(..), TyDecl(..), ClassDecl(..), HsTyVar, Bind, HsExpr, Sig(..), HsType(..), + HsBinds(..), MonoBinds, DefaultDecl, ConDecl(..), BangType, IfaceSig(..), + FixityDecl(..), Fixity, Fake, InPat, InstDecl(..), SYN_IE(Version), HsIdInfo, + IE(..) ) import HsPragmas ( noGenPragmas ) import RdrHsSyn ( SYN_IE(RdrNameHsDecl), SYN_IE(RdrNameInstDecl), RdrName, rdrNameOcc ) -import RnEnv ( newGlobalName, lookupRn, addImplicitOccsRn, availNames ) +import RnEnv ( newGlobalName, lookupRn, addImplicitOccsRn, + availName, availNames, addAvailToNameSet, pprAvail + ) import RnSource ( rnHsType ) import RnMonad import ParseIface ( parseIface ) import ErrUtils ( SYN_IE(Error), SYN_IE(Warning) ) -import FiniteMap ( FiniteMap, emptyFM, unitFM, lookupFM, addToFM, addListToFM, fmToList ) +import FiniteMap ( FiniteMap, emptyFM, unitFM, lookupFM, addToFM, addToFM_C, addListToFM, fmToList ) import Name ( Name {-instance NamedThing-}, Provenance, OccName(..), modAndOcc, occNameString, moduleString, pprModule, NameSet(..), emptyNameSet, unionNameSets, nameSetToList, - minusNameSet, mkNameSet, + minusNameSet, mkNameSet, elemNameSet, isWiredInName, maybeWiredInTyConName, maybeWiredInIdName ) import Id ( GenId, Id(..), idType, dataConTyCon, isDataCon ) @@ -48,13 +52,15 @@ import TyCon ( TyCon, tyConDataCons, isSynTyCon, getSynTyConDefn ) import Type ( namesOfType ) import TyVar ( GenTyVar ) import SrcLoc ( mkIfaceSrcLoc ) -import PrelMods ( gHC__ ) +import PrelMods ( gHC__, isPreludeModule ) import Bag import Maybes ( MaybeErr(..), expectJust, maybeToBool ) import ListSetOps ( unionLists ) import Pretty import PprStyle ( PprStyle(..) ) -import Util ( pprPanic ) +import Util ( pprPanic, pprTrace ) +import StringBuffer ( StringBuffer, hGetStringBuffer, freeStringBuffer ) + \end{code} @@ -70,10 +76,10 @@ loadInterface :: Pretty -> Module -> RnMG Ifaces loadInterface doc_str load_mod = getIfacesRn `thenRn` \ ifaces -> let - Ifaces this_mod mod_vers_map export_env_map vers_map decls_map inst_map inst_mods = ifaces + Ifaces this_mod mod_vers_map export_envs decls all_names imp_names insts inst_mods = ifaces in -- CHECK WHETHER WE HAVE IT ALREADY - if maybeToBool (lookupFM export_env_map load_mod) + if maybeToBool (lookupFM export_envs load_mod) then returnRn ifaces -- Already in the cache; don't re-read it else @@ -85,80 +91,96 @@ loadInterface doc_str load_mod Nothing -> -- Not found, so add an empty export env to the Ifaces map -- so that we don't look again let - new_export_env_map = addToFM export_env_map load_mod ([],[]) - new_ifaces = Ifaces this_mod mod_vers_map - new_export_env_map - vers_map decls_map inst_map inst_mods + new_export_envs = addToFM export_envs load_mod ([],[]) + new_ifaces = Ifaces this_mod mod_vers_map + new_export_envs + decls all_names imp_names insts inst_mods in setIfacesRn new_ifaces `thenRn_` failWithRn new_ifaces (noIfaceErr load_mod) ; -- Found and parsed! - Just (ParsedIface _ mod_vers usages exports rd_inst_mods fixs decls insts) -> + Just (ParsedIface _ mod_vers usages exports rd_inst_mods fixs rd_decls rd_insts) -> -- LOAD IT INTO Ifaces - mapRn loadExport exports `thenRn` \ avails -> - foldlRn (loadDecl load_mod) (decls_map,vers_map) decls `thenRn` \ (new_decls_map, new_vers_map) -> - foldlRn (loadInstDecl load_mod) inst_map insts `thenRn` \ new_insts_map -> + mapRn loadExport exports `thenRn` \ avails_s -> + foldlRn (loadDecl load_mod) decls rd_decls `thenRn` \ new_decls -> + foldlRn (loadInstDecl load_mod) insts rd_insts `thenRn` \ new_insts -> let - export_env = (avails, fixs) + export_env = (concat avails_s, fixs) -- Exclude this module from the "special-inst" modules new_inst_mods = inst_mods `unionLists` (filter (/= this_mod) rd_inst_mods) new_ifaces = Ifaces this_mod (addToFM mod_vers_map load_mod mod_vers) - (addToFM export_env_map load_mod export_env) - new_vers_map - new_decls_map - new_insts_map + (addToFM export_envs load_mod export_env) + new_decls + all_names imp_names + new_insts new_inst_mods in setIfacesRn new_ifaces `thenRn_` returnRn new_ifaces } -loadExport :: ExportItem -> RnMG AvailInfo -loadExport (mod, occ, occs) - = new_name occ `thenRn` \ name -> - mapRn new_name occs `thenRn` \ names -> - returnRn (Avail name names) +loadExport :: ExportItem -> RnMG [AvailInfo] +loadExport (mod, entities) + = mapRn load_entity entities where new_name occ = newGlobalName mod occ -loadVersion :: Module -> VersionMap -> (OccName,Version) -> RnMG VersionMap -loadVersion mod vers_map (occ, version) - = newGlobalName mod occ `thenRn` \ name -> - returnRn (addToFM vers_map name version) +-- The communcation between this little code fragment and the "entity" rule +-- in ParseIface.y is a bit gruesome. The idea is that things which are +-- destined to be AvailTCs show up as (occ, [non-empty-list]), whereas +-- things destined to be Avails show up as (occ, []) + load_entity (occ, occs) + = new_name occ `thenRn` \ name -> + if null occs then + returnRn (Avail name) + else + mapRn new_name occs `thenRn` \ names -> + returnRn (AvailTC name names) -loadDecl :: Module -> (DeclsMap, VersionMap) +loadDecl :: Module -> DeclsMap -> (Version, RdrNameHsDecl) - -> RnMG (DeclsMap, VersionMap) -loadDecl mod (decls_map, vers_map) (version, decl) - = getDeclBinders new_implicit_name decl `thenRn` \ avail@(Avail name _) -> + -> RnMG DeclsMap +loadDecl mod decls_map (version, decl) + = getDeclBinders new_implicit_name decl `thenRn` \ avail -> returnRn (addListToFM decls_map - [(name,(avail,decl)) | name <- availNames avail], - addToFM vers_map name version + [(name,(version,avail,decl)) | name <- availNames avail] ) where new_implicit_name rdr_name loc = newGlobalName mod (rdrNameOcc rdr_name) -loadInstDecl :: Module -> Bag IfaceInst -> RdrNameInstDecl -> RnMG (Bag IfaceInst) +loadInstDecl :: Module + -> Bag IfaceInst + -> RdrNameInstDecl + -> RnMG (Bag IfaceInst) loadInstDecl mod_name insts decl@(InstDecl inst_ty binds uprags dfun_name src_loc) - = initRnMS emptyRnEnv mod_name InterfaceMode $ - - -- Find out what type constructors and classes are mentioned in the - -- instance declaration. We have to be a bit clever. + = + -- Find out what type constructors and classes are "gates" for the + -- instance declaration. If all these "gates" are slurped in then + -- we should slurp the instance decl too. + -- + -- We *don't* want to count names in the context part as gates, though. + -- For example: + -- instance Foo a => Baz (T a) where ... -- - -- We want to rename the type so that we can find what - -- (free) type constructors are inside it. But we must *not* thereby - -- put new occurrences into the global pool because otherwise we'll force - -- them all to be loaded. We kill two birds with ones stone by renaming - -- with a fresh occurrence pool. - findOccurrencesRn (rnHsType inst_ty) `thenRn` \ ty_names -> - - returnRn ((ty_names, mod_name, decl) `consBag` insts) + -- Here the gates are Baz and T, but *not* Foo. + let + munged_inst_ty = case inst_ty of + HsForAllTy tvs cxt ty -> HsForAllTy tvs [] ty + HsPreForAllTy cxt ty -> HsPreForAllTy [] ty + other -> inst_ty + in + -- We find the gates by renaming the instance type with in a + -- and returning the occurrence pool. + initRnMS emptyRnEnv mod_name InterfaceMode ( + findOccurrencesRn (rnHsType munged_inst_ty) + ) `thenRn` \ gate_names -> + returnRn (((mod_name, decl), gate_names) `consBag` insts) \end{code} @@ -173,8 +195,9 @@ checkUpToDate :: Module -> RnMG Bool -- True <=> no need to recompile checkUpToDate mod_name = findAndReadIface doc_str mod_name `thenRn` \ read_result -> case read_result of - Nothing -> -- Old interface file not found, so we'd better bale out - traceRn (ppSep [ppStr "Didnt find old iface", pprModule PprDebug mod_name]) `thenRn_` + Nothing -> -- Old interface file not found, so we'd better bail out + traceRn (ppSep [ppPStr SLIT("Didnt find old iface"), + pprModule PprDebug mod_name]) `thenRn_` returnRn False Just (ParsedIface _ _ usages _ _ _ _ _) @@ -182,7 +205,7 @@ checkUpToDate mod_name checkModUsage usages where -- Only look in current directory, with suffix .hi - doc_str = ppSep [ppStr "Need usage info from", pprModule PprDebug mod_name] + doc_str = ppSep [ppPStr SLIT("Need usage info from"), pprModule PprDebug mod_name] checkModUsage [] = returnRn True -- Yes! Everything is up to date! @@ -190,52 +213,54 @@ checkModUsage [] = returnRn True -- Yes! Everything is up to date! checkModUsage ((mod, old_mod_vers, old_local_vers) : rest) = loadInterface doc_str mod `thenRn` \ ifaces -> let - Ifaces _ mod_vers_map _ new_vers_map _ _ _ = ifaces - maybe_new_mod_vers = lookupFM mod_vers_map mod + Ifaces _ mod_vers _ decls _ _ _ _ = ifaces + maybe_new_mod_vers = lookupFM mod_vers mod Just new_mod_vers = maybe_new_mod_vers in -- If we can't find a version number for the old module then - -- bale out saying things aren't up to date + -- bail out saying things aren't up to date if not (maybeToBool maybe_new_mod_vers) then returnRn False else -- If the module version hasn't changed, just move on if new_mod_vers == old_mod_vers then - traceRn (ppSep [ppStr "Module version unchanged:", pprModule PprDebug mod]) `thenRn_` + traceRn (ppSep [ppPStr SLIT("Module version unchanged:"), pprModule PprDebug mod]) `thenRn_` checkModUsage rest else - traceRn (ppSep [ppStr "Module version has changed:", pprModule PprDebug mod]) `thenRn_` + traceRn (ppSep [ppPStr SLIT("Module version has changed:"), pprModule PprDebug mod]) `thenRn_` -- New module version, so check entities inside - checkEntityUsage mod new_vers_map old_local_vers `thenRn` \ up_to_date -> + checkEntityUsage mod decls old_local_vers `thenRn` \ up_to_date -> if up_to_date then - traceRn (ppStr "...but the bits I use havn't.") `thenRn_` + traceRn (ppPStr 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 where - doc_str = ppSep [ppStr "need version info for", pprModule PprDebug mod] + doc_str = ppSep [ppPStr SLIT("need version info for"), pprModule PprDebug mod] -checkEntityUsage mod new_vers_map [] +checkEntityUsage mod decls [] = returnRn True -- Yes! All up to date! -checkEntityUsage mod new_vers_map ((occ_name,old_vers) : rest) +checkEntityUsage mod decls ((occ_name,old_vers) : rest) = newGlobalName mod occ_name `thenRn` \ name -> - case lookupFM new_vers_map name of + case lookupFM decls name of Nothing -> -- We used it before, but it ain't there now - traceRn (ppSep [ppStr "...and this no longer exported:", ppr PprDebug name]) `thenRn_` + traceRn (ppSep [ppPStr SLIT("...and this no longer exported:"), ppr PprDebug name]) `thenRn_` returnRn False - Just new_vers -> -- It's there, but is it up to date? - if new_vers == old_vers then - -- Up to date, so check the rest - checkEntityUsage mod new_vers_map rest - else - traceRn (ppSep [ppStr "...and this is out of date:", ppr PprDebug name]) `thenRn_` - returnRn False -- Out of date, so bale out + Just (new_vers,_,_) -- It's there, but is it up to date? + | new_vers == old_vers + -- Up to date, so check the rest + -> checkEntityUsage mod decls rest + + | otherwise + -- Out of date, so bale out + -> traceRn (ppSep [ppPStr SLIT("...and this is out of date:"), ppr PprDebug name]) `thenRn_` + returnRn False \end{code} @@ -246,24 +271,57 @@ checkEntityUsage mod new_vers_map ((occ_name,old_vers) : rest) %********************************************************* \begin{code} -getDecl :: Name -> RnMG (AvailInfo, RdrNameHsDecl) -getDecl name - = traceRn doc_str `thenRn_` - loadInterface doc_str mod `thenRn` \ (Ifaces _ _ _ _ decls_map _ _) -> - case lookupFM decls_map name of +importDecl :: Name -> Necessity -> RnMG (Maybe RdrNameHsDecl) + -- Returns Nothing for a wired-in or already-slurped decl + +importDecl name necessity + = checkSlurped name `thenRn` \ already_slurped -> + if already_slurped then + -- traceRn (ppSep [ppStr "Already slurped:", ppr PprDebug name]) `thenRn_` + returnRn Nothing -- Already dealt with + else + if isWiredInName name then + getWiredInDecl name + else + getIfacesRn `thenRn` \ ifaces -> + let + Ifaces this_mod _ _ _ _ _ _ _ = ifaces + (mod,_) = modAndOcc name + in + if mod == this_mod then -- Don't bring in decls from + pprTrace "importDecl wierdness:" (ppr PprDebug name) $ + returnRn Nothing -- the renamed module's own interface file + -- + else + getNonWiredInDecl name necessity - Just avail_w_decl -> returnRn avail_w_decl +\end{code} - Nothing -> -- Can happen legitimately for "Optional" occurrences - returnRn (NotAvailable, ValD EmptyBinds) +\begin{code} +getNonWiredInDecl :: Name -> Necessity -> RnMG (Maybe RdrNameHsDecl) +getNonWiredInDecl name necessity + = traceRn doc_str `thenRn_` + loadInterface doc_str mod `thenRn` \ (Ifaces _ _ _ decls _ _ _ _) -> + case lookupFM decls name of + + Just (version,avail,decl) -> recordSlurp (Just version) avail `thenRn_` + returnRn (Just decl) + + Nothing -> -- Can happen legitimately for "Optional" occurrences + case necessity of { + Optional -> addWarnRn (getDeclWarn name); + other -> addErrRn (getDeclErr name) + } `thenRn_` + returnRn Nothing where + doc_str = ppSep [ppPStr SLIT("Need decl for"), ppr PprDebug name] (mod,_) = modAndOcc name - doc_str = ppSep [ppStr "Need decl for", ppr PprDebug name] \end{code} @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, it brings in the type constructor and all the data constructors; and marks as "occurrences" any free vars of the data con. @@ -280,44 +338,70 @@ 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. \begin{code} -getWiredInDecl :: Name -> RnMG AvailInfo getWiredInDecl name - = -- Force in the home module in case it has instance decls for - -- the thing we are interested in - (if mod == gHC__ then - returnRn () -- Mini hack; GHC is guaranteed not to have - -- instance decls, so it's a waste of time - -- to read it + = get_wired `thenRn` \ avail -> + recordSlurp Nothing avail `thenRn_` + + -- Force in the home module in case it has instance decls for + -- the thing we are interested in. + -- + -- Mini hack 1: no point for non-tycons/class; and if we + -- do this we find PrelNum trying to import PackedString, + -- because PrelBase's .hi file mentions PackedString.unpackString + -- But PackedString.hi isn't built by that point! + -- + -- Mini hack 2; GHC is guaranteed not to have + -- instance decls, so it's a waste of time to read it + -- + -- NB: We *must* look at the availName of the slurped avail, + -- not the name passed to getWiredInDecl! Why? Because if a data constructor + -- or class op is passed to getWiredInDecl we'll pull in the whole data/class + -- decl, and recordSlurp will record that fact. But since the data constructor + -- isn't a tycon/class we won't force in the home module. And even if the + -- type constructor/class comes along later, loadDecl will say that it's already + -- been slurped, so getWiredInDecl won't even be called. Pretty obscure bug, this was. + let + main_name = availName avail + main_is_tc = case avail of { AvailTC _ _ -> True; Avail _ -> False } + (mod,_) = modAndOcc main_name + doc_str = ppSep [ppPStr SLIT("Need home module for wired in thing"), ppr PprDebug name] + in + (if not main_is_tc || mod == gHC__ then + returnRn () else loadInterface doc_str mod `thenRn_` returnRn () - ) `thenRn_` - - if (maybeToBool maybe_wired_in_tycon) then - get_wired_tycon the_tycon - else -- Must be a wired-in-Id - if (isDataCon the_id) then -- ... a wired-in data constructor - get_wired_tycon (dataConTyCon the_id) - else -- ... a wired-in non data-constructor - get_wired_id the_id + ) `thenRn_` + + returnRn Nothing -- No declaration to process further where - doc_str = ppSep [ppStr "Need home module for wired in thing", ppr PprDebug name] - (mod,_) = modAndOcc name + + get_wired | is_tycon -- ... a type constructor + = get_wired_tycon the_tycon + + | (isDataCon the_id) -- ... a wired-in data constructor + = get_wired_tycon (dataConTyCon the_id) + + | otherwise -- ... a wired-in non data-constructor + = get_wired_id the_id + maybe_wired_in_tycon = maybeWiredInTyConName name + is_tycon = maybeToBool maybe_wired_in_tycon maybe_wired_in_id = maybeWiredInIdName name Just the_tycon = maybe_wired_in_tycon Just the_id = maybe_wired_in_id + get_wired_id id = addImplicitOccsRn (nameSetToList id_mentioned) `thenRn_` - returnRn (Avail (getName id) []) + returnRn (Avail (getName id)) where - id_mentioned = namesOfType (idType id) + id_mentioned = namesOfType (idType id) get_wired_tycon tycon | isSynTyCon tycon = addImplicitOccsRn (nameSetToList mentioned) `thenRn_` - returnRn (Avail (getName tycon) []) + returnRn (Avail (getName tycon)) where (tyvars,ty) = getSynTyConDefn tycon mentioned = namesOfType ty `minusNameSet` mkNameSet (map getName tyvars) @@ -325,13 +409,39 @@ get_wired_tycon tycon get_wired_tycon tycon | otherwise -- data or newtype = addImplicitOccsRn (nameSetToList mentioned) `thenRn_` - returnRn (Avail (getName tycon) (map getName data_cons)) + returnRn (AvailTC tycon_name (tycon_name : map getName data_cons)) where - data_cons = tyConDataCons tycon - mentioned = foldr (unionNameSets . namesOfType . idType) emptyNameSet data_cons + tycon_name = getName tycon + data_cons = tyConDataCons tycon + mentioned = foldr (unionNameSets . namesOfType . idType) emptyNameSet data_cons \end{code} +\begin{code} +checkSlurped name + = getIfacesRn `thenRn` \ (Ifaces _ _ _ _ slurped_names _ _ _) -> + returnRn (name `elemNameSet` slurped_names) + +recordSlurp maybe_version avail + = -- traceRn (ppSep [ppStr "Record slurp:", pprAvail PprDebug avail]) `thenRn_` + getIfacesRn `thenRn` \ ifaces -> + let + Ifaces this_mod mod_vers export_envs decls slurped_names imp_names insts inst_mods = ifaces + new_slurped_names = addAvailToNameSet slurped_names avail + + new_imp_names = case maybe_version of + Just version -> (availName avail, version) : imp_names + Nothing -> imp_names + + new_ifaces = Ifaces this_mod mod_vers export_envs decls + new_slurped_names + new_imp_names + insts + inst_mods + in + setIfacesRn new_ifaces +\end{code} + %********************************************************* %* * \subsection{Getting other stuff} @@ -341,7 +451,7 @@ get_wired_tycon tycon \begin{code} getInterfaceExports :: Module -> RnMG (Avails, [(OccName,Fixity)]) getInterfaceExports mod - = loadInterface doc_str mod `thenRn` \ (Ifaces _ _ export_envs _ _ _ _) -> + = loadInterface doc_str mod `thenRn` \ (Ifaces _ _ export_envs _ _ _ _ _) -> case lookupFM export_envs mod of Nothing -> -- Not there; it must be that the interface file wasn't found; -- the error will have been reported already. @@ -351,66 +461,133 @@ getInterfaceExports mod Just stuff -> returnRn stuff where - doc_str = ppSep [pprModule PprDebug mod, ppStr "is directly imported"] + doc_str = ppSep [pprModule PprDebug mod, ppPStr SLIT("is directly imported")] -getImportedInstDecls :: RnMG [IfaceInst] +getImportedInstDecls :: RnMG [(Module,RdrNameInstDecl)] getImportedInstDecls = -- First load any special-instance modules that aren't aready loaded getSpecialInstModules `thenRn` \ inst_mods -> mapRn load_it inst_mods `thenRn_` -- Now we're ready to grab the instance declarations - getIfacesRn `thenRn` \ ifaces -> + -- Find the un-gated ones and return them, + -- removing them from the bag kept in Ifaces + getIfacesRn `thenRn` \ ifaces -> let - Ifaces _ _ _ _ _ insts _ = ifaces + Ifaces this_mod mod_vers export_envs decls slurped_names imp_names insts inst_mods = ifaces + + -- An instance decl is ungated if all its gates have been slurped + select_ungated :: IfaceInst -- A gated inst decl + + -> ([(Module, RdrNameInstDecl)], [IfaceInst]) -- Accumulator + + -> ([(Module, RdrNameInstDecl)], -- The ungated ones + [IfaceInst]) -- Still gated, but with + -- depeleted gates + select_ungated (decl,gates) (ungated_decls, gated_decls) + | null remaining_gates + = (decl : ungated_decls, gated_decls) + | otherwise + = (ungated_decls, (decl, remaining_gates) : gated_decls) + where + remaining_gates = filter (not . (`elemNameSet` slurped_names)) gates + + (un_gated_insts, still_gated_insts) = foldrBag select_ungated ([], []) insts + + new_ifaces = Ifaces this_mod mod_vers export_envs decls slurped_names imp_names + (listToBag still_gated_insts) + inst_mods in - returnRn (bagToList insts) + setIfacesRn new_ifaces `thenRn_` + returnRn un_gated_insts where load_it mod = loadInterface (doc_str mod) mod - doc_str mod = ppSep [pprModule PprDebug mod, ppStr "is a special-instance module"] + doc_str mod = ppSep [pprModule PprDebug mod, ppPStr SLIT("is a special-instance module")] + getSpecialInstModules :: RnMG [Module] getSpecialInstModules = getIfacesRn `thenRn` \ ifaces -> let - Ifaces _ _ _ _ _ _ inst_mods = ifaces + Ifaces _ _ _ _ _ _ _ inst_mods = ifaces in returnRn inst_mods \end{code} +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". + +Why the latter? 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. + \begin{code} -getImportVersions :: [AvailInfo] -- Imported avails +getImportVersions :: Module -- Name of this module + -> Maybe [IE any] -- Export list for this module -> RnMG (VersionInfo Name) -- Version info for these names -getImportVersions imported_avails +getImportVersions this_mod exports = getIfacesRn `thenRn` \ ifaces -> let - Ifaces _ mod_versions_map _ version_map _ _ _ = ifaces - - -- import_versions is harder: we have to group together all the things imported - -- from a particular module. We do this with yet another finite map - - mv_map :: FiniteMap Module [LocalVersion Name] - mv_map = foldl add_mv emptyFM imported_avails - add_mv mv_map (Avail name _) - | isWiredInName name = mv_map -- Don't record versions for wired-in names - | otherwise = case lookupFM mv_map mod of - Just versions -> addToFM mv_map mod ((name,version):versions) - Nothing -> addToFM mv_map mod [(name,version)] - where - (mod,_) = modAndOcc name - version = case lookupFM version_map name of - Just v -> v - Nothing -> pprPanic "getVersionInfo:" (ppr PprDebug name) - - import_versions = [ (mod, expectJust "import_versions" (lookupFM mod_versions_map mod), local_versions) - | (mod, local_versions) <- fmToList mv_map - ] - - -- Question: should we filter the builtins out of import_versions? + Ifaces _ mod_versions_map _ _ _ imp_names _ _ = ifaces + mod_version mod = expectJust "import_versions" (lookupFM mod_versions_map mod) + + -- mv_map groups together all the things imported from a particular module. + mv_map, mv_map_mod :: FiniteMap Module [LocalVersion Name] + + mv_map_mod = foldl add_mod emptyFM export_mods + -- mv_map_mod records all the modules that have a "module M" + -- in this module's export list + + mv_map = foldl add_mv mv_map_mod imp_names + -- mv_map adds the version numbers of things exported individually in - returnRn import_versions + returnRn [ (mod, mod_version mod, local_versions) + | (mod, local_versions) <- fmToList mv_map + ] + + where + export_mods = case exports of + Nothing -> [] + Just es -> [mod | IEModuleContents mod <- es, mod /= this_mod] + + add_mv mv_map v@(name, version) + = addToFM_C (\ ls _ -> (v:ls)) mv_map mod [v] + where + (mod,_) = modAndOcc name + + add_mod mv_map mod = addToFM mv_map mod [] \end{code} %********************************************************* @@ -434,25 +611,25 @@ getDeclBinders :: (RdrName -> SrcLoc -> RnMG Name) -- New-name function getDeclBinders new_name (TyD (TyData _ tycon _ condecls _ _ src_loc)) = new_name tycon src_loc `thenRn` \ tycon_name -> getConFieldNames new_name condecls `thenRn` \ sub_names -> - returnRn (Avail tycon_name sub_names) + returnRn (AvailTC tycon_name (tycon_name : sub_names)) getDeclBinders new_name (TyD (TyNew _ tycon _ (NewConDecl con _ con_loc) _ _ src_loc)) = new_name tycon src_loc `thenRn` \ tycon_name -> new_name con src_loc `thenRn` \ con_name -> - returnRn (Avail tycon_name [con_name]) + returnRn (AvailTC tycon_name [tycon_name, con_name]) getDeclBinders new_name (TyD (TySynonym tycon _ _ src_loc)) = new_name tycon src_loc `thenRn` \ tycon_name -> - returnRn (Avail tycon_name []) + returnRn (Avail tycon_name) getDeclBinders new_name (ClD (ClassDecl _ cname _ sigs _ _ src_loc)) = new_name cname src_loc `thenRn` \ class_name -> mapRn (getClassOpNames new_name) sigs `thenRn` \ sub_names -> - returnRn (Avail class_name sub_names) + returnRn (AvailTC class_name (class_name : sub_names)) getDeclBinders new_name (SigD (IfaceSig var ty prags src_loc)) = new_name var src_loc `thenRn` \ var_name -> - returnRn (Avail var_name []) + returnRn (Avail var_name) getDeclBinders new_name (DefD _) = returnRn NotAvailable getDeclBinders new_name (InstD _) = returnRn NotAvailable @@ -501,21 +678,28 @@ findAndReadIface doc_str mod getSearchPathRn `thenRn` \ dirs -> try dirs dirs where - trace_msg = ppHang (ppBesides [ppStr "Reading interface for ", + trace_msg = ppHang (ppBesides [ppPStr SLIT("Reading interface for "), pprModule PprDebug mod, ppSemi]) - 4 (ppBesides [ppStr "reason: ", doc_str]) + 4 (ppBesides [ppPStr SLIT("reason: "), doc_str]) - try all_dirs [] = traceRn (ppStr "...failed") `thenRn_` + mod_str = moduleString mod + hisuf = + if isPreludeModule mod then + case opt_HiSuffixPrelude of { Just hisuf -> hisuf; _ -> ".hi"} + else + case opt_HiSuffix of {Just hisuf -> hisuf; _ -> ".hi"} + + try all_dirs [] = traceRn (ppPStr SLIT("...failed")) `thenRn_` returnRn Nothing try all_dirs (dir:dirs) = readIface file_path `thenRn` \ read_result -> case read_result of Nothing -> try all_dirs dirs - Just iface -> traceRn (ppStr "...done") `thenRn_` + Just iface -> traceRn (ppPStr SLIT("...done")) `thenRn_` returnRn (Just iface) where - file_path = dir ++ "/" ++ moduleString mod ++ ".hi" + file_path = dir ++ "/" ++ moduleString mod ++ hisuf \end{code} @readIface@ trys just one file. @@ -525,11 +709,14 @@ readIface :: String -> RnMG (Maybe ParsedIface) -- Nothing <=> file not found, or unreadable, or illegible -- Just x <=> successfully found and parsed readIface file_path - = ioToRnMG (readFile file_path) `thenRn` \ read_result -> + = ioToRnMG (hGetStringBuffer file_path) `thenRn` \ read_result -> +--OLD: = ioToRnMG (readFile file_path) `thenRn` \ read_result -> case read_result of Right contents -> case parseIface contents of - Failed err -> failWithRn Nothing err - Succeeded iface -> returnRn (Just iface) + Failed err -> --ioToRnMG (freeStringBuffer contents) `thenRn` \ _ -> + failWithRn Nothing err + Succeeded iface -> --ioToRnMG (freeStringBuffer contents) `thenRn` \ _ -> + returnRn (Just iface) Left (NoSuchThing _) -> returnRn Nothing @@ -563,9 +750,15 @@ mkSearchPath (Just s) \begin{code} noIfaceErr mod sty - = ppBesides [ppStr "Could not find interface for ", ppQuote (pprModule sty mod)] + = ppBesides [ppPStr SLIT("Could not find valid interface file for "), ppQuote (pprModule sty mod)] -- , ppStr " in"]) 4 (ppAboves (map ppStr dirs)) cannaeReadFile file err sty - = ppBesides [ppPStr SLIT("Failed in reading file: "), ppStr file, ppStr "; error=", ppStr (show err)] + = ppBesides [ppPStr SLIT("Failed in reading file: "), ppStr file, ppPStr SLIT("; error="), ppStr (show err)] + +getDeclErr name sty + = ppSep [ppPStr SLIT("Failed to find interface decl for"), ppr sty name] + +getDeclWarn name sty + = ppSep [ppPStr SLIT("Warning: failed to find (optional) interface decl for"), ppr sty name] \end{code}