Improve the "could not find module" error message
authorSimon Marlow <simonmar@microsoft.com>
Fri, 11 Aug 2006 13:21:35 +0000 (13:21 +0000)
committerSimon Marlow <simonmar@microsoft.com>
Fri, 11 Aug 2006 13:21:35 +0000 (13:21 +0000)
In particular, if we're searching for the profiling version of a
module in another package, then suggest that perhaps it might not have
been installed.

compiler/iface/LoadIface.lhs
compiler/main/Finder.lhs
compiler/main/GHC.hs
compiler/main/HscTypes.lhs

index 51b540c..ecba1d6 100644 (file)
@@ -48,7 +48,7 @@ import SrcLoc         ( importedSrcLoc )
 import Maybes          ( MaybeErr(..) )
 import ErrUtils         ( Message )
 import Finder          ( findImportedModule, findExactModule,  
 import Maybes          ( MaybeErr(..) )
 import ErrUtils         ( Message )
 import Finder          ( findImportedModule, findExactModule,  
-                         FindResult(..), cantFindError )
+                         FindResult(..), cannotFindInterface )
 import UniqFM
 import Outputable
 import BinIface                ( readBinIface )
 import UniqFM
 import Outputable
 import BinIface                ( readBinIface )
@@ -81,14 +81,11 @@ loadSrcInterface doc mod want_boot  = do
     Found _ mod -> do
       mb_iface <- initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
       case mb_iface of
     Found _ mod -> do
       mb_iface <- initIfaceTcRn $ loadInterface doc mod (ImportByUser want_boot)
       case mb_iface of
-       Failed err      -> failWithTc (elaborate err)
+       Failed err      -> failWithTc err
        Succeeded iface -> return iface
     err ->
         let dflags = hsc_dflags hsc_env in
        Succeeded iface -> return iface
     err ->
         let dflags = hsc_dflags hsc_env in
-       failWithTc (elaborate (cantFindError dflags mod err))
-  where
-    elaborate err = hang (ptext SLIT("Failed to load interface for") <+> 
-                         quotes (ppr mod) <> colon) 4 err
+       failWithTc (cannotFindInterface dflags mod err)
 
 -- | Load interfaces for a collection of orphan modules.
 loadOrphanModules :: [Module] -> TcM ()
 
 -- | Load interfaces for a collection of orphan modules.
 loadOrphanModules :: [Module] -> TcM ()
@@ -420,7 +417,8 @@ findAndReadIface doc_str mod hi_boot_file
              Failed err -> do
                { traceIf (ptext SLIT("...not found"))
                ; dflags <- getDOpts
              Failed err -> do
                { traceIf (ptext SLIT("...not found"))
                ; dflags <- getDOpts
-               ; returnM (Failed (cantFindError dflags (moduleName mod) err)) } ;
+               ; returnM (Failed (cannotFindInterface dflags 
+                                       (moduleName mod) err)) } ;
 
              Succeeded file_path -> do 
 
 
              Succeeded file_path -> do 
 
index fd0982d..1f047fa 100644 (file)
@@ -19,7 +19,8 @@ module Finder (
     findObjectLinkableMaybe,
     findObjectLinkable,
 
     findObjectLinkableMaybe,
     findObjectLinkable,
 
-    cantFindError,
+    cannotFindModule,
+    cannotFindInterface,
   ) where
 
 #include "HsVersions.h"
   ) where
 
 #include "HsVersions.h"
@@ -144,10 +145,10 @@ findExactModule hsc_env mod =
 this `orIfNotFound` or_this = do
   res <- this
   case res of
 this `orIfNotFound` or_this = do
   res <- this
   case res of
-    NotFound here -> do
+    NotFound here _ -> do
        res2 <- or_this
        case res2 of
        res2 <- or_this
        case res2 of
-          NotFound or_here -> return (NotFound (here ++ or_here))
+          NotFound or_here pkg -> return (NotFound (here ++ or_here) pkg)
           _other -> return res2
     _other -> return res
 
           _other -> return res2
     _other -> return res
 
@@ -168,7 +169,7 @@ homeSearchCache hsc_env mod_name do_this = do
 findExposedPackageModule :: HscEnv -> ModuleName -> IO FindResult
 findExposedPackageModule hsc_env mod_name
         -- not found in any package:
 findExposedPackageModule :: HscEnv -> ModuleName -> IO FindResult
 findExposedPackageModule hsc_env mod_name
         -- not found in any package:
-  | null found = return (NotFound [])
+  | null found = return (NotFound [] Nothing)
         -- found in just one exposed package:
   | [(pkg_conf, _)] <- found_exposed
         = let pkgid = mkPackageId (package pkg_conf) in      
         -- found in just one exposed package:
   | [(pkg_conf, _)] <- found_exposed
         = let pkgid = mkPackageId (package pkg_conf) in      
@@ -329,7 +330,7 @@ searchPathExts paths mod exts
                      file = base `joinFileExt` ext
                ]
 
                      file = base `joinFileExt` ext
                ]
 
-    search [] = return (NotFound (map fst to_search))
+    search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod)))
     search ((file, mk_result) : rest) = do
       b <- doesFileExist file
       if b 
     search ((file, mk_result) : rest) = do
       b <- doesFileExist file
       if b 
@@ -505,14 +506,19 @@ dots_to_slashes = map (\c -> if c == '.' then '/' else c)
 -- -----------------------------------------------------------------------------
 -- Error messages
 
 -- -----------------------------------------------------------------------------
 -- Error messages
 
