[project @ 2003-01-08 15:28:04 by simonmar]
authorsimonmar <unknown>
Wed, 8 Jan 2003 15:28:05 +0000 (15:28 +0000)
committersimonmar <unknown>
Wed, 8 Jan 2003 15:28:05 +0000 (15:28 +0000)
Improve missing-module error messages.  eg.

hello2.hs:1:
    Failed to load interface for `Foo':
        Could not find interface file for `Foo'
        (use -v to see a list of the files searched for)

and if we add the -v flag:

hello2.hs:1:
    Failed to load interface for `Foo':
        Could not find interface file for `Foo'
        locations searched:
            Foo.hi
            Foo.hi-boot-6
            Foo.hi-boot
            /home/simonmar/builds/i386-unknown-linux/libraries/haskell-src/Foo.hi
            /home/simonmar/builds/i386-unknown-linux/libraries/haskell98/Foo.hi
            /home/simonmar/builds/i386-unknown-linux/libraries/readline/Foo.hi
            /home/simonmar/builds/i386-unknown-linux/libraries/unix/Foo.hi
            /home/simonmar/builds/i386-unknown-linux/libraries/network/Foo.hi
            /home/simonmar/builds/i386-unknown-linux/libraries/base/Foo.hi

ghc/compiler/compMan/CompManager.lhs
ghc/compiler/main/DriverMkDepend.hs
ghc/compiler/main/Finder.lhs
ghc/compiler/rename/RnEnv.lhs
ghc/compiler/rename/RnHiFiles.lhs

index 044b1d0..47afe26 100644 (file)
@@ -1162,11 +1162,11 @@ downsweep roots old_summaries
         getSummary (currentMod,nm)
            = do found <- findModule nm
                case found of
-                  Just (mod, location) -> do
+                  Right (mod, location) -> do
                        let old_summary = findModInSummaries old_summaries mod
                        summarise mod location old_summary
 
-                  Nothing -> 
+                  Left _ -> 
                        throwDyn (CmdLineError 
                                    ("can't find module `" 
                                      ++ showSDoc (ppr nm) ++ "' (while processing " 
index c6d3290..5a0cd62 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverMkDepend.hs,v 1.26 2002/11/08 12:52:51 simonmar Exp $
+-- $Id: DriverMkDepend.hs,v 1.27 2003/01/08 15:28:05 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -173,7 +173,7 @@ findDependency is_source src imp = do
       else do
        r <- findModule imp
        case r of 
-          Just (mod,loc)
+          Right (mod,loc)
                -- not in this package: we don't need a dependency
                | not (isHomeModule mod) && not include_prelude
                -> return Nothing
@@ -198,6 +198,6 @@ findDependency is_source src imp = do
                           then return (Just (boot_hi_file, not is_source))
                           else return (Just (hi_file, not is_source))
 
-          Nothing -> throwDyn (ProgramError 
+          Left _ -> throwDyn (ProgramError 
                (src ++ ": " ++ "can't locate import `" ++ imp_mod ++ "'" ++
                 if is_source then " (SOURCE import)" else ""))
index 8054e91..dc7e190 100644 (file)
@@ -7,8 +7,11 @@
 module Finder (
     flushFinderCache,  -- :: IO ()
 
-    findModule,                -- :: ModuleName -> IO (Maybe (Module, ModLocation))
-    findPackageModule,  -- :: ModuleName -> IO (Maybe (Module, ModLocation))
+    findModule,                -- :: ModuleName 
+                       --   -> IO (Either [FilePath] (Module, ModLocation))
+
+    findPackageModule,  -- :: ModuleName
+                       --   -> IO (Either [FilePath] (Module, ModLocation))
 
     mkHomeModLocation, -- :: ModuleName -> String -> FilePath 
                        --      -> IO ModLocation
@@ -24,7 +27,6 @@ module Finder (
 
 import Module
 import UniqFM          ( filterUFM )
-import Packages                ( PackageConfig(..) )
 import HscTypes                ( Linkable(..), Unlinked(..) )
 import DriverState
 import DriverUtil      ( split_longest_prefix, splitFilename3 )
@@ -86,28 +88,32 @@ lookupFinderCache mod_name = do
 -- The ModLocation contains the names of all the files associated with
 -- that module: its source file, .hi file, object file, etc.
 
-findModule :: ModuleName -> IO (Maybe (Module, ModLocation))
+findModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
 findModule name = do
   r <- lookupFinderCache name
   case r of
-   Just result -> return (Just result)
+   Just result -> return (Right result)
    Nothing -> do  
        j <- maybeHomeModule name
        case j of
-        Just home_module -> return (Just home_module)
-        Nothing          -> findPackageMod name
-
-findPackageModule :: ModuleName -> IO (Maybe (Module, ModLocation))
+        Right home_module -> return (Right home_module)
+        Left home_files   -> do
+           r <- findPackageMod name
+           case r of
+               Right pkg_module -> return (Right pkg_module)
+               Left pkg_files   -> return (Left (home_files ++ pkg_files))
+
+findPackageModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
 findPackageModule name = do
   r <- lookupFinderCache name
   case r of
-   Just result -> return (Just result)
+   Just result -> return (Right result)
    Nothing     -> findPackageMod name
 
 hiBootExt = "hi-boot"
 hiBootVerExt = "hi-boot-" ++ cHscIfaceFileVersion
 
-maybeHomeModule :: ModuleName -> IO (Maybe (Module, ModLocation))
+maybeHomeModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
 maybeHomeModule mod_name = do
    home_path <- readIORef v_Import_paths
    hisuf     <- readIORef v_Hi_suf
@@ -142,7 +148,7 @@ maybeHomeModule mod_name = do
 -- -----------------------------------------------------------------------------
 -- Looking for a package module
 
-findPackageMod :: ModuleName -> IO (Maybe (Module, ModLocation))
+findPackageMod :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
 findPackageMod mod_name = do
   mode     <- readIORef v_GhcMode
   imp_dirs <- getPackageImportPath -- including the 'auto' ones
@@ -185,25 +191,28 @@ searchPathExts
        String -> String -> String -> IO (Module, ModLocation)  -- action
        )
      ] 
-  -> IO (Maybe (Module, ModLocation))
+  -> IO (Either [FilePath] (Module, ModLocation))
 
-searchPathExts path mod_name exts = search path
+searchPathExts path mod_name exts = search to_search
   where
     mod_str = moduleNameUserString mod_name
     basename = map (\c -> if c == '.' then '/' else c) mod_str
 
-    search [] = return Nothing
-    search (p:ps) = loop exts
-      where    
-       base | p == "."  = basename
-            | otherwise = p ++ '/':basename
-
-       loop [] = search ps
-       loop ((ext,fn):exts) = do
-           let file = base ++ '.':ext
-           b <- doesFileExist file
-           if b then Just `liftM` fn p basename ext
-                else loop exts
+    to_search :: [(FilePath, IO (Module,ModLocation))]
+    to_search = [ (file, fn p basename ext)
+               | p <- path, 
+                 (ext,fn) <- exts,
+                 let base | p == "."  = basename
+                          | otherwise = p ++ '/':basename
+                     file = base ++ '.':ext
+               ]
+
+    search [] = return (Left (map fst to_search))
+    search ((file, result) : rest) = do
+      b <- doesFileExist file
+      if b 
+       then Right `liftM` result
+       else search rest
 
 -- -----------------------------------------------------------------------------
 -- Building ModLocations
index e11b771..a75353b 100644 (file)
@@ -147,14 +147,14 @@ newGlobalName2 mod_name occ
       Nothing   ->     -- No names from this module yet
        ioToTcRn (findModule mod_name)          `thenM` \ mb_loc ->
        case mb_loc of
-           Just (mod, _) -> new_name mod
-           Nothing       -> addErr (noModule mod_name) `thenM_`
-                               -- Things have really gone wrong at this point,
-                               -- so having the wrong package info in the 
-                               -- Module is the least of our worries.
-                            new_name (mkHomeModule mod_name)
-  where
-    noModule mod_name = ptext SLIT("Can't find interface for module") <+> ppr mod_name
+           Right (mod, _) -> new_name mod
+           Left files     -> 
+               getDOpts `thenM` \ dflags ->
+               addErr (noIfaceErr dflags mod_name False files) `thenM_`
+                       -- Things have really gone wrong at this point,
+                       -- so having the wrong package info in the 
+                       -- Module is the least of our worries.
+               new_name (mkHomeModule mod_name)
 
 
 newIPName rdr_name_ip
@@ -1054,6 +1054,16 @@ dupNamesErr descriptor ((name,loc) : dup_things)
              $$ 
              descriptor)
 
+noIfaceErr dflags mod_name boot_file files
+  = ptext SLIT("Could not find interface file for") <+> quotes (ppr mod_name)
+    $$ extra
+  where 
+   extra
+    | verbosity dflags < 3 = 
+        text "(use -v to see a list of the files searched for)"
+    | otherwise =
+        hang (ptext SLIT("locations searched:")) 4 (vcat (map text files))
+
 warnDeprec :: GlobalRdrElt -> TcRn m ()
 warnDeprec (GRE {gre_name = name, gre_deprec = Just txt})
   = ifOptM Opt_WarnDeprecations        $
index f14fb61..e5f83a5 100644 (file)
@@ -15,7 +15,7 @@ module RnHiFiles (
 
 import DriverState     ( v_GhcMode, isCompManagerMode )
 import DriverUtil      ( replaceFilenameSuffix )
-import CmdLineOpts     ( opt_IgnoreIfacePragmas )
+import CmdLineOpts     ( opt_IgnoreIfacePragmas, verbosity )
 import Parser          ( parseIface )
 import HscTypes                ( ModIface(..), emptyModIface,
                          ExternalPackageState(..), noDependencies,
@@ -568,11 +568,12 @@ findAndReadIface doc_str mod_name hi_boot_file
     ioToTcRn (findHiFile mod_name hi_boot_file)        `thenM` \ maybe_found ->
 
     case maybe_found of
-      Nothing -> 
+      Left files -> 
        traceRn (ptext SLIT("...not found"))    `thenM_`
-       returnM (Left (noIfaceErr mod_name hi_boot_file))
+       getDOpts                                `thenM` \ dflags ->
+       returnM (Left (noIfaceErr dflags mod_name hi_boot_file files))
 
-      Just (wanted_mod, file_path) -> 
+      Right (wanted_mod, file_path) -> 
        traceRn (ptext SLIT("readIFace") <+> text file_path)    `thenM_` 
 
        readIface wanted_mod file_path hi_boot_file     `thenM` \ read_result ->
@@ -591,7 +592,8 @@ findAndReadIface doc_str mod_name hi_boot_file
                           ppr mod_name <> semi],
                     nest 4 (ptext SLIT("reason:") <+> doc_str)]
 
-findHiFile :: ModuleName -> IsBootInterface -> IO (Maybe (Module, FilePath))
+findHiFile :: ModuleName -> IsBootInterface
+          -> IO (Either [FilePath] (Module, FilePath))
 findHiFile mod_name hi_boot_file
  = do { 
        -- In interactive or --make mode, we are *not allowed* to demand-load
@@ -607,9 +609,9 @@ findHiFile mod_name hi_boot_file
                        else findPackageModule mod_name ;
 
        case maybe_found of {
-         Nothing -> return Nothing ;
+         Left files -> return (Left files) ;
 
-         Just (mod,loc) -> do {
+         Right (mod,loc) -> do {
 
        -- Return the path to M.hi, M.hi-boot, or M.hi-boot-n as appropriate
        let { hi_path            = ml_hi_file loc ;
@@ -618,11 +620,11 @@ findHiFile mod_name hi_boot_file
            };
 
        if not hi_boot_file then
-          return (Just (mod, hi_path))
+          return (Right (mod, hi_path))
        else do {
                hi_ver_exists <- doesFileExist hi_boot_ver_path ;
-               if hi_ver_exists then return (Just (mod, hi_boot_ver_path))
-                                else return (Just (mod, hi_boot_path))
+               if hi_ver_exists then return (Right (mod, hi_boot_ver_path))
+                                else return (Right (mod, hi_boot_path))
        }}}}
 \end{code}
 
@@ -699,12 +701,6 @@ ghcPrimIface = ParsedIface {
 %*********************************************************
 
 \begin{code}
-noIfaceErr mod_name boot_file
-  = ptext SLIT("Could not find interface file for") <+> quotes (ppr mod_name)
-       -- We used to print the search path, but we can't do that
-       -- now, because it's hidden inside the finder.
-       -- Maybe the finder should expose more functions.
-
 badIfaceFile file err
   = vcat [ptext SLIT("Bad interface file:") <+> text file, 
          nest 4 err]