Remove unused imports
[ghc-hetmet.git] / compiler / main / Finder.lhs
index 63beae4..cc19e31 100644 (file)
@@ -10,6 +10,7 @@ module Finder (
     findImportedModule,
     findExactModule,
     findHomeModule,
+    findExposedPackageModule,
     mkHomeModLocation,
     mkHomeModLocation2,
     mkHiOnlyModLocation,
@@ -37,11 +38,10 @@ import FiniteMap
 import LazyUniqFM
 import Maybes          ( expectJust )
 
+import Distribution.Package hiding (PackageId)
 import Data.IORef      ( IORef, writeIORef, readIORef, modifyIORef )
-import Data.List
 import System.Directory
 import System.FilePath
-import System.IO
 import Control.Monad
 import System.Time     ( ClockTime )
 
@@ -113,27 +113,20 @@ lookupModLocationCache ref key = do
 -- packages to find the module, if a package is specified then only
 -- that package is searched for the module.
 
-findImportedModule :: HscEnv -> ModuleName -> Maybe PackageId -> IO FindResult
-findImportedModule hsc_env mod_name mb_pkgid =
-  case mb_pkgid of
-       Nothing                    -> unqual_import
-       Just pkg | pkg == this_pkg -> home_import
-                | otherwise       -> pkg_import pkg
+findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
+findImportedModule hsc_env mod_name mb_pkg =
+  case mb_pkg of
+       Nothing                        -> unqual_import
+       Just pkg | pkg == fsLit "this" -> home_import -- "this" is special
+                | otherwise           -> pkg_import
   where
-    dflags = hsc_dflags hsc_env
-    this_pkg = thisPackage dflags
+    home_import   = findHomeModule hsc_env mod_name
 
-    home_import     = findHomeModule hsc_env mod_name
+    pkg_import    = findExposedPackageModule hsc_env mod_name mb_pkg
 
-    pkg_import pkg  = findPackageModule hsc_env (mkModule pkg mod_name)
-                       -- ToDo: this isn't quite right, the module we want
-                       -- might actually be in another package, but re-exposed
-                       -- ToDo: should return NotFoundInPackage if
-                       -- the module isn't exposed by the package.
-
-    unqual_import   = home_import 
+    unqual_import = home_import 
                        `orIfNotFound`
-                     findExposedPackageModule hsc_env mod_name
+                     findExposedPackageModule hsc_env mod_name Nothing
 
 -- | Locate a specific 'Module'.  The purpose of this function is to
 -- create a 'ModLocation' for a given 'Module', that is to find out
@@ -155,10 +148,14 @@ orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult
 this `orIfNotFound` or_this = do
   res <- this
   case res of
-    NotFound here _ -> do
+    NotFound places1 _mb_pkg1 mod_hiddens1 pkg_hiddens1 -> do
        res2 <- or_this
        case res2 of
-          NotFound or_here pkg -> return (NotFound (here ++ or_here) pkg)
+          NotFound places2 mb_pkg2 mod_hiddens2 pkg_hiddens2 -> 
+              return (NotFound (places1 ++ places2)
+                               mb_pkg2 -- snd arg is the package search
+                               (mod_hiddens1 ++ mod_hiddens2)
+                               (pkg_hiddens1 ++ pkg_hiddens2))
           _other -> return res2
     _other -> return res
 
@@ -176,28 +173,40 @@ homeSearchCache hsc_env mod_name do_this = do
           _other        -> return ()
        return result
 
-findExposedPackageModule :: HscEnv -> ModuleName -> IO FindResult
-findExposedPackageModule hsc_env mod_name
+findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
+                         -> IO FindResult
+findExposedPackageModule hsc_env mod_name mb_pkg
         -- not found in any package:
-  | null found = return (NotFound [] Nothing)
+  | null found_exposed = return (NotFound [] Nothing mod_hiddens pkg_hiddens)
         -- found in just one exposed package:
   | [(pkg_conf, _)] <- found_exposed
         = let pkgid = mkPackageId (package pkg_conf) in      
           findPackageModule_ hsc_env (mkModule pkgid mod_name) pkg_conf
-        -- not found in any exposed package, report how it was hidden:
-  | null found_exposed, ((pkg_conf, exposed_mod):_) <- found
-        = let pkgid = mkPackageId (package pkg_conf) in
-          if not (exposed_mod)
-                then return (ModuleHidden pkgid)
-                else return (PackageHidden pkgid)
   | otherwise
         = return (FoundMultiple (map (mkPackageId.package.fst) found_exposed))
   where
        dflags = hsc_dflags hsc_env
         found = lookupModuleInAllPackages dflags mod_name
-        found_exposed = filter is_exposed found
+
+        for_this_pkg = filter ((`matches` mb_pkg) . fst) found
+
+        found_exposed = [ (pkg_conf,exposed_mod) 
+                        | x@(pkg_conf,exposed_mod) <- for_this_pkg,
+                          is_exposed x ]
+
         is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod
 
+        mod_hiddens = [ mkPackageId (package pkg_conf)
+                      | (pkg_conf,False) <- found ]
+
+        pkg_hiddens = [ mkPackageId (package pkg_conf)
+                      | (pkg_conf,_) <- found, not (exposed pkg_conf) ]
+
+        _pkg_conf `matches` Nothing  = True
+        pkg_conf  `matches` Just pkg =
+           case packageName pkg_conf of 
+              PackageName n -> pkg == mkFastString n
+
 
 modLocationCache :: HscEnv -> Module -> IO FindResult -> IO FindResult
 modLocationCache hsc_env mod do_this = do
@@ -293,24 +302,22 @@ findPackageModule_ hsc_env mod pkg_conf =
           -- hi-suffix for packages depends on the build tag.
      package_hisuf | null tag  = "hi"
                   | otherwise = tag ++ "_hi"
-     hi_exts =
-        [ (package_hisuf, mkHiOnlyModLocation dflags package_hisuf) ]
 
-     source_exts = 
-       [ ("hs",   mkHiOnlyModLocation dflags package_hisuf)
-       , ("lhs",  mkHiOnlyModLocation dflags package_hisuf)
-       ]
-
-     -- mkdependHS needs to look for source files in packages too, so
-     -- that we can make dependencies between package before they have
-     -- been built.
-     exts 
-      | MkDepend <- ghcMode dflags = hi_exts ++ source_exts
-      | otherwise                 = hi_exts
+     mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf
+
+     import_dirs = importDirs pkg_conf
       -- we never look for a .hi-boot file in an external package;
       -- .hi-boot files only make sense for the home package.
   in
-  searchPathExts (importDirs pkg_conf) mod exts
+  case import_dirs of
+    [one] | MkDepend <- ghcMode dflags -> do
+          -- there's only one place that this .hi file can be, so
+          -- don't bother looking for it.
+          let basename = moduleNameSlashes (moduleName mod)
+          loc <- mk_hi_loc one basename
+          return (Found loc mod)
+    _otherwise ->
+          searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
 
 -- -----------------------------------------------------------------------------
 -- General path searching
@@ -349,7 +356,8 @@ searchPathExts paths mod exts
                      file = base <.> ext
                ]
 
