[project @ 2000-05-10 08:27:12 by simonmar]
[ghc-hetmet.git] / ghc / compiler / rename / RnIfaces.lhs
index ff3f51c..0b6c368 100644 (file)
@@ -50,7 +50,7 @@ import Name           ( Name {-instance NamedThing-},
                         )
 import Module          ( Module, moduleString, pprModule,
                          mkVanillaModule, pprModuleName,
-                         moduleUserString, moduleName, isLibModule,
+                         moduleUserString, moduleName, isLocalModule,
                          ModuleName, WhereFrom(..),
                        )
 import RdrName         ( RdrName, rdrNameOcc )
@@ -84,60 +84,84 @@ import List ( nub )
 \begin{code}
 loadHomeInterface :: SDoc -> Name -> RnM d Ifaces
 loadHomeInterface doc_str name
-  = loadInterface doc_str (moduleName (nameModule name)) ImportBySystem                `thenRn` \ (_, ifaces) ->
-    returnRn ifaces
+  = loadInterface doc_str (moduleName (nameModule name)) ImportBySystem
 
 loadOrphanModules :: [ModuleName] -> RnM d ()
 loadOrphanModules mods
   | null mods = returnRn ()
-  | otherwise = traceRn (text "Loading orphan modules:" <+> fsep (map pprModuleName mods))     `thenRn_` 
-               mapRn_ load mods        `thenRn_`
+  | otherwise = traceRn (text "Loading orphan modules:" <+> 
+                        fsep (map pprModuleName mods))         `thenRn_` 
+               mapRn_ load mods                                `thenRn_`
                returnRn ()
   where
-    load mod = loadInterface (pprModuleName mod <+> ptext SLIT("is a orphan-instance module")) mod ImportBySystem
+    load mod   = loadInterface (mk_doc mod) mod ImportBySystem
+    mk_doc mod = pprModuleName mod <+> ptext SLIT("is a orphan-instance module")
+          
 
