= return ()
| otherwise
= do { mod <- getModule
+ ; traceIf (text "checkWiredInTyCon" <+> ppr tc_name $$ ppr mod)
; ASSERT( isExternalName tc_name )
when (mod /= nameModule tc_name)
(initIfaceTcRn (loadWiredInHomeIface tc_name))
-- interface; it will call the Finder again, but the ModLocation will be
-- cached from the first search.
= do { hsc_env <- getTopEnv
- -- ToDo: findImportedModule should return a list of interfaces
; res <- liftIO $ findImportedModule hsc_env mod maybe_pkg
; case res of
- Found _ mod -> fmap (fmap (:[]))
- . initIfaceTcRn
- $ loadInterface doc mod (ImportByUser want_boot)
+ FoundModule (FoundHs { fr_mod = mod })
+ -> fmap (fmap (:[]))
+ . initIfaceTcRn
+ $ loadInterface doc mod (ImportByUser want_boot)
+ FoundSigs mods _backing
+ -> initIfaceTcRn $ do
+ ms <- forM mods $ \(FoundHs { fr_mod = mod }) ->
+ loadInterface doc mod (ImportByUser want_boot)
+ return (sequence ms)
err -> return (Failed (cannotFindInterface (hsc_dflags hsc_env) mod err)) }
-- | Load interface directly for a fully qualified 'Module'. (This is a fairly
-- | An 'IfM' function to load the home interface for a wired-in thing,
-- so that we're sure that we see its instance declarations and rules
--- See Note [Loading instances for wired-in things] in TcIface
+-- See Note [Loading instances for wired-in things]
loadWiredInHomeIface :: Name -> IfM lcl ()
loadWiredInHomeIface name
= ASSERT( isWiredInName name )
loadInterface doc_str mod from
= do { -- Read the state
(eps,hpt) <- getEpsAndHpt
+ ; gbl_env <- getGblEnv
; traceIf (text "Considering whether to load" <+> ppr mod <+> ppr from)
-- READ THE MODULE IN
; read_result <- case (wantHiBootFile dflags eps mod from) of
Failed err -> return (Failed err)
- Succeeded hi_boot_file -> findAndReadIface doc_str mod hi_boot_file
+ Succeeded hi_boot_file ->
+ -- Stoutly warn against an EPS-updating import
+ -- of one's own boot file! (one-shot only)
+ --See Note [Do not update EPS with your own hi-boot]
+ -- in MkIface.
+ WARN( hi_boot_file &&
+ fmap fst (if_rec_types gbl_env) == Just mod,
+ ppr mod )
+ findAndReadIface doc_str mod hi_boot_file
; case read_result of {
Failed err -> do
{ let fake_iface = emptyModIface mod
; updateEps_ $ \ eps ->
if elemModuleEnv mod (eps_PIT eps) then eps else
- case from of -- See Note [Care with plugin imports]
- ImportByPlugin -> eps {
- eps_PIT = extendModuleEnv (eps_PIT eps) mod final_iface,
- eps_PTE = addDeclsToPTE (eps_PTE eps) new_eps_decls}
- _ -> eps {
+ eps {
eps_PIT = extendModuleEnv (eps_PIT eps) mod final_iface,
eps_PTE = addDeclsToPTE (eps_PTE eps) new_eps_decls,
eps_rule_base = extendRuleBaseList (eps_rule_base eps)
2 (ptext (sLit "but") <+> quotes (ppr mod) <+> ptext (sLit "is from package")
<+> quotes (ppr (modulePackageKey mod)))
-{-
-Note [Care with plugin imports]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-When dynamically loading a plugin (via loadPluginInterface) we
-populate the same External Package State (EPS), even though plugin
-modules are to link with the compiler itself, and not with the
-compiled program. That's fine: mostly the EPS is just a cache for
-the interace files on disk.
-
-But it's NOT ok for the RULES or instance environment. We do not want
-to fire a RULE from the plugin on the code we are compiling, otherwise
-the code we are compiling will have a reference to a RHS of the rule
-that exists only in the compiler! This actually happened to Daniel,
-via a RULE arising from a specialisation of (^) in the plugin.
-
-Solution: when loading plugins, do not extend the rule and instance
-environments. We are only interested in the type environment, so that
-we can check that the plugin exports a function with the type that the
-compiler expects.
--}
-
-----------------------------------------------------
-- Loading type/class/value decls
-- We pass the full Module name here, replete with
-> [(Fingerprint, IfaceDecl)]
-> IfL [(Name,TyThing)]
loadDecls ignore_prags ver_decls
- = do { mod <- getIfModule
- ; thingss <- mapM (loadDecl ignore_prags mod) ver_decls
+ = do { thingss <- mapM (loadDecl ignore_prags) ver_decls
; return (concat thingss)
}
loadDecl :: Bool -- Don't load pragmas into the decl pool
- -> Module
-> (Fingerprint, IfaceDecl)
-> IfL [(Name,TyThing)] -- The list can be poked eagerly, but the
-- TyThings are forkM'd thunks
-loadDecl ignore_prags mod (_version, decl)
+loadDecl ignore_prags (_version, decl)
= do { -- Populate the name cache with final versions of all
-- the names associated with the decl
- main_name <- lookupOrig mod (ifName decl)
+ main_name <- lookupIfaceTop (ifName decl)
-- Typecheck the thing, lazily
-- NB. Firstly, the laziness is there in case we never need the
Nothing ->
pprPanic "loadDecl" (ppr main_name <+> ppr n $$ ppr (decl))
- ; implicit_names <- mapM (lookupOrig mod) (ifaceDeclImplicitBndrs decl)
+ ; implicit_names <- mapM lookupIfaceTop (ifaceDeclImplicitBndrs decl)
-- ; traceIf (text "Loading decl for " <> ppr main_name $$ ppr implicit_names)
; return $ (main_name, thing) :
hsc_env <- getTopEnv
mb_found <- liftIO (findExactModule hsc_env mod)
case mb_found of
- Found loc mod -> do
+ FoundExact loc mod -> do
-- Found file, so read it
let file_path = addBootSuffix_maybe hi_boot_file
traceIf (ptext (sLit "...not found"))
dflags <- getDynFlags
return (Failed (cannotFindInterface dflags
- (moduleName mod) err))
+ (moduleName mod)
+ (convFindExactResult err)))
where read_file file_path = do
traceIf (ptext (sLit "readIFace") <+> text file_path)
read_result <- readIface mod file_path
-- Show a ModIface
pprModIface iface
= vcat [ ptext (sLit "interface")
- <+> ppr (mi_module iface) <+> pp_boot
+ <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface)
<+> (if mi_orphan iface then ptext (sLit "[orphan module]") else Outputable.empty)
<+> (if mi_finsts iface then ptext (sLit "[family instance module]") else Outputable.empty)
<+> (if mi_hpc iface then ptext (sLit "[hpc]") else Outputable.empty)
, pprTrustPkg (mi_trust_pkg iface)
]
where
- pp_boot | mi_boot iface = ptext (sLit "[boot]")
- | otherwise = Outputable.empty
+ pp_hsc_src HsBootFile = ptext (sLit "[boot]")
+ pp_hsc_src HsigFile = ptext (sLit "[hsig]")
+ pp_hsc_src HsSrcFile = Outputable.empty
{-
When printing export lists, we print like this: