X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRnHiFiles.lhs;h=d9fec6eb5b3e65aebbdfd6c4f47a1e2fd8dbd778;hb=caac75c6a454396dadff0323162ed14adb4893cd;hp=29a64498ab8e5cacfde94b7f4558f686ab5d64bd;hpb=96cf57e3ca14b3d9e6654a7780ea0b0ea4f5c0e8;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/RnHiFiles.lhs b/ghc/compiler/rename/RnHiFiles.lhs index 29a6449..d9fec6e 100644 --- a/ghc/compiler/rename/RnHiFiles.lhs +++ b/ghc/compiler/rename/RnHiFiles.lhs @@ -11,57 +11,63 @@ module RnHiFiles ( lookupFixityRn, - getTyClDeclBinders, - removeContext -- removeContext probably belongs somewhere else + getTyClDeclBinders ) where #include "HsVersions.h" +import DriverState ( v_GhcMode, isCompManagerMode ) +import DriverUtil ( splitFilename ) import CmdLineOpts ( opt_IgnoreIfacePragmas ) import HscTypes ( ModuleLocation(..), ModIface(..), emptyModIface, - VersionInfo(..), - lookupIfaceByModName, + VersionInfo(..), ImportedModuleInfo, + lookupIfaceByModName, RdrExportItem, ImportVersion, WhetherHasOrphans, IsBootInterface, DeclsMap, GatedDecl, IfaceInsts, IfaceRules, AvailInfo, GenAvailInfo(..), Avails, Deprecations(..) ) -import HsSyn ( TyClDecl(..), InstDecl(..), - HsType(..), FixitySig(..), RuleDecl(..), - tyClDeclNames, tyClDeclSysNames - ) -import RdrHsSyn ( RdrNameTyClDecl, RdrNameInstDecl, RdrNameRuleDecl, - extractHsTyRdrNames +import HsSyn ( TyClDecl(..), InstDecl(..), RuleDecl(..), + tyClDeclNames, tyClDeclSysNames, hsTyVarNames, + getHsInstHead, ) +import RdrHsSyn ( RdrNameTyClDecl, RdrNameInstDecl, RdrNameRuleDecl ) +import RnHsSyn ( extractHsTyNames_s ) import BasicTypes ( Version, defaultFixity ) +import RnTypes ( rnHsType ) import RnEnv import RnMonad -import ParseIface ( parseIface, IfaceStuff(..) ) +import ParseIface ( parseIface ) -import Name ( Name {-instance NamedThing-}, nameOccName, - nameModule, isLocalName, nameIsLocalOrFrom, - NamedThing(..), +import PrelNames ( gHC_PRIM_Name, gHC_PRIM ) +import Name ( Name {-instance NamedThing-}, + nameModule, isLocalName, nameIsLocalOrFrom ) -import Name ( mkNameEnv, extendNameEnv ) -import Module ( Module, - moduleName, isHomeModule, - ModuleName, WhereFrom(..), - extendModuleEnv, mkVanillaModule - ) -import RdrName ( RdrName, rdrNameOcc ) +import NameEnv +import NameSet +import Module +import RdrName ( rdrNameOcc ) import SrcLoc ( mkSrcLoc ) import Maybes ( maybeToBool, orElse ) import StringBuffer ( hGetStringBuffer ) import FastString ( mkFastString ) import ErrUtils ( Message ) -import Finder ( findModule ) +import Finder ( findModule, findPackageModule ) import Lex import FiniteMap +import ListSetOps ( minusList ) import Outputable import Bag +import BinIface ( {- just instances -} ) +import qualified Binary +import Panic import Config +import IOExts +import Exception ( tryAllIO, Exception(DynException) ) +import Dynamic ( fromDynamic ) import Directory +import List ( isSuffixOf ) \end{code} @@ -93,7 +99,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 @@ -106,8 +115,9 @@ 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 @@ -148,8 +158,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 + `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 @@ -198,18 +216,26 @@ 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 new_pit = extendModuleEnv pit mod mod_iface - mod_iface = ModIface { mi_module = mod, mi_version = version, + mod_iface = ModIface { mi_module = mod, mi_package = pi_pkg iface, + mi_version = version, mi_orphan = has_orphans, mi_boot = hi_boot_file, mi_exports = avails, 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 = Nothing } new_ifaces = ifaces { iPIT = new_pit, @@ -228,7 +254,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) @@ -241,8 +267,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 - | isHomeModule 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,15 +285,14 @@ addModDeps mod is_loaded new_deps mod_deps -- Loading the export list ----------------------------------------------------- -loadExports :: (Version, [ExportItem]) -> RnM d (Version, [(ModuleName,Avails)]) +loadExports :: (Version, [RdrExportItem]) -> 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 :: RdrExportItem -> RnM d (ModuleName, Avails) +loadExport (mod, entities) = mapRn (load_entity mod) entities `thenRn` \ avails -> returnRn (mod, avails) where @@ -294,8 +318,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))) @@ -303,6 +330,7 @@ loadDecl mod (version_map, decls_map) (version, decl) new_version_map = extendNameEnv version_map main_name version in + traceRn (text "Loading" <+> ppr full_avail) `thenRn_` returnRn (new_version_map, new_decls_map) ----------------------------------------------------- @@ -315,7 +343,7 @@ loadFixDecls mod decls where mod_name = moduleName mod -loadFixDecl mod_name sig@(FixitySig rdr_name fixity loc) +loadFixDecl mod_name (rdr_name, fixity) = newGlobalName mod_name (rdrNameOcc rdr_name) `thenRn` \ name -> returnRn (name, fixity) @@ -344,23 +372,36 @@ loadInstDecl mod insts decl@(InstDecl inst_ty _ _ _ _) -- instance Foo a => Baz (T a) where ... -- -- Here the gates are Baz and T, but *not* Foo. + -- + -- HOWEVER: functional dependencies make things more complicated + -- class C a b | a->b where ... + -- instance C Foo Baz where ... + -- Here, the gates are really only C and Foo, *not* Baz. + -- That is, if C and Foo are visible, even if Baz isn't, we must + -- slurp the decl. + -- + -- Rather than take fundeps into account "properly", we just slurp + -- if C is visible and *any one* of the Names in the types + -- This is a slightly brutal approximation, but most instance decls + -- are regular H98 ones and it's perfect for them. + -- + -- NOTICE that we rename the type before extracting its free + -- variables. The free-variable finder for a renamed HsType + -- does the Right Thing for built-in syntax like [] and (,). + initIfaceRnMS mod ( + rnHsType (text "In an interface instance decl") inst_ty + ) `thenRn` \ inst_ty' -> let - munged_inst_ty = removeContext inst_ty - free_names = extractHsTyRdrNames munged_inst_ty - in - mapRn lookupIfaceName free_names `thenRn` \ gate_names -> - returnRn ((gate_names, (mod, decl)) `consBag` insts) + (tvs,(cls,tys)) = getHsInstHead inst_ty' + free_tcs = nameSetToList (extractHsTyNames_s tys) `minusList` hsTyVarNames tvs + gate_fn vis_fn = vis_fn cls && (null free_tcs || any vis_fn free_tcs) + -- Here is the implementation of HOWEVER above + -- (Note that we do let the inst decl in if it mentions + -- no tycons at all. Hence the null free_ty_names.) + in + returnRn ((gate_fn, (mod, decl)) `consBag` insts) --- In interface files, the instance decls now look like --- forall a. Foo a -> Baz (T a) --- so we have to strip off function argument types as well --- as the bit before the '=>' (which is always empty in interface files) -removeContext (HsForAllTy tvs cxt ty) = HsForAllTy tvs [] (removeFuns ty) -removeContext ty = removeFuns ty - -removeFuns (HsFunTy _ ty) = removeFuns ty -removeFuns ty = ty ----------------------------------------------------- @@ -381,9 +422,9 @@ loadRules mod (rule_bag, n_slurped) (version, rules) loadRule :: Module -> RdrNameRuleDecl -> RnM d (GatedDecl RdrNameRuleDecl) -- "Gate" the rule simply by whether the rule variable is -- needed. We can refine this later. -loadRule mod decl@(IfaceRule _ _ var _ _ src_loc) +loadRule mod decl@(IfaceRule _ _ _ var _ _ src_loc) = lookupIfaceName var `thenRn` \ var_name -> - returnRn ([var_name], (mod, decl)) + returnRn (\vis_fn -> vis_fn var_name, (mod, decl)) ----------------------------------------------------- @@ -416,30 +457,24 @@ 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 ----------------- -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 - = new_top_bndrs mod (tyClDeclNames tycl_decl) `thenRn` \ (main_name:sub_names) -> - returnRn (AvailTC main_name (main_name : sub_names)) - ------------------ -getIfaceDeclBinders mod (IfaceSig var ty prags src_loc) - = newTopBinder mod var src_loc `thenRn` \ var_name -> - returnRn (Avail var_name) - -getIfaceDeclBinders mod tycl_decl - = new_top_bndrs mod (tyClDeclNames tycl_decl) `thenRn` \ (main_name:sub_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 (main_name : (sys_names ++ sub_names))) + returnRn (AvailTC main_name names, sys_names) ----------------- new_top_bndrs mod names_w_locs @@ -464,7 +499,24 @@ findAndReadIface :: SDoc -> ModuleName findAndReadIface doc_str mod_name hi_boot_file = traceRn trace_msg `thenRn_` - ioToRnM (findModule mod_name) `thenRn` \ maybe_found -> + -- Check for GHC.Prim, and return its static interface + if mod_name == gHC_PRIM_Name + then returnRn (Right (gHC_PRIM, ghcPrimIface)) + else + + -- In interactive or --make mode, we are *not allowed* to demand-load + -- a home package .hi file. So don't even look for them. + -- This helps in the case where you are sitting in eg. ghc/lib/std + -- and start up GHCi - it won't complain that all the modules it tries + -- to load are found in the home location. + ioToRnM_no_fail (readIORef v_GhcMode) `thenRn` \ mode -> + let home_allowed = hi_boot_file || not (isCompManagerMode mode) + in + + ioToRnM (if home_allowed + then findModule mod_name + else findPackageModule mod_name) `thenRn` \ maybe_found -> + case maybe_found of Right (Just (wanted_mod,locn)) @@ -472,11 +524,14 @@ findAndReadIface doc_str mod_name hi_boot_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_` + Right iface -> -- check that the module names agree + let read_mod_name = pi_mod iface + wanted_mod_name = moduleName wanted_mod + in + checkRn + (wanted_mod_name == read_mod_name) + (hiModuleNameMismatchWarn wanted_mod_name read_mod_name) + `thenRn_` returnRn (Right (wanted_mod, iface)) -- Can't find it other -> traceRn (ptext SLIT("...not found")) `thenRn_` @@ -495,9 +550,10 @@ mkHiPath hi_boot_file locn 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_boot_path = hi_path ++ "-boot" - hi_boot_ver_path = hi_path ++ "-boot-" ++ cHscIfaceFileVersion + where 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. @@ -507,40 +563,50 @@ 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_` + + let hi_boot_ver = "hi-boot-" ++ cHscIfaceFileVersion in + if ".hi-boot" `isSuffixOf` file_path + || hi_boot_ver `isSuffixOf` file_path then - ioToRnM (hGetStringBuffer False file_path) `thenRn` \ read_result -> - case read_result of { - Left io_error -> bale_out (text (show io_error)) ; + ioToRnM (hGetStringBuffer False file_path) `thenRn` \ read_result -> + case read_result of { + Left io_error -> bale_out (text (show io_error)); Right contents -> - case parseIface contents init_parser_state of - POk _ (PIface iface) -> returnRn (Right iface) + case parseIface contents (mkPState loc exts) of { + 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. - } + }} + + else + ioToRnM_no_fail (tryAllIO (Binary.getBinFileWithDict file_path)) + `thenRn` \ either_iface -> + + case either_iface of + Right iface -> returnRn (Right iface) + Left (DynException d) | Just e <- fromDynamic d + -> bale_out (text (show (e :: GhcException))) + + Left err -> bale_out (text (show err)) + where - init_parser_state = PState{ bol = 0#, atbol = 1#, - context = [], - glasgow_exts = 1#, - loc = mkSrcLoc (mkFastString file_path) 1 } + exts = ExtFlags {glasgowExtsEF = True, + parrEF = True} + loc = mkSrcLoc (mkFastString file_path) 1 bale_out err = returnRn (Left (badIfaceFile file_path err)) \end{code} - %********************************************************* %* * \subsection{Looking up fixities} %* * %********************************************************* -@lookupFixityRn@ has to be in RnIfaces (or RnHiFiles) because -it calls @loadHomeInterface@. +@lookupFixityRn@ has to be in RnIfaces (or RnHiFiles), instead of +its obvious home in RnEnv, because it calls @loadHomeInterface@. lookupFixity is a bit strange. @@ -565,13 +631,19 @@ lookupFixityRn name returnRn (lookupLocalFixity local_fix_env name) else -- It's imported - -- 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. + -- 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', thus; + -- module CurrentModule where + -- import A( f ) + -- module A( f ) where + -- import B( f ) + -- 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` \ iface -> returnRn (lookupNameEnv (mi_fixities iface) name `orElse` defaultFixity) where @@ -596,10 +668,10 @@ badIfaceFile file err = vcat [ptext SLIT("Bad interface file:") <+> text file, nest 4 err] -hiModuleNameMismatchWarn :: Module -> Module -> Message +hiModuleNameMismatchWarn :: ModuleName -> ModuleName -> Message hiModuleNameMismatchWarn requested_mod read_mod = hsep [ ptext SLIT("Something is amiss; requested module name") - , ppr (moduleName requested_mod) + , ppr requested_mod , ptext SLIT("differs from name found in the interface file") , ppr read_mod ] @@ -607,5 +679,7 @@ hiModuleNameMismatchWarn requested_mod read_mod = warnRedundantSourceImport mod_name = ptext SLIT("Unnecessary {- SOURCE -} in the import of module") <+> quotes (ppr mod_name) -\end{code} +warnSelfImport mod + = ptext SLIT("Importing my own interface: module") <+> ppr mod +\end{code}