-loadInterface :: SDoc -> ModuleName -> WhereFrom -> RnM d (Module, Ifaces)
-loadInterface doc_str mod_name from
+loadInterface :: SDoc -> ModuleName -> WhereFrom -> RnM d Ifaces
+loadInterface doc mod from 
+  = tryLoadInterface doc mod from      `thenRn` \ (ifaces, maybe_err) ->
+    case maybe_err of
+       Nothing  -> returnRn ifaces
+       Just err -> failWithRn ifaces err
+
+tryLoadInterface :: SDoc -> ModuleName -> WhereFrom -> RnM d (Ifaces, Maybe Message)
+       -- Returns (Just err) if an error happened
+       -- Guarantees to return with iImpModInfo m --> (... Just cts)
+       -- (If the load fails, we plug in a vanilla placeholder
+tryLoadInterface doc_str mod_name from
  = getIfacesRn                         `thenRn` \ ifaces ->
    let
        mod_map  = iImpModInfo ifaces
        mod_info = lookupFM mod_map mod_name
-       below_me = case mod_info of
-                      Nothing -> False
-                      Just (_, _, is_boot, _) -> not is_boot
-   in
-
-       -- Issue a warning for a redundant {- SOURCE -} import
-       -- It's redundant if the moduld is in the iImpModInfo at all,
-       -- because we arrange to read all the ordinary imports before 
-       -- any of the {- SOURCE -} imports
-   warnCheckRn (not (below_me && case from of {ImportByUserSource -> True; other -> False}))
-               (warnRedundantSourceImport mod_name)    `thenRn_`
 
+       hi_boot_file = case from of {
+                        ImportByUser       -> False ;          -- Not hi-boot
+                        ImportByUserSource -> True ;           -- hi-boot
+                        ImportBySystem     -> 
+                      case mod_info of
+                        Just (_, _, is_boot, _) -> is_boot
+
+                        Nothing -> False
+                               -- We're importing a module we know absolutely
+                               -- nothing about, so we assume it's from
+                               -- another package, where we aren't doing 
+                               -- dependency tracking. So it won't be a hi-boot file.
+                      }
+       redundant_source_import 
+         = case (from, mod_info) of 
+               (ImportByUserSource, Just (_,_,False,_)) -> True
+               other                                    -> False
+   in
        -- CHECK WHETHER WE HAVE IT ALREADY
    case mod_info of {
-       Just (_, _, _, Just (load_mod, _))
+       Just (_, _, _, Just _)
                ->      -- We're read it already so don't re-read it
-                   returnRn (load_mod, ifaces) ;
+                   returnRn (ifaces, Nothing) ;
+
+       _ ->
 
-       mod_map_result ->
+       -- Issue a warning for a redundant {- SOURCE -} import
+       -- NB that we arrange to read all the ordinary imports before 
+       -- any of the {- SOURCE -} imports
+   warnCheckRn (not redundant_source_import)
+               (warnRedundantSourceImport mod_name)    `thenRn_`
 
        -- READ THE MODULE IN
-   findAndReadIface doc_str mod_name from below_me
-   `thenRn` \ (hi_boot_read, read_result) ->
+   findAndReadIface doc_str mod_name hi_boot_file   `thenRn` \ read_result ->
    case read_result of {
-       Nothing ->      -- Not found, so add an empty export env to the Ifaces map
+       Left err ->     -- Not found, so add an empty export env to the Ifaces map
                        -- so that we don't look again
           let
                mod         = mkVanillaModule mod_name
-               new_mod_map = addToFM mod_map mod_name (0, False, False, Just (mod, []))
+               new_mod_map = addToFM mod_map mod_name (0, False, False, Just (mod, from, []))
                new_ifaces  = ifaces { iImpModInfo = new_mod_map }
           in
           setIfacesRn new_ifaces               `thenRn_`
-          failWithRn (mod, new_ifaces) (noIfaceErr mod hi_boot_read) ;
+          returnRn (new_ifaces, Just err) ;
 
        -- Found and parsed!
-       Just (mod, iface) ->
+       Right iface ->
 
        -- LOAD IT INTO Ifaces
 
@@ -149,7 +173,14 @@ loadInterface doc_str mod_name from
     getModuleRn                `thenRn` \ this_mod_nm ->
     let
        rd_decls = pi_decls iface
+       mod      = pi_mod   iface
     in
+       -- Sanity check.  If we're system-importing a module we know nothing at all
+       -- about, it should be from a different package to this one
+    WARN( not (maybeToBool mod_info) && 
+         case from of { ImportBySystem -> True; other -> False } &&
+         isLocalModule mod,
+         ppr mod )
     foldlRn (loadDecl mod)           (iDecls ifaces) rd_decls                  `thenRn` \ new_decls ->
     foldlRn (loadInstDecl mod)       (iInsts ifaces) (pi_insts iface)          `thenRn` \ new_insts ->
     (if opt_IgnoreIfacePragmas
@@ -165,12 +196,13 @@ loadInterface doc_str mod_name from
        -- the things the imported module depends on, extracted
        -- from its usage info.
        mod_map1 = case from of
-                       ImportByUser -> addModDeps mod mod_map (pi_usages iface)
+                       ImportByUser -> addModDeps mod (pi_usages iface) mod_map
                        other        -> mod_map
 
        -- Now add info about this module
        mod_map2    = addToFM mod_map1 mod_name mod_details
-       mod_details = (pi_mod iface, pi_orphan iface, hi_boot_read, Just (mod, concat avails_s))
+       cts         = (pi_mod iface, from, concat avails_s)
+       mod_details = (pi_vers iface, pi_orphan iface, hi_boot_file, Just cts)
 
        new_ifaces = ifaces { iImpModInfo = mod_map2,
                              iDecls      = new_decls,
@@ -180,21 +212,28 @@ loadInterface doc_str mod_name from
                              iDeprecs    = new_deprecs }
     in
     setIfacesRn new_ifaces             `thenRn_`
-    returnRn (mod, new_ifaces)
+    returnRn (new_ifaces, Nothing)
     }}
 
-addModDeps :: Module -> ImportedModuleInfo
-          -> [ImportVersion a] -> ImportedModuleInfo
-addModDeps mod mod_deps new_deps
-  = foldr add mod_deps new_deps
+addModDeps :: Module -> [ImportVersion a] 
+          -> ImportedModuleInfo -> ImportedModuleInfo
+-- (addModDeps M ivs deps)
+-- We are importing module M, and M.hi contains 'import' decls given by ivs
+addModDeps mod new_deps mod_deps
+  = foldr add mod_deps filtered_new_deps
   where
-    is_lib = isLibModule mod   -- Don't record dependencies when importing a library module
-    add (imp_mod, version, has_orphans, is_boot, _) deps
-       | is_lib && not has_orphans = deps
-       | otherwise  =  addToFM_C combine deps imp_mod (version, has_orphans, is_boot, Nothing)
-       -- Record dependencies for modules that are
-       --      either are dependent via a non-library module
-       --      or contain orphan rules or instance decls
+       -- Don't record dependencies when importing a module from another package
+       -- Except for its descendents which contain orphans,
+       -- and in that case, forget about the boot indicator
+    filtered_new_deps
+       | isLocalModule mod = [ (imp_mod, (version, has_orphans, is_boot, Nothing))
+                             | (imp_mod, version, has_orphans, is_boot, _) <- new_deps 
+                             ]                       
+       | otherwise         = [ (imp_mod, (version, True, False, Nothing))
+                             | (imp_mod, version, has_orphans, _, _) <- new_deps, 
+                               has_orphans
+                             ]
+    add (imp_mod, dep) deps = addToFM_C combine deps imp_mod dep
 
     combine old@(_, _, old_is_boot, cts) new
        | maybeToBool cts || not old_is_boot = old      -- Keep the old info if it's already loaded
@@ -376,28 +415,32 @@ namesFromIE (IEModuleContents _   ) = []
 %********************************************************
 
 \begin{code}
-checkUpToDate :: ModuleName -> RnMG Bool               -- True <=> no need to recompile
+upToDate  = True
+outOfDate = False
+
+checkUpToDate :: ModuleName -> RnMG Bool       -- True <=> no need to recompile
+       -- When this guy is called, we already know that the
+       -- source code is unchanged from last time
 checkUpToDate mod_name
   = getIfacesRn                                        `thenRn` \ ifaces ->
     findAndReadIface doc_str mod_name 
-                    ImportByUser
-                    (error "checkUpToDate")    `thenRn` \ (_, read_result) ->
+                    False {- Not hi-boot -}    `thenRn` \ read_result ->
 
        -- CHECK WHETHER WE HAVE IT ALREADY
     case read_result of
-       Nothing ->      -- Old interface file not found, so we'd better bail out
-                   traceRn (sep [ptext SLIT("Didnt find old iface"), 
-                                 pprModuleName mod_name])      `thenRn_`
-                   returnRn False
+       Left err ->     -- Old interface file not found, or garbled, so we'd better bail out
+                   traceRn (vcat [ptext SLIT("No old iface") <+> pprModuleName mod_name,
+                                  err])                        `thenRn_`
+                   returnRn outOfDate
 
-       Just (_, iface)
+       Right iface
                ->      -- Found it, so now check it
                    checkModUsage (pi_usages iface)
   where
        -- Only look in current directory, with suffix .hi
     doc_str = sep [ptext SLIT("need usage info from"), pprModuleName mod_name]
 
-checkModUsage [] = returnRn True               -- Yes!  Everything is up to date!
+checkModUsage [] = returnRn upToDate           -- Yes!  Everything is up to date!
 
 checkModUsage ((mod_name, old_mod_vers, _, _, Specifically []) : rest)
        -- If CurrentModule.hi contains 
@@ -408,22 +451,20 @@ checkModUsage ((mod_name, old_mod_vers, _, _, Specifically []) : rest)
   = traceRn (ptext SLIT("Nothing used from:") <+> ppr mod_name)        `thenRn_`
     checkModUsage rest -- This one's ok, so check the rest
 
-checkModUsage ((mod_name, old_mod_vers, _, _, whats_imported) : rest)
-  = loadInterface doc_str mod_name ImportBySystem      `thenRn` \ (mod, ifaces) ->
+checkModUsage ((mod_name, old_mod_vers, _, _, whats_imported)  : rest)
+  = tryLoadInterface doc_str mod_name ImportBySystem   `thenRn` \ (ifaces, maybe_err) ->
+    case maybe_err of {
+       Just err -> traceRn (sep [ptext SLIT("Can't find version number for module"), 
+                            pprModuleName mod_name])           `thenRn_`
+                    returnRn outOfDate ;
+               -- Couldn't find or parse a module mentioned in the
+               -- old interface file.  Don't complain -- it might just be that
+               -- the current module doesn't need that import and it's been deleted
+       Nothing -> 
     let
-       maybe_mod_vers = case lookupFM (iImpModInfo ifaces) mod_name of
-                          Just (version, _, _, Just (_, _)) -> Just version
-                          other                             -> Nothing
+       new_mod_vers = case lookupFM (iImpModInfo ifaces) mod_name of
+                          Just (version, _, _, _) -> version
     in
-    case maybe_mod_vers of {
-       Nothing ->      -- If we can't find a version number for the old module then
-                       -- bail out saying things aren't up to date
-               traceRn (sep [ptext SLIT("Can't find version number for module"), 
-                             pprModuleName mod_name])
-               `thenRn_` returnRn False ;
-
-       Just new_mod_vers ->
-
        -- If the module version hasn't changed, just move on
     if new_mod_vers == old_mod_vers then
        traceRn (sep [ptext SLIT("Module version unchanged:"), pprModuleName mod_name])
@@ -438,7 +479,7 @@ checkModUsage ((mod_name, old_mod_vers, _, _, whats_imported) : rest)
        -- In that case, we must recompile
     case whats_imported of {
       Everything -> traceRn (ptext SLIT("...and I needed the whole module"))   `thenRn_`
-                   returnRn False;                -- Bale out
+                   returnRn outOfDate;            -- Bale out
 
       Specifically old_local_vers ->
 
@@ -448,14 +489,14 @@ checkModUsage ((mod_name, old_mod_vers, _, _, whats_imported) : rest)
        traceRn (ptext 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
+       returnRn outOfDate              -- This one failed, so just bail out now
     }}
   where
     doc_str = sep [ptext SLIT("need version info for"), pprModuleName mod_name]
 
 
 checkEntityUsage mod decls [] 
-  = returnRn True      -- Yes!  All up to date!
+  = returnRn upToDate  -- Yes!  All up to date!
 
 checkEntityUsage mod decls ((occ_name,old_vers) : rest)
   = mkImportedGlobalName mod occ_name  `thenRn` \ name ->
@@ -463,7 +504,7 @@ checkEntityUsage mod decls ((occ_name,old_vers) : rest)
 
        Nothing       ->        -- We used it before, but it ain't there now
                          traceRn (sep [ptext SLIT("No longer exported:"), ppr name])
-                         `thenRn_` returnRn False
+                         `thenRn_` returnRn outOfDate
 
        Just (new_vers,_,_,_)   -- It's there, but is it up to date?
                | new_vers == old_vers
@@ -473,7 +514,7 @@ checkEntityUsage mod decls ((occ_name,old_vers) : rest)
                | otherwise
                        -- Out of date, so bale out
                -> traceRn (sep [ptext SLIT("Out of date:"), ppr name])  `thenRn_`
-                  returnRn False
+                  returnRn outOfDate
 \end{code}
 
 
@@ -557,15 +598,11 @@ that we know just what instances to bring into scope.
 \begin{code}
 getInterfaceExports :: ModuleName -> WhereFrom -> RnMG (Module, Avails)
 getInterfaceExports mod_name from
-  = loadInterface doc_str mod_name from        `thenRn` \ (mod, ifaces) ->
+  = loadInterface doc_str mod_name from        `thenRn` \ ifaces ->
     case lookupFM (iImpModInfo ifaces) mod_name of
-       Nothing -> -- Not there; it must be that the interface file wasn't found;
-                  -- the error will have been reported already.
-                  -- (Actually loadInterface should put the empty export env in there
-                  --  anyway, but this does no harm.)
-                  returnRn (mod, [])
-
-       Just (_, _, _, Just (mod, avails)) -> returnRn (mod, avails)
+       Just (_, _, _, Just (mod, _, avails)) -> returnRn (mod, avails)
+       -- loadInterface always puts something in the map
+       -- even if it's a fake
   where
     doc_str = sep [pprModuleName mod_name, ptext SLIT("is directly imported")]
 \end{code}
@@ -606,12 +643,6 @@ getImportedInstDecls gates
   where
     gate_list      = nameSetToList gates
 
-    load_home gate | isLocallyDefined gate
-                  = returnRn ()
-                  | otherwise
-                  = loadHomeInterface (ppr gate <+> text "is an instance gate") gate   `thenRn_`
-                    returnRn ()
-
 ppr_brief_inst_decl (mod, InstD (InstDecl inst_ty _ _ _ _))
   = case inst_ty of
        HsForAllTy _ _ tau -> ppr tau
@@ -777,10 +808,11 @@ getImportVersions this_mod (ExportEnv _ _ export_all_mods)
                        -- Foo in the module dependency hierarchy.  We want to propagate this
                        -- information.  The Nothing says that we didn't even open the interface
                        -- file but we must still propagate the dependeny info.
+                       -- The module in question must be a local module (in the same package)
                   go_for_it (Specifically [])
 
-               Just (mod, _)                           -- We did open the interface
-                  |  is_lib_module && not has_orphans
+               Just (mod, how_imported, _)
+                  |  is_sys_import && is_lib_module && not has_orphans
                   -> so_far            
           
                   |  is_lib_module                     -- Record the module but not detailed
@@ -796,7 +828,10 @@ getImportVersions this_mod (ExportEnv _ _ export_all_mods)
                                                -- but don't actually *use* anything from Foo
                                                -- In which case record an empty dependency list
                   where
-                    is_lib_module     = isLibModule mod
+                    is_lib_module = not (isLocalModule mod)
+                    is_sys_import = case how_imported of
+                                       ImportBySystem -> True
+                                       other          -> False
             
     in
 
@@ -946,51 +981,36 @@ getDeclSysBinders new_name other_decl
 %*********************************************************
 
 \begin{code}
-findAndReadIface :: SDoc -> ModuleName -> WhereFrom 
-                -> Bool        -- Only relevant for SystemImport
-                               -- True  <=> Look for a .hi file
-                               -- False <=> Look for .hi-boot file unless there's
-                               --           a library .hi file
-                -> RnM d (Bool, Maybe (Module, ParsedIface))
-       -- Bool is True if the interface actually read was a .hi-boot one
+findAndReadIface :: SDoc -> ModuleName 
+                -> IsBootInterface     -- True  <=> Look for a .hi-boot file
+                                       -- False <=> Look for .hi file
+                -> RnM d (Either Message ParsedIface)
        -- Nothing <=> file not found, or unreadable, or illegible
        -- Just x  <=> successfully found and parsed 
 
-findAndReadIface doc_str mod_name from hi_file
+findAndReadIface doc_str mod_name hi_boot_file
   = traceRn trace_msg                  `thenRn_`
       -- we keep two maps for interface files,
       -- one for 'normal' ones, the other for .hi-boot files,
       -- hence the need to signal which kind we're interested.
 
-    getHiMaps                  `thenRn` \ hi_maps ->
+    getHiMaps                  `thenRn` \ (search_path, hi_map, hiboot_map) ->
+    let
+       relevant_map | hi_boot_file = hiboot_map
+                    | otherwise    = hi_map
+    in 
+    case lookupFM relevant_map mod_name of
+       -- Found the file
+      Just fpath -> traceRn (ptext SLIT("...reading from") <+> text fpath)     `thenRn_`
+                   readIface mod_name fpath
        
-    case find_path from hi_maps of
-         -- Found the file
-       (hi_boot, Just (fpath, mod)) -> traceRn (ptext SLIT("...reading from") <+> text fpath)
-                                      `thenRn_`
-                                      readIface mod fpath      `thenRn` \ result ->
-                                      returnRn (hi_boot, result)
-       (hi_boot, Nothing)           -> traceRn (ptext SLIT("...not found"))    `thenRn_`
-                                      returnRn (hi_boot, Nothing)
-  where
-    find_path ImportByUser       (hi_map, _)     = (False, lookupFM hi_map mod_name)
-    find_path ImportByUserSource (_, hiboot_map) = (True,  lookupFM hiboot_map mod_name)
-
-    find_path ImportBySystem     (hi_map, hiboot_map)
-      | hi_file
-      =                -- If the module we seek is in our dependent set, 
-               -- Look for a .hi file
-         (False, lookupFM hi_map mod_name)
-
-      | otherwise
-               -- Check if there's a library module of that name
-               -- If not, look for an hi-boot file
-      = case lookupFM hi_map mod_name of
-          stuff@(Just (_, mod)) | isLibModule mod -> (False, stuff)
-          other                                   -> (True, lookupFM hiboot_map mod_name)
+       -- Can't find it
+      Nothing    -> traceRn (ptext SLIT("...not found"))       `thenRn_`
+                   returnRn (Left (noIfaceErr mod_name hi_boot_file search_path))
 
+  where
     trace_msg = sep [hsep [ptext SLIT("Reading"), 
-                          ppr from,
+                          if hi_boot_file then ptext SLIT("[boot]") else empty,
                           ptext SLIT("interface for"), 
                           pprModuleName mod_name <> semi],
                     nest 4 (ptext SLIT("reason:") <+> doc_str)]
@@ -999,10 +1019,10 @@ findAndReadIface doc_str mod_name from hi_file
 @readIface@ tries just the one file.
 
 \begin{code}
-readIface :: Module -> String -> RnM d (Maybe (Module, ParsedIface))
+readIface :: ModuleName -> String -> RnM d (Either Message ParsedIface)
        -- Nothing <=> file not found, or unreadable, or illegible
        -- Just x  <=> successfully found and parsed 
-readIface the_mod file_path
+readIface wanted_mod file_path
   = ioToRnM (hGetStringBuffer False file_path)       `thenRn` \ read_result ->
     case read_result of
        Right contents    -> 
@@ -1011,21 +1031,23 @@ readIface the_mod file_path
                                context = [],
                                glasgow_exts = 1#,
                                loc = mkSrcLoc (mkFastString file_path) 1 } of
-                 POk _  (PIface mod_nm iface) ->
-                   warnCheckRn (mod_nm == moduleName the_mod)
-                               (hiModuleNameMismatchWarn the_mod mod_nm) `thenRn_`
-                   returnRn (Just (the_mod, iface))
-
-                 PFailed err   -> failWithRn Nothing err 
-                 other         -> failWithRn Nothing (ptext SLIT("Unrecognisable interface file"))
-                               -- 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.
-
-        Left err
-         | isDoesNotExistError err -> returnRn Nothing
-         | otherwise               -> failWithRn Nothing (cannaeReadFile file_path err)
+                 POk _  (PIface iface) ->
+                     warnCheckRn (read_mod == wanted_mod)
+                                 (hiModuleNameMismatchWarn wanted_mod read_mod) `thenRn_`
+                     returnRn (Right iface)
+                   where
+                     read_mod = moduleName (pi_mod 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.
+
+        Left io_err -> bale_out (text (show io_err))
+  where
+    bale_out err = returnRn (Left (badIfaceFile file_path err))
 \end{code}
 
 %*********************************************************
@@ -1035,21 +1057,26 @@ readIface the_mod file_path
 %*********************************************************
 
 \begin{code}
-noIfaceErr filename boot_file
-  = hsep [ptext SLIT("Could not find valid"), boot, 
-         ptext SLIT("interface file"), quotes (pprModule filename)]
+noIfaceErr mod_name boot_file search_path
+  = vcat [ptext SLIT("Could not find interface file for") <+> quotes (pprModuleName mod_name),
+         ptext SLIT("in the directories") <+> 
+                       -- \& to avoid cpp interpreting this string as a
+                       -- comment starter with a pre-4.06 mkdependHS --SDM
+               vcat [ text dir <> text "/\&*" <> pp_suffix suffix 
+                    | (dir,suffix) <- search_path]
+       ]
   where
-    boot | boot_file = ptext SLIT("[boot]")
-        | otherwise = empty
+    pp_suffix suffix | boot_file = ptext SLIT(".hi-boot")
+                    | otherwise = text suffix
 
-cannaeReadFile file err
-  = hcat [ptext SLIT("Failed in reading file: "), 
-          text file, 
-         ptext SLIT("; error="), 
-         text (show err)]
+badIfaceFile file err
+  = vcat [ptext SLIT("Bad interface file:") <+> text file, 
+         nest 4 err]
 
 getDeclErr name
-  = ptext SLIT("Failed to find interface decl for") <+> quotes (ppr name)
+  = vcat [ptext SLIT("Failed to find interface decl for") <+> quotes (ppr name),
+         ptext SLIT("from module") <+> quotes (ppr (nameModule name))
+        ]
 
 getDeclWarn name loc
   = sep [ptext SLIT("Failed to find (optional) interface decl for") <+> quotes (ppr name),
@@ -1067,12 +1094,12 @@ warnRedundantSourceImport mod_name
   = ptext SLIT("Unnecessary {- SOURCE -} in the import of module")
           <+> quotes (pprModuleName mod_name)
 
-hiModuleNameMismatchWarn :: Module -> ModuleName -> Message
-hiModuleNameMismatchWarn requested_mod mod_nm = 
+hiModuleNameMismatchWarn :: ModuleName -> ModuleName  -> Message
+hiModuleNameMismatchWarn requested_mod read_mod = 
     hsep [ ptext SLIT("Something is amiss; requested module name")
-        , pprModule requested_mod
-        , ptext SLIT("differs from name found in the interface file ")
-        , pprModuleName mod_nm
+        , pprModuleName requested_mod
+        , ptext SLIT("differs from name found in the interface file")
+        , pprModuleName read_mod
         ]
 
 \end{code}