X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRnHiFiles.lhs;h=6d4f26f65e15f3eae81d573645ec0b071f3e997d;hb=2e63bea6efcfe3020623a0eb7ad8dae42ae4468f;hp=ad4f8c1e453a4ad0161ed4632be794a0bee5ae88;hpb=00fe57d46c18e83674cc17c77643164289abdef5;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/RnHiFiles.lhs b/ghc/compiler/rename/RnHiFiles.lhs index ad4f8c1..6d4f26f 100644 --- a/ghc/compiler/rename/RnHiFiles.lhs +++ b/ghc/compiler/rename/RnHiFiles.lhs @@ -17,19 +17,19 @@ module RnHiFiles ( #include "HsVersions.h" +import DriverUtil ( splitFilename ) import CmdLineOpts ( opt_IgnoreIfacePragmas ) import HscTypes ( ModuleLocation(..), ModIface(..), emptyModIface, - VersionInfo(..), + VersionInfo(..), ImportedModuleInfo, lookupIfaceByModName, ImportVersion, WhetherHasOrphans, IsBootInterface, DeclsMap, GatedDecl, IfaceInsts, IfaceRules, AvailInfo, GenAvailInfo(..), Avails, Deprecations(..) ) import HsSyn ( TyClDecl(..), InstDecl(..), - HsType(..), ConDecl(..), - FixitySig(..), RuleDecl(..), - tyClDeclNames + HsType(..), FixitySig(..), RuleDecl(..), + tyClDeclNames, tyClDeclSysNames ) import RdrHsSyn ( RdrNameTyClDecl, RdrNameInstDecl, RdrNameRuleDecl, extractHsTyRdrNames @@ -37,19 +37,18 @@ import RdrHsSyn ( RdrNameTyClDecl, RdrNameInstDecl, RdrNameRuleDecl, import BasicTypes ( Version, defaultFixity ) import RnEnv import RnMonad -import ParseIface ( parseIface, IfaceStuff(..) ) +import ParseIface ( parseIface ) -import Name ( Name {-instance NamedThing-}, nameOccName, - nameModule, isLocalName, nameIsLocalOrFrom, - NamedThing(..), +import Name ( Name {-instance NamedThing-}, + nameModule, isLocalName, nameIsLocalOrFrom ) -import Name ( mkNameEnv, extendNameEnv ) +import NameEnv import Module ( Module, - moduleName, isModuleInThisPackage, + moduleName, isHomeModule, ModuleName, WhereFrom(..), extendModuleEnv, mkVanillaModule ) -import RdrName ( RdrName, rdrNameOcc ) +import RdrName ( rdrNameOcc ) import SrcLoc ( mkSrcLoc ) import Maybes ( maybeToBool, orElse ) import StringBuffer ( hGetStringBuffer ) @@ -60,6 +59,9 @@ import Lex import FiniteMap import Outputable import Bag +import Config + +import Directory \end{code} @@ -91,7 +93,10 @@ loadInterface doc mod from = tryLoadInterface doc mod from `thenRn` \ (ifaces, maybe_err) -> case maybe_err of Nothing -> returnRn ifaces - Just err -> failWithRn ifaces err + Just err -> failWithRn ifaces (elaborate err) + where + elaborate err = hang (ptext SLIT("failed to load interface for") <+> quotes (ppr mod) <> colon) + 4 err tryLoadInterface :: SDoc -> ModuleName -> WhereFrom -> RnM d (ModIface, Maybe Message) -- Returns (Just err) if an error happened @@ -104,14 +109,16 @@ tryLoadInterface :: SDoc -> ModuleName -> WhereFrom -> RnM d (ModIface, Maybe Me -- (If the load fails, we plug in a vanilla placeholder) tryLoadInterface doc_str mod_name from = getHomeIfaceTableRn `thenRn` \ hit -> + getModuleRn `thenRn` \ this_mod -> getIfacesRn `thenRn` \ ifaces@(Ifaces { iPIT = pit }) -> - + -- CHECK WHETHER WE HAVE IT ALREADY case lookupIfaceByModName hit pit mod_name of { Just iface | case from of ImportByUser -> not (mi_boot iface) ImportByUserSource -> mi_boot iface ImportBySystem -> True + ImportByCmdLine -> True -> returnRn (iface, Nothing) ; -- Already loaded -- The not (mi_boot iface) test checks that the already-loaded -- interface isn't a boot iface. This can conceivably happen, @@ -127,6 +134,7 @@ tryLoadInterface doc_str mod_name from = case (from, mod_info) of (ImportByUser, _) -> False -- Not hi-boot (ImportByUserSource, _) -> True -- hi-boot + (ImportByCmdLine, _) -> False (ImportBySystem, Just (_, is_boot)) -> is_boot (ImportBySystem, Nothing) -> False -- We're importing a module we know absolutely @@ -138,6 +146,9 @@ tryLoadInterface doc_str mod_name from = case (from, mod_info) of (ImportByUserSource, Just (_,False)) -> True other -> False + + home_allowed | ImportByCmdLine <- from = True + | otherwise = False in -- Issue a warning for a redundant {- SOURCE -} import @@ -146,8 +157,16 @@ tryLoadInterface doc_str mod_name from warnCheckRn (not redundant_source_import) (warnRedundantSourceImport mod_name) `thenRn_` + -- Check that we aren't importing ourselves. + -- That only happens in Rename.checkOldIface, + -- which doesn't call tryLoadInterface + warnCheckRn + (not (isHomeModule this_mod) || moduleName this_mod /= mod_name) + (warnSelfImport this_mod) `thenRn_` + -- READ THE MODULE IN - findAndReadIface doc_str mod_name hi_boot_file `thenRn` \ read_result -> + findAndReadIface doc_str mod_name hi_boot_file home_allowed + `thenRn` \ read_result -> case read_result of { Left err -> -- Not found, so add an empty export env to the Ifaces map -- so that we don't look again @@ -174,7 +193,7 @@ tryLoadInterface doc_str mod_name from -- about, it should be from a different package to this one WARN( not (maybeToBool mod_info) && case from of { ImportBySystem -> True; other -> False } && - isModuleInThisPackage mod, + isHomeModule mod, ppr mod ) loadDecls mod (iDecls ifaces) (pi_decls iface) `thenRn` \ (decls_vers, new_decls) -> @@ -196,7 +215,14 @@ tryLoadInterface doc_str mod_name from ImportByUser -> addModDeps mod is_loaded (pi_usages iface) mod_map other -> mod_map mod_map2 = delFromFM mod_map1 mod_name - is_loaded m = maybeToBool (lookupIfaceByModName hit pit m) + + this_mod_name = moduleName this_mod + is_loaded m = m == this_mod_name + || maybeToBool (lookupIfaceByModName hit pit m) + -- We treat the currently-being-compiled module as 'loaded' because + -- even though it isn't yet in the HIT or PIT; otherwise it gets + -- put into iImpModInfo, and then spat out into its own interface + -- file as a dependency -- Now add info about this module to the PIT has_orphans = pi_orphan iface @@ -207,7 +233,7 @@ tryLoadInterface doc_str mod_name from mi_fixities = fix_env, mi_deprecs = deprec_env, mi_usages = [], -- Will be filled in later mi_decls = panic "No mi_decls in PIT", - mi_globals = panic "No mi_globals in PIT" + mi_globals = mkIfaceGlobalRdrEnv avails } new_ifaces = ifaces { iPIT = new_pit, @@ -226,7 +252,7 @@ tryLoadInterface doc_str mod_name from ----------------------------------------------------- addModDeps :: Module - -> (ModuleName -> Bool) -- True for module interfaces + -> (ModuleName -> Bool) -- True for modules that are already loaded -> [ImportVersion a] -> ImportedModuleInfo -> ImportedModuleInfo -- (addModDeps M ivs deps) @@ -239,8 +265,7 @@ addModDeps mod is_loaded new_deps mod_deps -- and in that case, forget about the boot indicator filtered_new_deps :: [(ModuleName, (WhetherHasOrphans, IsBootInterface))] filtered_new_deps - | isModuleInThisPackage mod - = [ (imp_mod, (has_orphans, is_boot)) + | isHomeModule mod = [ (imp_mod, (has_orphans, is_boot)) | (imp_mod, has_orphans, is_boot, _) <- new_deps, not (is_loaded imp_mod) ] @@ -260,13 +285,12 @@ addModDeps mod is_loaded new_deps mod_deps loadExports :: (Version, [ExportItem]) -> RnM d (Version, [(ModuleName,Avails)]) loadExports (vers, items) - = getModuleRn `thenRn` \ this_mod -> - mapRn (loadExport this_mod) items `thenRn` \ avails_s -> + = mapRn loadExport items `thenRn` \ avails_s -> returnRn (vers, avails_s) -loadExport :: Module -> ExportItem -> RnM d (ModuleName, Avails) -loadExport this_mod (mod, entities) +loadExport :: ExportItem -> RnM d (ModuleName, Avails) +loadExport (mod, entities) = mapRn (load_entity mod) entities `thenRn` \ avails -> returnRn (mod, avails) where @@ -292,8 +316,11 @@ loadDecls mod (decls_map, n_slurped) decls returnRn (vers, (decls_map', n_slurped)) loadDecl mod (version_map, decls_map) (version, decl) - = getIfaceDeclBinders mod decl `thenRn` \ full_avail -> + = getTyClDeclBinders mod decl `thenRn` \ (avail, sys_names) -> let + full_avail = case avail of + Avail n -> avail + AvailTC n ns -> AvailTC n (sys_names ++ ns) main_name = availName full_avail new_decls_map = extendNameEnvList decls_map stuff stuff = [ (name, (full_avail, name==main_name, (mod, decl))) @@ -414,51 +441,31 @@ It's used for both source code (from @availsFromDecl@) and interface files It doesn't deal with source-code specific things: @ValD@, @DefD@. They are handled by the sourc-code specific stuff in @RnNames@. + *** See "THE NAMING STORY" in HsDecls **** + + \begin{code} -getIfaceDeclBinders, getTyClDeclBinders +getTyClDeclBinders :: Module -> RdrNameTyClDecl - -> RnM d AvailInfo + -> RnM d (AvailInfo, [Name]) -- The [Name] are the system names -getIfaceDeclBinders mod tycl_decl - = getTyClDeclBinders mod tycl_decl `thenRn` \ avail -> - getSysTyClDeclBinders mod tycl_decl `thenRn` \ extras -> - returnRn (addSysAvails avail extras) - -- 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! - -getTyClDeclBinders mod (IfaceSig var ty prags src_loc) +----------------- +getTyClDeclBinders mod (IfaceSig {tcdName = var, tcdLoc = src_loc}) = newTopBinder mod var src_loc `thenRn` \ var_name -> - returnRn (Avail var_name) + returnRn (Avail var_name, []) getTyClDeclBinders mod tycl_decl - = mapRn do_one (tyClDeclNames tycl_decl) `thenRn` \ (main_name:sub_names) -> - returnRn (AvailTC main_name (main_name : sub_names)) - where - do_one (name,loc) = newTopBinder mod name 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'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} -getSysTyClDeclBinders mod (ClassDecl _ cname _ _ sigs _ names src_loc) - = sequenceRn [newTopBinder mod n src_loc | n <- names] + = new_top_bndrs mod (tyClDeclNames tycl_decl) `thenRn` \ names@(main_name:_) -> + new_top_bndrs mod (tyClDeclSysNames tycl_decl) `thenRn` \ sys_names -> + returnRn (AvailTC main_name names, sys_names) -getSysTyClDeclBinders mod (TyData _ _ _ _ cons _ _ _ _ _) - = sequenceRn [newTopBinder mod wkr_name src_loc | ConDecl _ wkr_name _ _ _ src_loc <- cons] - -getSysTyClDeclBinders mod other_decl - = returnRn [] +----------------- +new_top_bndrs mod names_w_locs + = sequenceRn [newTopBinder mod name loc | (name,loc) <- names_w_locs] \end{code} + %********************************************************* %* * \subsection{Reading an interface file} @@ -469,26 +476,35 @@ getSysTyClDeclBinders mod other_decl findAndReadIface :: SDoc -> ModuleName -> IsBootInterface -- True <=> Look for a .hi-boot file -- False <=> Look for .hi file + -> Bool -- True <=> can read home interface -> RnM d (Either Message (Module, ParsedIface)) -- Nothing <=> file not found, or unreadable, or illegible -- Just x <=> successfully found and parsed -findAndReadIface doc_str mod_name hi_boot_file +findAndReadIface doc_str mod_name hi_boot_file home_allowed = traceRn trace_msg `thenRn_` ioToRnM (findModule mod_name) `thenRn` \ maybe_found -> case maybe_found of Right (Just (wanted_mod,locn)) - -> readIface (mkHiPath hi_boot_file (ml_hi_file locn)) `thenRn` \ read_result -> + -> -- in CmdLineMode, we cannot demand-load home interfaces + -- because the corresponding code won't be loaded, so we + -- check for this here and emit an error message. + if (home_allowed && isHomeModule wanted_mod) + then returnRn (Left (notLoaded wanted_mod)) + else + + mkHiPath hi_boot_file locn `thenRn` \ file -> + readIface file `thenRn` \ read_result -> case read_result of - Left bad -> returnRn (Left bad) - Right iface - -> let read_mod = pi_mod iface - in warnCheckRn (wanted_mod == read_mod) - (hiModuleNameMismatchWarn wanted_mod read_mod) - `thenRn_` - returnRn (Right (wanted_mod, iface)) + Left bad -> returnRn (Left bad) + Right iface + -> let read_mod = pi_mod iface + in warnCheckRn (wanted_mod == read_mod) + (hiModuleNameMismatchWarn wanted_mod + read_mod) `thenRn_` + returnRn (Right (wanted_mod, iface)) -- Can't find it other -> traceRn (ptext SLIT("...not found")) `thenRn_` returnRn (Left (noIfaceErr mod_name hi_boot_file)) @@ -500,9 +516,16 @@ findAndReadIface doc_str mod_name hi_boot_file ppr mod_name <> semi], nest 4 (ptext SLIT("reason:") <+> doc_str)] -mkHiPath hi_boot_file (Just path) - | hi_boot_file = path ++ "-boot-5" - | otherwise = path +mkHiPath hi_boot_file locn + | hi_boot_file = + ioToRnM_no_fail (doesFileExist hi_boot_ver_path) `thenRn` \ b -> + if b then returnRn hi_boot_ver_path + else returnRn hi_boot_path + | otherwise = returnRn hi_path + where (Just hi_path) = ml_hi_file locn + (hi_base, _hi_suf) = splitFilename hi_path + hi_boot_path = hi_base ++ ".hi-boot" + hi_boot_ver_path = hi_base ++ ".hi-boot-" ++ cHscIfaceFileVersion \end{code} @readIface@ tries just the one file. @@ -512,7 +535,8 @@ readIface :: String -> RnM d (Either Message ParsedIface) -- Nothing <=> file not found, or unreadable, or illegible -- Just x <=> successfully found and parsed readIface file_path - = traceRn (ptext SLIT("readIFace") <+> text file_path) `thenRn_` + = --ioToRnM (putStrLn ("reading iface " ++ file_path)) `thenRn_` + traceRn (ptext SLIT("readIFace") <+> text file_path) `thenRn_` ioToRnM (hGetStringBuffer False file_path) `thenRn` \ read_result -> case read_result of { @@ -520,13 +544,8 @@ readIface file_path Right contents -> case parseIface contents init_parser_state of - POk _ (PIface iface) -> returnRn (Right iface) + POk _ iface -> returnRn (Right iface) PFailed err -> bale_out err - parse_result -> bale_out empty - -- 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. } where init_parser_state = PState{ bol = 0#, atbol = 1#, @@ -612,5 +631,11 @@ hiModuleNameMismatchWarn requested_mod read_mod = warnRedundantSourceImport mod_name = ptext SLIT("Unnecessary {- SOURCE -} in the import of module") <+> quotes (ppr mod_name) + +notLoaded mod + = ptext SLIT("Module") <+> quotes (ppr mod) <+> ptext SLIT("is not loaded") + +warnSelfImport mod + = ptext SLIT("Importing my own interface: module") <+> ppr mod \end{code}