-    search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod)))
+    search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod))
+                        [] [])
     search ((file, mk_result) : rest) = do
       b <- doesFileExist file
       if b 
@@ -489,23 +497,14 @@ mkStubPaths dflags mod location
 
         stub_basename = stub_basename0 ++ "_stub"
 
-        -- this is the filename we're going to use when
-        -- \#including the stub_h file from the .hc file.
-        -- Without -stubdir, we just #include the basename
-        -- (eg. for a module A.B, we #include "B_stub.h"),
-        -- relying on the fact that we add an implicit -I flag
-        -- for the directory in which the source file resides
-        -- (see DriverPipeline.hs).  With -stubdir, we
-        -- \#include "A/B.h", assuming that the user has added
-        -- -I<dir> along with -stubdir <dir>.
-        include_basename
-                | Just _ <- stubdir = mod_basename 
-                | otherwise         = takeFileName src_basename
+        obj  = ml_obj_file location
+        osuf = objectSuf dflags
+        stub_obj_base = dropTail (length osuf + 1) obj ++ "_stub"
+                        -- NB. not takeFileName, see #3093
      in
         (stub_basename <.> "c",
          stub_basename <.> "h",
-         (include_basename ++ "_stub") <.> "h")
-        -- the _stub.o filename is derived from the ml_obj_file.
+         stub_obj_base <.> objectSuf dflags)
 
 -- -----------------------------------------------------------------------------
 -- findLinkable isn't related to the other stuff in here, 
