2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 \section{Dealing with interface files}
8 readIface, loadInterface, loadHomeInterface,
14 #include "HsVersions.h"
16 import DriverState ( v_GhcMode, isCompManagerMode )
17 import DriverUtil ( replaceFilenameSuffix )
18 import CmdLineOpts ( DynFlag(..) )
19 import Parser ( parseIface )
20 import HscTypes ( ModIface(..), emptyModIface,
21 ExternalPackageState(..), noDependencies,
22 VersionInfo(..), Usage(..),
23 lookupIfaceByModName, RdrExportItem,
25 DeclsMap, GatedDecl, IfaceInsts, IfaceRules, mkIfaceDecls,
26 AvailInfo, GenAvailInfo(..), ParsedIface(..), IfaceDeprecs,
27 Avails, availNames, availName, Deprecations(..)
29 import HsSyn ( TyClDecl(..), InstDecl(..), RuleDecl(..), ConDecl(..),
30 hsTyVarNames, splitHsInstDeclTy, tyClDeclName, tyClDeclNames
32 import RdrHsSyn ( RdrNameTyClDecl, RdrNameInstDecl, RdrNameRuleDecl )
33 import RnHsSyn ( RenamedInstDecl, RenamedRuleDecl, RenamedTyClDecl,
35 import BasicTypes ( Version, FixitySig(..), Fixity(..), FixityDirection(..) )
36 import RnSource ( rnIfaceRuleDecl, rnTyClDecl, rnInstDecl )
37 import RnTypes ( rnHsType )
41 import PrelNames ( gHC_PRIM_Name, gHC_PRIM )
42 import PrelInfo ( ghcPrimExports )
43 import Name ( Name {-instance NamedThing-},
44 nameModule, isInternalName )
49 import Packages ( basePackage )
50 import Module ( Module, ModuleName, ModLocation(ml_hi_file),
51 moduleName, isHomeModule, mkPackageModule,
52 extendModuleEnv, lookupModuleEnvByName
54 import RdrName ( RdrName, mkRdrUnqual, rdrNameOcc, nameRdrName )
55 import OccName ( OccName, mkClassTyConOcc, mkClassDataConOcc,
56 mkSuperDictSelOcc, mkGenOcc1, mkGenOcc2,
57 mkDataConWrapperOcc, mkDataConWorkerOcc )
58 import TyCon ( DataConDetails(..) )
59 import SrcLoc ( noSrcLoc, mkSrcLoc )
60 import Maybes ( maybeToBool )
61 import StringBuffer ( hGetStringBuffer )
62 import FastString ( mkFastString )
63 import ErrUtils ( Message )
64 import Finder ( findModule, findPackageModule,
65 hiBootExt, hiBootVerExt )
68 import ListSetOps ( minusList )
71 import BinIface ( readBinIface )
74 import EXCEPTION as Exception
75 import DATA_IOREF ( readIORef )
81 %*********************************************************
83 \subsection{Loading a new interface file}
85 %*********************************************************
88 loadHomeInterface :: SDoc -> Name -> TcRn m ModIface
89 loadHomeInterface doc_str name
90 = ASSERT2( not (isInternalName name), ppr name <+> parens doc_str )
91 loadInterface doc_str (moduleName (nameModule name)) ImportBySystem
93 loadOrphanModules :: [ModuleName] -> TcRn m ()
94 loadOrphanModules mods
95 | null mods = returnM ()
96 | otherwise = traceRn (text "Loading orphan modules:" <+>
97 fsep (map ppr mods)) `thenM_`
98 mappM_ load mods `thenM_`
101 load mod = loadInterface (mk_doc mod) mod ImportBySystem
102 mk_doc mod = ppr mod <+> ptext SLIT("is a orphan-instance module")
104 loadInterface :: SDoc -> ModuleName -> WhereFrom -> TcRn m ModIface
105 -- Returns Nothing if failed
106 -- If we can't find an interface file, and we are doing ImportForUsage,
107 -- just fail in the monad, and modify anything else
108 -- Otherwise, if we can't find an interface file,
109 -- add an error message to the monad (the first time only)
110 -- and return emptyIface
111 -- The "first time only" part is done by modifying the PackageIfaceTable
112 -- to have an empty entry
114 -- The ImportForUsage case is because when we read the usage information from
115 -- an interface file, we try to read the interfaces it mentions.
116 -- But it's OK to fail; perhaps the module has changed, and that interface
117 -- is no longer used.
119 loadInterface doc_str mod_name from
120 = getHpt `thenM` \ hpt ->
121 getModule `thenM` \ this_mod ->
122 getImports `thenM` \ import_avails ->
123 getEps `thenM` \ eps@(EPS { eps_PIT = pit }) ->
125 -- CHECK WHETHER WE HAVE IT ALREADY
126 case lookupIfaceByModName hpt pit mod_name of {
127 Just iface | case from of
128 ImportByUser src_imp -> src_imp == mi_boot iface
129 ImportForUsage src_imp -> src_imp == mi_boot iface
130 ImportBySystem -> True
131 -> returnM iface ; -- Already loaded
132 -- The not (mi_boot iface) test checks that the already-loaded
133 -- interface isn't a boot iface. This can conceivably happen,
134 -- if the version checking happened to load a boot interface
135 -- before we got to real imports.
139 mod_map = imp_dep_mods import_avails
140 mod_info = lookupModuleEnvByName mod_map mod_name
143 = case (from, mod_info) of
144 (ImportByUser is_boot, _) -> is_boot
145 (ImportForUsage is_boot, _) -> is_boot
146 (ImportBySystem, Just (_, is_boot)) -> is_boot
147 (ImportBySystem, Nothing) -> False
148 -- We're importing a module we know absolutely
149 -- nothing about, so we assume it's from
150 -- another package, where we aren't doing
151 -- dependency tracking. So it won't be a hi-boot file.
153 redundant_source_import
154 = case (from, mod_info) of
155 (ImportByUser True, Just (_, False)) -> True
159 -- Issue a warning for a redundant {- SOURCE -} import
160 -- NB that we arrange to read all the ordinary imports before
161 -- any of the {- SOURCE -} imports
162 warnIf redundant_source_import
163 (warnRedundantSourceImport mod_name) `thenM_`
165 -- Check that we aren't importing ourselves.
166 -- That only happens in Rename.checkOldIface,
167 -- which doesn't call loadInterface
169 (isHomeModule this_mod && moduleName this_mod == mod_name)
170 (warnSelfImport this_mod) `thenM_`
172 -- READ THE MODULE IN
173 findAndReadIface doc_str mod_name hi_boot_file
174 `thenM` \ read_result ->
175 case read_result of {
177 | case from of { ImportForUsage _ -> True ; other -> False }
178 -> failM -- Fail with no error messages
181 -> let -- Not found, so add an empty export env to
182 -- the EPS map so that we don't look again
183 fake_mod = mkPackageModule mod_name
184 fake_iface = emptyModIface fake_mod
185 new_eps = eps { eps_PIT = extendModuleEnv pit fake_mod fake_iface }
187 setEps new_eps `thenM_`
188 addErr (elaborate err) `thenM_`
191 elaborate err = hang (ptext SLIT("Failed to load interface for") <+>
192 quotes (ppr mod_name) <> colon) 4 err
196 Right (mod, iface) ->
200 -- NB: *first* we do loadDecl, so that the provenance of all the locally-defined
201 --- names is done correctly (notably, whether this is an .hi file or .hi-boot file).
202 -- If we do loadExport first the wrong info gets into the cache (unless we
203 -- explicitly tag each export which seems a bit of a bore)
206 -- Sanity check. If we're system-importing a module we know nothing at all
207 -- about, it should be from a different package to this one
208 WARN( not (maybeToBool mod_info) &&
209 case from of { ImportBySystem -> True; other -> False } &&
213 initRn (InterfaceMode mod) $
214 -- Set the module, for use when looking up occurrences
215 -- of names in interface decls and rules
216 loadDecls mod (eps_decls eps) (pi_decls iface) `thenM` \ (decls_vers, new_decls) ->
217 loadRules mod (eps_rules eps) (pi_rules iface) `thenM` \ (rule_vers, new_rules) ->
218 loadInstDecls mod (eps_insts eps) (pi_insts iface) `thenM` \ new_insts ->
219 loadExports (pi_exports iface) `thenM` \ (export_vers, avails) ->
220 loadFixDecls (pi_fixity iface) `thenM` \ fix_env ->
221 loadDeprecs (pi_deprecs iface) `thenM` \ deprec_env ->
223 version = VersionInfo { vers_module = pi_vers iface,
224 vers_exports = export_vers,
225 vers_rules = rule_vers,
226 vers_decls = decls_vers }
228 -- Now add info about this module to the PIT
229 -- Even home modules loaded by this route (which only
230 -- happens in OneShot mode) are put in the PIT
231 has_orphans = pi_orphan iface
232 new_pit = extendModuleEnv pit mod mod_iface
233 mod_iface = ModIface { mi_module = mod, mi_package = pi_pkg iface,
234 mi_version = version,
235 mi_orphan = has_orphans, mi_boot = hi_boot_file,
237 mi_fixities = fix_env, mi_deprecs = deprec_env,
238 mi_deps = pi_deps iface,
239 mi_usages = panic "No mi_usages in PIT",
240 mi_decls = panic "No mi_decls in PIT",
244 new_eps = eps { eps_PIT = new_pit,
245 eps_decls = new_decls,
246 eps_insts = new_insts,
247 eps_rules = new_rules }
249 setEps new_eps `thenM_`
253 -----------------------------------------------------
254 -- Loading the export list
255 -----------------------------------------------------
257 loadExports :: (Version, [RdrExportItem]) -> TcRn m (Version, [(ModuleName,Avails)])
258 loadExports (vers, items)
259 = mappM loadExport items `thenM` \ avails_s ->
260 returnM (vers, avails_s)
263 loadExport :: RdrExportItem -> TcRn m (ModuleName, Avails)
264 loadExport (mod, entities)
265 = mappM (load_entity mod) entities `thenM` \ avails ->
266 returnM (mod, avails)
268 load_entity mod (Avail occ)
269 = newGlobalName2 mod occ `thenM` \ name ->
271 load_entity mod (AvailTC occ occs)
272 = newGlobalName2 mod occ `thenM` \ name ->
273 mappM (newGlobalName2 mod) occs `thenM` \ names ->
274 returnM (AvailTC name names)
277 -----------------------------------------------------
278 -- Loading type/class/value decls
279 -----------------------------------------------------
283 -> [(Version, RdrNameTyClDecl)]
284 -> TcRn m (NameEnv Version, DeclsMap)
285 loadDecls mod (decls_map, n_slurped) decls
286 = foldlM (loadDecl mod) (emptyNameEnv, decls_map) decls `thenM` \ (vers, decls_map') ->
287 returnM (vers, (decls_map', n_slurped))
289 loadDecl mod (version_map, decls_map) (version, decl)
290 = maybeStripPragmas decl `thenM` \ decl ->
291 getTyClDeclBinders mod decl `thenM` \ avail ->
292 getSysBinders mod decl `thenM` \ sys_names ->
294 full_avail = case avail of
296 AvailTC n ns -> AvailTC n (sys_names ++ ns)
297 main_name = availName full_avail
298 new_decls_map = extendNameEnvList decls_map stuff
299 stuff = [ (name, (full_avail, name==main_name, (mod, decl)))
300 | name <- availNames full_avail]
302 new_version_map = extendNameEnv version_map main_name version
304 -- traceRn (text "Loading" <+> ppr full_avail) `thenM_`
305 returnM (new_version_map, new_decls_map)
307 maybeStripPragmas sig@(IfaceSig {tcdIdInfo = idinfo})
308 = doptM Opt_IgnoreInterfacePragmas `thenM` \ ignore_prags ->
310 then returnM sig{ tcdIdInfo = [] }
312 maybeStripPragmas other
316 getTyClDeclBinders :: Module -> RdrNameTyClDecl -> TcRn m AvailInfo
318 getTyClDeclBinders mod (IfaceSig {tcdName = var, tcdLoc = src_loc})
319 = newTopBinder mod var src_loc `thenM` \ var_name ->
320 returnM (Avail var_name)
322 getTyClDeclBinders mod tycl_decl
323 = mapM new (tyClDeclNames tycl_decl) `thenM` \ names@(main_name:_) ->
324 returnM (AvailTC main_name names)
326 new (nm,loc) = newTopBinder mod nm loc
328 --------------------------------
329 -- The "system names" are extra implicit names *bound* by the decl.
331 getSysBinders :: Module -> TyClDecl RdrName -> TcRn m [Name]
332 -- Similar to tyClDeclNames, but returns the "implicit"
333 -- or "system" names of the declaration. And it only works
334 -- on RdrNames, returning OccNames
336 getSysBinders mod (ClassDecl {tcdName = cname, tcdCtxt = cxt, tcdLoc = loc})
337 = mapM (new_sys_bndr mod loc) sys_occs
339 -- C.f. TcClassDcl.tcClassDecl1
340 sys_occs = tc_occ : data_occ : dwrap_occ : dwork_occ : sc_sel_occs
341 cls_occ = rdrNameOcc cname
342 data_occ = mkClassDataConOcc cls_occ
343 dwrap_occ = mkDataConWrapperOcc data_occ
344 dwork_occ = mkDataConWorkerOcc data_occ
345 tc_occ = mkClassTyConOcc cls_occ
346 sc_sel_occs = [mkSuperDictSelOcc n cls_occ | n <- [1..length cxt]]
348 getSysBinders mod (TyData {tcdName = tc_name, tcdCons = DataCons cons,
349 tcdGeneric = Just want_generic, tcdLoc = loc})
350 -- The 'Just' is because this is an interface-file decl
351 -- so it will say whether to derive generic stuff for it or not
352 = mapM (new_sys_bndr mod loc) (gen_occs ++ concatMap mk_con_occs cons)
355 -- c.f. TcTyDecls.tcTyDecl
356 tc_occ = rdrNameOcc tc_name
357 gen_occs | want_generic = [mkGenOcc1 tc_occ, mkGenOcc2 tc_occ]
359 mk_con_occs (ConDecl name _ _ _ _)
360 = [mkDataConWrapperOcc con_occ, mkDataConWorkerOcc con_occ]
362 con_occ = rdrNameOcc name -- The "source name"
364 getSysBinders mod decl = returnM []
366 new_sys_bndr mod loc occ = newTopBinder mod (mkRdrUnqual occ) loc
369 -----------------------------------------------------
370 -- Loading fixity decls
371 -----------------------------------------------------
374 = mappM loadFixDecl decls `thenM` \ to_add ->
375 returnM (mkNameEnv to_add)
377 loadFixDecl (FixitySig rdr_name fixity loc)
378 = lookupGlobalOccRn rdr_name `thenM` \ name ->
379 returnM (name, FixitySig name fixity loc)
382 -----------------------------------------------------
383 -- Loading instance decls
384 -----------------------------------------------------
386 loadInstDecls :: Module -> IfaceInsts
389 loadInstDecls mod (insts, n_slurped) decls
390 = foldlM (loadInstDecl mod) insts decls `thenM` \ insts' ->
391 returnM (insts', n_slurped)
394 loadInstDecl mod insts decl@(InstDecl inst_ty _ _ _ _)
395 = -- Find out what type constructors and classes are "gates" for the
396 -- instance declaration. If all these "gates" are slurped in then
397 -- we should slurp the instance decl too.
399 -- We *don't* want to count names in the context part as gates, though.
401 -- instance Foo a => Baz (T a) where ...
403 -- Here the gates are Baz and T, but *not* Foo.
405 -- HOWEVER: functional dependencies make things more complicated
406 -- class C a b | a->b where ...
407 -- instance C Foo Baz where ...
408 -- Here, the gates are really only C and Foo, *not* Baz.
409 -- That is, if C and Foo are visible, even if Baz isn't, we must
412 -- Rather than take fundeps into account "properly", we just slurp
413 -- if C is visible and *any one* of the Names in the types
414 -- This is a slightly brutal approximation, but most instance decls
415 -- are regular H98 ones and it's perfect for them.
417 -- NOTICE that we rename the type before extracting its free
418 -- variables. The free-variable finder for a renamed HsType
419 -- does the Right Thing for built-in syntax like [] and (,).
420 rnHsType (text "In an interface instance decl") inst_ty `thenM` \ inst_ty' ->
422 (tvs,_,cls,tys) = splitHsInstDeclTy inst_ty'
423 free_tcs = nameSetToList (extractHsTyNames_s tys) `minusList` hsTyVarNames tvs
425 gate_fn vis_fn = vis_fn cls && (null free_tcs || any vis_fn free_tcs)
426 -- The 'vis_fn' returns True for visible names
427 -- Here is the implementation of HOWEVER above
428 -- (Note that we do let the inst decl in if it mentions
429 -- no tycons at all. Hence the null free_ty_names.)
431 -- traceRn ((text "Load instance for" <+> ppr inst_ty') $$ ppr free_tcs) `thenM_`
432 returnM ((gate_fn, (mod, decl)) `consBag` insts)
436 -----------------------------------------------------
438 -----------------------------------------------------
442 -> (Version, [RdrNameRuleDecl])
443 -> RnM (Version, IfaceRules)
444 loadRules mod (rule_bag, n_slurped) (version, rules)
445 = doptM Opt_IgnoreInterfacePragmas `thenM` \ ignore_prags ->
446 if null rules || ignore_prags
447 then returnM (version, (rule_bag, n_slurped))
448 else mappM (loadRule mod) rules `thenM` \ new_rules ->
449 returnM (version, (rule_bag `unionBags`
450 listToBag new_rules, n_slurped))
452 loadRule :: Module -> RdrNameRuleDecl -> RnM (GatedDecl RdrNameRuleDecl)
453 -- "Gate" the rule simply by whether the rule variable is
454 -- needed. We can refine this later.
455 loadRule mod decl@(IfaceRule _ _ _ var _ _ src_loc)
456 = lookupGlobalOccRn var `thenM` \ var_name ->
457 returnM (\vis_fn -> vis_fn var_name, (mod, decl))
460 -----------------------------------------------------
461 -- Loading Deprecations
462 -----------------------------------------------------
464 loadDeprecs :: IfaceDeprecs -> RnM Deprecations
465 loadDeprecs Nothing = returnM NoDeprecs
466 loadDeprecs (Just (Left txt)) = returnM (DeprecAll txt)
467 loadDeprecs (Just (Right prs)) = foldlM loadDeprec emptyNameEnv prs `thenM` \ env ->
468 returnM (DeprecSome env)
469 loadDeprec deprec_env (n, txt)
470 = lookupGlobalOccRn n `thenM` \ name ->
471 -- traceRn (text "Loaded deprecation(s) for" <+> ppr name <> colon <+> ppr txt) `thenM_`
472 returnM (extendNameEnv deprec_env name (name,txt))
476 %********************************************************
478 Load the ParsedIface for the *current* module
479 into a ModIface; then it can be checked
482 %********************************************************
485 loadOldIface :: ParsedIface -> RnM ModIface
488 = loadHomeDecls (pi_decls iface) `thenM` \ (decls_vers, new_decls) ->
489 loadHomeRules (pi_rules iface) `thenM` \ (rule_vers, new_rules) ->
490 loadHomeInsts (pi_insts iface) `thenM` \ new_insts ->
491 mappM loadHomeUsage (pi_usages iface) `thenM` \ usages ->
492 loadExports (pi_exports iface) `thenM` \ (export_vers, avails) ->
493 loadFixDecls (pi_fixity iface) `thenM` \ fix_env ->
494 loadDeprecs (pi_deprecs iface) `thenM` \ deprec_env ->
496 getModeRn `thenM` \ (InterfaceMode mod) ->
497 -- Caller sets the module before the call; also needed
498 -- by the newGlobalName stuff in some of the loadHomeX calls
500 version = VersionInfo { vers_module = pi_vers iface,
501 vers_exports = export_vers,
502 vers_rules = rule_vers,
503 vers_decls = decls_vers }
505 decls = mkIfaceDecls new_decls new_rules new_insts
507 mod_iface = ModIface { mi_module = mod, mi_package = pi_pkg iface,
508 mi_version = version, mi_deps = pi_deps iface,
509 mi_exports = avails, mi_usages = usages,
510 mi_boot = False, mi_orphan = pi_orphan iface,
511 mi_fixities = fix_env, mi_deprecs = deprec_env,
520 loadHomeDecls :: [(Version, RdrNameTyClDecl)]
521 -> RnM (NameEnv Version, [RenamedTyClDecl])
522 loadHomeDecls decls = foldlM loadHomeDecl (emptyNameEnv, []) decls
524 loadHomeDecl :: (NameEnv Version, [RenamedTyClDecl])
525 -> (Version, RdrNameTyClDecl)
526 -> RnM (NameEnv Version, [RenamedTyClDecl])
527 loadHomeDecl (version_map, decls) (version, decl)
528 = rnTyClDecl decl `thenM` \ decl' ->
529 returnM (extendNameEnv version_map (tyClDeclName decl') version, decl':decls)
532 loadHomeRules :: (Version, [RdrNameRuleDecl])
533 -> RnM (Version, [RenamedRuleDecl])
534 loadHomeRules (version, rules)
535 = mappM rnIfaceRuleDecl rules `thenM` \ rules' ->
536 returnM (version, rules')
539 loadHomeInsts :: [RdrNameInstDecl]
540 -> RnM [RenamedInstDecl]
541 loadHomeInsts insts = mappM rnInstDecl insts
544 loadHomeUsage :: Usage OccName -> TcRn m (Usage Name)
546 = mappM rn_imp (usg_entities usage) `thenM` \ entities' ->
547 returnM (usage { usg_entities = entities' })
549 mod_name = usg_name usage
550 rn_imp (occ,vers) = newGlobalName2 mod_name occ `thenM` \ name ->
555 %*********************************************************
557 \subsection{Reading an interface file}
559 %*********************************************************
562 findAndReadIface :: SDoc -> ModuleName
563 -> IsBootInterface -- True <=> Look for a .hi-boot file
564 -- False <=> Look for .hi file
565 -> TcRn m (Either Message (Module, ParsedIface))
566 -- Nothing <=> file not found, or unreadable, or illegible
567 -- Just x <=> successfully found and parsed
569 -- It *doesn't* add an error to the monad, because
570 -- sometimes it's ok to fail... see notes with loadInterface
572 findAndReadIface doc_str mod_name hi_boot_file
573 = traceRn trace_msg `thenM_`
575 -- Check for GHC.Prim, and return its static interface
576 if mod_name == gHC_PRIM_Name
577 then returnM (Right (gHC_PRIM, ghcPrimIface))
580 ioToTcRn (findHiFile mod_name hi_boot_file) `thenM` \ maybe_found ->
584 traceRn (ptext SLIT("...not found")) `thenM_`
585 getDOpts `thenM` \ dflags ->
586 returnM (Left (noIfaceErr dflags mod_name hi_boot_file files))
588 Right (wanted_mod, file_path) ->
589 traceRn (ptext SLIT("readIFace") <+> text file_path) `thenM_`
591 readIface wanted_mod file_path hi_boot_file `thenM` \ read_result ->
592 -- Catch exceptions here
595 Left exn -> returnM (Left (badIfaceFile file_path
596 (text (showException exn))))
598 Right iface -> returnM (Right (wanted_mod, iface))
601 trace_msg = sep [hsep [ptext SLIT("Reading"),
602 if hi_boot_file then ptext SLIT("[boot]") else empty,
603 ptext SLIT("interface for"),
604 ppr mod_name <> semi],
605 nest 4 (ptext SLIT("reason:") <+> doc_str)]
607 findHiFile :: ModuleName -> IsBootInterface
608 -> IO (Either [FilePath] (Module, FilePath))
609 findHiFile mod_name hi_boot_file
611 -- In interactive or --make mode, we are *not allowed* to demand-load
612 -- a home package .hi file. So don't even look for them.
613 -- This helps in the case where you are sitting in eg. ghc/lib/std
614 -- and start up GHCi - it won't complain that all the modules it tries
615 -- to load are found in the home location.
616 ghci_mode <- readIORef v_GhcMode ;
617 let { home_allowed = hi_boot_file ||
618 not (isCompManagerMode ghci_mode) } ;
619 maybe_found <- if home_allowed
620 then findModule mod_name
621 else findPackageModule mod_name ;
623 case maybe_found of {
624 Left files -> return (Left files) ;
626 Right (mod,loc) -> do {
628 -- Return the path to M.hi, M.hi-boot, or M.hi-boot-n as appropriate
629 let { hi_path = ml_hi_file loc ;
630 hi_boot_path = replaceFilenameSuffix hi_path hiBootExt ;
631 hi_boot_ver_path = replaceFilenameSuffix hi_path hiBootVerExt
634 if not hi_boot_file then
635 return (Right (mod, hi_path))
637 hi_ver_exists <- doesFileExist hi_boot_ver_path ;
638 if hi_ver_exists then return (Right (mod, hi_boot_ver_path))
639 else return (Right (mod, hi_boot_path))
643 @readIface@ tries just the one file.
646 readIface :: Module -> String -> IsBootInterface -> TcRn m (Either Exception ParsedIface)
647 -- Nothing <=> file not found, or unreadable, or illegible
648 -- Just x <=> successfully found and parsed
650 readIface mod file_path is_hi_boot_file
651 = do dflags <- getDOpts
652 ioToTcRn (tryMost (read_iface mod dflags file_path is_hi_boot_file))
654 read_iface mod dflags file_path is_hi_boot_file
655 | is_hi_boot_file -- Read ascii
656 = do { buffer <- hGetStringBuffer file_path ;
657 case unP parseIface (mkPState buffer loc dflags) of
658 POk _ iface | wanted_mod_name == actual_mod_name
661 -> throwDyn (ProgramError (showSDoc err))
662 -- 'showSDoc' is a bit yukky
664 wanted_mod_name = moduleName mod
665 actual_mod_name = pi_mod iface
666 err = hiModuleNameMismatchWarn wanted_mod_name actual_mod_name
668 PFailed loc1 loc2 err ->
669 throwDyn (ProgramError (showPFailed loc1 loc2 err))
672 | otherwise -- Read binary
673 = readBinIface file_path
676 loc = mkSrcLoc (mkFastString file_path) 1 0
680 %*********************************************************
682 Wired-in interface for GHC.Prim
684 %*********************************************************
687 ghcPrimIface :: ParsedIface
688 ghcPrimIface = ParsedIface {
689 pi_mod = gHC_PRIM_Name,
690 pi_pkg = basePackage,
691 pi_deps = noDependencies,
695 pi_exports = (1, [(gHC_PRIM_Name, ghcPrimExports)]),
697 pi_fixity = [FixitySig (nameRdrName (idName seqId))
698 (Fixity 0 InfixR) noSrcLoc],
706 %*********************************************************
710 %*********************************************************
713 badIfaceFile file err
714 = vcat [ptext SLIT("Bad interface file:") <+> text file,
717 hiModuleNameMismatchWarn :: ModuleName -> ModuleName -> Message
718 hiModuleNameMismatchWarn requested_mod read_mod =
719 hsep [ ptext SLIT("Something is amiss; requested module name")
721 , ptext SLIT("differs from name found in the interface file")
725 warnRedundantSourceImport mod_name
726 = ptext SLIT("Unnecessary {- SOURCE -} in the import of module")
727 <+> quotes (ppr mod_name)
730 = ptext SLIT("Importing my own interface: module") <+> ppr mod