-cantFindError :: DynFlags -> ModuleName -> FindResult -> SDoc
-cantFindError dflags mod_name (FoundMultiple pkgs)
-  = hang (ptext SLIT("Cannot import") <+> quotes (ppr mod_name) <> colon) 2 (
+cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
+cannotFindModule = cantFindErr SLIT("Could not find module")
+
+cannotFindInterface  :: DynFlags -> ModuleName -> FindResult -> SDoc
+cannotFindInterface = cantFindErr SLIT("Failed to load interface for")
+
+cantFindErr cannot_find dflags mod_name (FoundMultiple pkgs)
+  = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 (
        sep [ptext SLIT("it was found in multiple packages:"),
                hsep (map (text.packageIdString) pkgs)]
     )
        sep [ptext SLIT("it was found in multiple packages:"),
                hsep (map (text.packageIdString) pkgs)]
     )
-cantFindError dflags mod_name find_result
-  = hang (ptext SLIT("Could not find module") <+> quotes (ppr mod_name) <> colon)
+cantFindErr cannot_find dflags mod_name find_result
+  = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon)
        2 more_info
   where
     more_info
        2 more_info
   where
     more_info
@@ -529,17 +535,31 @@ cantFindError dflags mod_name find_result
                -> ptext SLIT("no package matching") <+> ppr pkg <+>
                   ptext SLIT("was found")
 
                -> ptext SLIT("no package matching") <+> ppr pkg <+>
                   ptext SLIT("was found")
 
-           NotFound files
+           NotFound files mb_pkg
                | null files
                -> ptext SLIT("it is not a module in the current program, or in any known package.")
                | null files
                -> ptext SLIT("it is not a module in the current program, or in any known package.")
-               | verbosity dflags < 3 
-               -> ptext SLIT("use -v to see a list of the files searched for")
-               | otherwise 
-               -> hang (ptext SLIT("locations searched:")) 
-                     2 (vcat (map text files))
+               | Just pkg <- mb_pkg, pkg /= thisPackage dflags, build_tag /= ""
+               -> let 
+                    build = if build_tag == "p" then "profiling" 
+                                                else "\"" ++ build_tag ++ "\""
+                  in
+                  ptext SLIT("Perhaps you haven't installed the ") <> text build <>
+                  ptext SLIT(" libraries for package ") <> ppr pkg <> char '?' $$
+                  not_found files
+
+               | otherwise
+               -> not_found files
 
            NotFoundInPackage pkg
                -> ptext SLIT("it is not in package") <+> ppr pkg
 
            _ -> panic "cantFindErr"
 
            NotFoundInPackage pkg
                -> ptext SLIT("it is not in package") <+> ppr pkg
 
            _ -> panic "cantFindErr"
+
+    build_tag = buildTag dflags
+
+    not_found files
+       | verbosity dflags < 3
+       = ptext SLIT("Use -v to see a list of the files searched for.")
+       | otherwise 
+       = hang (ptext SLIT("locations searched:")) 2 (vcat (map text files))
 \end{code}
 \end{code}
index 207f5a3..0654323 100644 (file)
@@ -1631,7 +1631,7 @@ preprocessFile dflags src_fn mb_phase (Just (buf, time))
 noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> IO ab
 -- ToDo: we don't have a proper line number for this error
 noModError dflags loc wanted_mod err
 noModError :: DynFlags -> SrcSpan -> ModuleName -> FindResult -> IO ab
 -- ToDo: we don't have a proper line number for this error
 noModError dflags loc wanted_mod err
-  = throwDyn $ mkPlainErrMsg loc $ cantFindError dflags wanted_mod err
+  = throwDyn $ mkPlainErrMsg loc $ cannotFindModule dflags wanted_mod err
                                
 noHsFileErr loc path
   = throwDyn $ mkPlainErrMsg loc $ text "Can't find" <+> text path
                                
 noHsFileErr loc path
   = throwDyn $ mkPlainErrMsg loc $ text "Can't find" <+> text path
@@ -1850,7 +1850,7 @@ findModule' hsc_env mod_name maybe_pkg =
          case res of
            Found _ m | modulePackageId m /= this_pkg -> return m
                         -- not allowed to be a home module
          case res of
            Found _ m | modulePackageId m /= this_pkg -> return m
                         -- not allowed to be a home module
-           err -> let msg = cantFindError dflags mod_name err in
+           err -> let msg = cannotFindModule dflags mod_name err in
                   throwDyn (CmdLineError (showSDoc msg))
 
 #ifdef GHCI
                   throwDyn (CmdLineError (showSDoc msg))
 
 #ifdef GHCI
index a200bf9..9bc5fb1 100644 (file)
@@ -323,8 +323,8 @@ data FindResult
   | ModuleHidden  PackageId
        -- for an explicit source import: the package containing the module is
        -- exposed, but the module itself is hidden.
   | ModuleHidden  PackageId
        -- for an explicit source import: the package containing the module is
        -- exposed, but the module itself is hidden.
-  | NotFound [FilePath]
-       -- the module was not found, the specified places were searched.
+  | NotFound [FilePath] (Maybe PackageId)
+       -- the module was not found, the specified places were searched
   | NotFoundInPackage PackageId
        -- the module was not found in this package
 
   | NotFoundInPackage PackageId
        -- the module was not found in this package