@@ -534,59 +533,74 @@ findObjectLinkable mod obj_fn obj_time = do
 
 cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
 cannotFindModule = cantFindErr (sLit "Could not find module")
+                               (sLit "Ambiguous module name")
 
 cannotFindInterface  :: DynFlags -> ModuleName -> FindResult -> SDoc
 cannotFindInterface = cantFindErr (sLit "Failed to load interface for")
+                                  (sLit "Ambiguous interface for")
 
-cantFindErr :: LitString -> DynFlags -> ModuleName -> FindResult -> SDoc
-cantFindErr cannot_find _dflags mod_name (FoundMultiple pkgs)
-  = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 (
+cantFindErr :: LitString -> LitString -> DynFlags -> ModuleName -> FindResult
+            -> SDoc
+cantFindErr _ multiple_found _ mod_name (FoundMultiple pkgs)
+  = hang (ptext multiple_found <+> quotes (ppr mod_name) <> colon) 2 (
        sep [ptext (sLit "it was found in multiple packages:"),
                hsep (map (text.packageIdString) pkgs)]
     )
-cantFindErr cannot_find dflags mod_name find_result
+cantFindErr cannot_find _ dflags mod_name find_result
   = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon)
        2 more_info
   where
     more_info
       = case find_result of
-           PackageHidden pkg 
-               -> ptext (sLit "it is a member of package") <+> ppr pkg <> comma
-                  <+> ptext (sLit "which is hidden")
-
-           ModuleHidden pkg
-               -> ptext (sLit "it is hidden") <+> parens (ptext (sLit "in package")
-                  <+> ppr pkg)
-
            NoPackage pkg
-               -> ptext (sLit "no package matching") <+> ppr pkg <+>
+               -> ptext (sLit "no package matching") <+> quotes (ppr pkg) <+>
                   ptext (sLit "was found")
 
-           NotFound files mb_pkg
-               | null files
+           NotFound files mb_pkg mod_hiddens pkg_hiddens
+               | Just pkg <- mb_pkg, pkg /= thisPackage dflags
+               -> not_found_in_package pkg files
+
+                | null files && null mod_hiddens && null pkg_hiddens
                -> ptext (sLit "it is not a module in the current program, or in any known package.")
-               | 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
+               -> vcat (map pkg_hidden pkg_hiddens) $$
+                   vcat (map mod_hidden mod_hiddens) $$ 
+                   tried_these files
 
            NotFoundInPackage pkg
-               -> ptext (sLit "it is not in package") <+> ppr pkg
+               -> ptext (sLit "it is not in package") <+> quotes (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))
+    not_found_in_package pkg files
+       | 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 ") <> quotes (ppr pkg) <> char '?' $$
+         tried_these files
+
+       | otherwise
+       = ptext (sLit "There are files missing in the ") <> quotes (ppr pkg) <>
+         ptext (sLit " package,") $$
+         ptext (sLit "try running 'ghc-pkg check'.") $$
+         tried_these files
+
+    tried_these files
+        | null files = empty
+        | 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)
+        
+    pkg_hidden pkg =
+        ptext (sLit "it is a member of the hidden package") <+> quotes (ppr pkg)
+
+    mod_hidden pkg =
+        ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg)
 \end{code}