Improvements to the "can't find module" error message (#2980)
[ghc-hetmet.git] / compiler / main / Finder.lhs
1 %
2 % (c) The University of Glasgow, 2000-2006
3 %
4 \section[Finder]{Module Finder}
5
6 \begin{code}
7 module Finder (
8     flushFinderCaches,
9     FindResult(..),
10     findImportedModule,
11     findExactModule,
12     findHomeModule,
13     mkHomeModLocation,
14     mkHomeModLocation2,
15     mkHiOnlyModLocation,
16     addHomeModuleToFinder,
17     uncacheModule,
18     mkStubPaths,
19
20     findObjectLinkableMaybe,
21     findObjectLinkable,
22
23     cannotFindModule,
24     cannotFindInterface,
25
26   ) where
27
28 import Module
29 import HscTypes
30 import Packages
31 import FastString
32 import Util
33 import PrelNames        ( gHC_PRIM )
34 import DynFlags         ( DynFlags(..), isOneShot, GhcMode(..) )
35 import Outputable
36 import FiniteMap
37 import LazyUniqFM
38 import Maybes           ( expectJust )
39
40 import Distribution.Package hiding (PackageId)
41 import Data.IORef       ( IORef, writeIORef, readIORef, modifyIORef )
42 import Data.List
43 import System.Directory
44 import System.FilePath
45 import System.IO
46 import Control.Monad
47 import System.Time      ( ClockTime )
48
49
50 type FileExt = String   -- Filename extension
51 type BaseName = String  -- Basename of file
52
53 -- -----------------------------------------------------------------------------
54 -- The Finder
55
56 -- The Finder provides a thin filesystem abstraction to the rest of
57 -- the compiler.  For a given module, it can tell you where the
58 -- source, interface, and object files for that module live.
59
60 -- It does *not* know which particular package a module lives in.  Use
61 -- Packages.lookupModuleInAllPackages for that.
62
63 -- -----------------------------------------------------------------------------
64 -- The finder's cache
65
66 -- remove all the home modules from the cache; package modules are
67 -- assumed to not move around during a session.
68 flushFinderCaches :: HscEnv -> IO ()
69 flushFinderCaches hsc_env = do
70   writeIORef fc_ref emptyUFM
71   flushModLocationCache this_pkg mlc_ref
72  where
73         this_pkg = thisPackage (hsc_dflags hsc_env)
74         fc_ref = hsc_FC hsc_env
75         mlc_ref = hsc_MLC hsc_env
76
77 flushModLocationCache :: PackageId -> IORef ModLocationCache -> IO ()
78 flushModLocationCache this_pkg ref = do
79   fm <- readIORef ref
80   writeIORef ref $! filterFM is_ext fm
81   return ()
82   where is_ext mod _ | modulePackageId mod /= this_pkg = True
83                      | otherwise = False
84
85 addToFinderCache :: IORef FinderCache -> ModuleName -> FindResult -> IO ()
86 addToFinderCache       ref key val = modifyIORef ref $ \c -> addToUFM c key val
87
88 addToModLocationCache :: IORef ModLocationCache -> Module -> ModLocation -> IO ()
89 addToModLocationCache  ref key val = modifyIORef ref $ \c -> addToFM c key val
90
91 removeFromFinderCache :: IORef FinderCache -> ModuleName -> IO ()
92 removeFromFinderCache      ref key = modifyIORef ref $ \c -> delFromUFM c key
93
94 removeFromModLocationCache :: IORef ModLocationCache -> Module -> IO ()
95 removeFromModLocationCache ref key = modifyIORef ref $ \c -> delFromFM c key
96
97 lookupFinderCache :: IORef FinderCache -> ModuleName -> IO (Maybe FindResult)
98 lookupFinderCache ref key = do 
99    c <- readIORef ref
100    return $! lookupUFM c key
101
102 lookupModLocationCache :: IORef ModLocationCache -> Module
103                        -> IO (Maybe ModLocation)
104 lookupModLocationCache ref key = do
105    c <- readIORef ref
106    return $! lookupFM c key
107
108 -- -----------------------------------------------------------------------------
109 -- The two external entry points
110
111 -- | Locate a module that was imported by the user.  We have the
112 -- module's name, and possibly a package name.  Without a package
113 -- name, this function will use the search path and the known exposed
114 -- packages to find the module, if a package is specified then only
115 -- that package is searched for the module.
116
117 findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
118 findImportedModule hsc_env mod_name mb_pkg =
119   case mb_pkg of
120         Nothing                        -> unqual_import
121         Just pkg | pkg == fsLit "this" -> home_import -- "this" is special
122                  | otherwise           -> pkg_import
123   where
124     home_import   = findHomeModule hsc_env mod_name
125
126     pkg_import    = findExposedPackageModule hsc_env mod_name mb_pkg
127
128     unqual_import = home_import 
129                         `orIfNotFound`
130                       findExposedPackageModule hsc_env mod_name Nothing
131
132 -- | Locate a specific 'Module'.  The purpose of this function is to
133 -- create a 'ModLocation' for a given 'Module', that is to find out
134 -- where the files associated with this module live.  It is used when
135 -- reading the interface for a module mentioned by another interface, 
136 -- for example (a "system import").
137
138 findExactModule :: HscEnv -> Module -> IO FindResult
139 findExactModule hsc_env mod =
140    let dflags = hsc_dflags hsc_env in
141    if modulePackageId mod == thisPackage dflags
142         then findHomeModule hsc_env (moduleName mod)
143         else findPackageModule hsc_env mod
144
145 -- -----------------------------------------------------------------------------
146 -- Helpers
147
148 orIfNotFound :: IO FindResult -> IO FindResult -> IO FindResult
149 this `orIfNotFound` or_this = do
150   res <- this
151   case res of
152     NotFound places1 _mb_pkg1 mod_hiddens1 pkg_hiddens1 -> do
153         res2 <- or_this
154         case res2 of
155            NotFound places2 mb_pkg2 mod_hiddens2 pkg_hiddens2 -> 
156               return (NotFound (places1 ++ places2)
157                                mb_pkg2 -- snd arg is the package search
158                                (mod_hiddens1 ++ mod_hiddens2)
159                                (pkg_hiddens1 ++ pkg_hiddens2))
160            _other -> return res2
161     _other -> return res
162
163
164 homeSearchCache :: HscEnv -> ModuleName -> IO FindResult -> IO FindResult
165 homeSearchCache hsc_env mod_name do_this = do
166   m <- lookupFinderCache (hsc_FC hsc_env) mod_name
167   case m of 
168     Just result -> return result
169     Nothing     -> do
170         result <- do_this
171         addToFinderCache (hsc_FC hsc_env) mod_name result
172         case result of
173            Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc
174            _other        -> return ()
175         return result
176
177 findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString
178                          -> IO FindResult
179 findExposedPackageModule hsc_env mod_name mb_pkg
180         -- not found in any package:
181   | null found_exposed = return (NotFound [] Nothing mod_hiddens pkg_hiddens)
182         -- found in just one exposed package:
183   | [(pkg_conf, _)] <- found_exposed
184         = let pkgid = mkPackageId (package pkg_conf) in      
185           findPackageModule_ hsc_env (mkModule pkgid mod_name) pkg_conf
186   | otherwise
187         = return (FoundMultiple (map (mkPackageId.package.fst) found_exposed))
188   where
189         dflags = hsc_dflags hsc_env
190         found = lookupModuleInAllPackages dflags mod_name
191
192         for_this_pkg = filter ((`matches` mb_pkg) . fst) found
193
194         found_exposed = [ (pkg_conf,exposed_mod) 
195                         | x@(pkg_conf,exposed_mod) <- for_this_pkg,
196                           is_exposed x ]
197
198         is_exposed (pkg_conf,exposed_mod) = exposed pkg_conf && exposed_mod
199
200         mod_hiddens = [ mkPackageId (package pkg_conf)
201                       | (pkg_conf,False) <- found ]
202
203         pkg_hiddens = [ mkPackageId (package pkg_conf)
204                       | (pkg_conf,_) <- found, not (exposed pkg_conf) ]
205
206         _pkg_conf `matches` Nothing  = True
207         pkg_conf  `matches` Just pkg =
208            case packageName pkg_conf of 
209               PackageName n -> pkg == mkFastString n
210
211
212 modLocationCache :: HscEnv -> Module -> IO FindResult -> IO FindResult
213 modLocationCache hsc_env mod do_this = do
214   mb_loc <- lookupModLocationCache mlc mod
215   case mb_loc of
216      Just loc -> return (Found loc mod)
217      Nothing  -> do
218         result <- do_this
219         case result of
220             Found loc mod -> addToModLocationCache (hsc_MLC hsc_env) mod loc
221             _other -> return ()
222         return result
223   where
224     mlc = hsc_MLC hsc_env
225
226 addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
227 addHomeModuleToFinder hsc_env mod_name loc = do
228   let mod = mkModule (thisPackage (hsc_dflags hsc_env)) mod_name
229   addToFinderCache (hsc_FC hsc_env) mod_name (Found loc mod)
230   addToModLocationCache (hsc_MLC hsc_env) mod loc
231   return mod
232
233 uncacheModule :: HscEnv -> ModuleName -> IO ()
234 uncacheModule hsc_env mod = do
235   let this_pkg = thisPackage (hsc_dflags hsc_env)
236   removeFromFinderCache (hsc_FC hsc_env) mod
237   removeFromModLocationCache (hsc_MLC hsc_env) (mkModule this_pkg mod)
238
239 -- -----------------------------------------------------------------------------
240 --      The internal workers
241
242 -- | Search for a module in the home package only.
243 findHomeModule :: HscEnv -> ModuleName -> IO FindResult
244 findHomeModule hsc_env mod_name =
245    homeSearchCache hsc_env mod_name $
246    let 
247      dflags = hsc_dflags hsc_env
248      home_path = importPaths dflags
249      hisuf = hiSuf dflags
250      mod = mkModule (thisPackage dflags) mod_name
251
252      source_exts = 
253       [ ("hs",   mkHomeModLocationSearched dflags mod_name "hs")
254       , ("lhs",  mkHomeModLocationSearched dflags mod_name "lhs")
255       ]
256      
257      hi_exts = [ (hisuf,                mkHiOnlyModLocation dflags hisuf)
258                , (addBootSuffix hisuf,  mkHiOnlyModLocation dflags hisuf)
259                ]
260      
261         -- In compilation manager modes, we look for source files in the home
262         -- package because we can compile these automatically.  In one-shot
263         -- compilation mode we look for .hi and .hi-boot files only.
264      exts | isOneShot (ghcMode dflags) = hi_exts
265           | otherwise                  = source_exts
266    in
267
268   -- special case for GHC.Prim; we won't find it in the filesystem.
269   -- This is important only when compiling the base package (where GHC.Prim
270   -- is a home module).
271   if mod == gHC_PRIM 
272         then return (Found (error "GHC.Prim ModLocation") mod)
273         else 
274
275    searchPathExts home_path mod exts
276
277
278 -- | Search for a module in external packages only.
279 findPackageModule :: HscEnv -> Module -> IO FindResult
280 findPackageModule hsc_env mod = do
281   let
282         dflags = hsc_dflags hsc_env
283         pkg_id = modulePackageId mod
284         pkg_map = pkgIdMap (pkgState dflags)
285   --
286   case lookupPackage pkg_map pkg_id of
287      Nothing -> return (NoPackage pkg_id)
288      Just pkg_conf -> findPackageModule_ hsc_env mod pkg_conf
289       
290 findPackageModule_ :: HscEnv -> Module -> PackageConfig -> IO FindResult
291 findPackageModule_ hsc_env mod pkg_conf = 
292   modLocationCache hsc_env mod $
293
294   -- special case for GHC.Prim; we won't find it in the filesystem.
295   if mod == gHC_PRIM 
296         then return (Found (error "GHC.Prim ModLocation") mod)
297         else 
298
299   let
300      dflags = hsc_dflags hsc_env
301      tag = buildTag dflags
302
303            -- hi-suffix for packages depends on the build tag.
304      package_hisuf | null tag  = "hi"
305                    | otherwise = tag ++ "_hi"
306
307      mk_hi_loc = mkHiOnlyModLocation dflags package_hisuf
308
309      import_dirs = importDirs pkg_conf
310       -- we never look for a .hi-boot file in an external package;
311       -- .hi-boot files only make sense for the home package.
312   in
313   case import_dirs of
314     [one] | MkDepend <- ghcMode dflags -> do
315           -- there's only one place that this .hi file can be, so
316           -- don't bother looking for it.
317           let basename = moduleNameSlashes (moduleName mod)
318           loc <- mk_hi_loc one basename
319           return (Found loc mod)
320     _otherwise ->
321           searchPathExts import_dirs mod [(package_hisuf, mk_hi_loc)]
322
323 -- -----------------------------------------------------------------------------
324 -- General path searching
325
326 searchPathExts
327   :: [FilePath]         -- paths to search
328   -> Module             -- module name
329   -> [ (
330         FileExt,                                -- suffix
331         FilePath -> BaseName -> IO ModLocation  -- action
332        )
333      ] 
334   -> IO FindResult
335
336 searchPathExts paths mod exts 
337    = do result <- search to_search
338 {-
339         hPutStrLn stderr (showSDoc $
340                 vcat [text "Search" <+> ppr mod <+> sep (map (text. fst) exts)
341                     , nest 2 (vcat (map text paths))
342                     , case result of
343                         Succeeded (loc, p) -> text "Found" <+> ppr loc
344                         Failed fs          -> text "not found"])
345 -}      
346         return result
347
348   where
349     basename = moduleNameSlashes (moduleName mod)
350
351     to_search :: [(FilePath, IO ModLocation)]
352     to_search = [ (file, fn path basename)
353                 | path <- paths, 
354                   (ext,fn) <- exts,
355                   let base | path == "." = basename
356                            | otherwise   = path </> basename
357                       file = base <.> ext
358                 ]
359
360     search [] = return (NotFound (map fst to_search) (Just (modulePackageId mod))
361                         [] [])
362     search ((file, mk_result) : rest) = do
363       b <- doesFileExist file
364       if b 
365         then do { loc <- mk_result; return (Found loc mod) }
366         else search rest
367
368 mkHomeModLocationSearched :: DynFlags -> ModuleName -> FileExt
369                           -> FilePath -> BaseName -> IO ModLocation
370 mkHomeModLocationSearched dflags mod suff path basename = do
371    mkHomeModLocation2 dflags mod (path </> basename) suff
372
373 -- -----------------------------------------------------------------------------
374 -- Constructing a home module location
375
376 -- This is where we construct the ModLocation for a module in the home
377 -- package, for which we have a source file.  It is called from three
378 -- places:
379 --
380 --  (a) Here in the finder, when we are searching for a module to import,
381 --      using the search path (-i option).
382 --
383 --  (b) The compilation manager, when constructing the ModLocation for
384 --      a "root" module (a source file named explicitly on the command line
385 --      or in a :load command in GHCi).
386 --
387 --  (c) The driver in one-shot mode, when we need to construct a
388 --      ModLocation for a source file named on the command-line.
389 --
390 -- Parameters are:
391 --
392 -- mod
393 --      The name of the module
394 --
395 -- path
396 --      (a): The search path component where the source file was found.
397 --      (b) and (c): "."
398 --
399 -- src_basename
400 --      (a): (moduleNameSlashes mod)
401 --      (b) and (c): The filename of the source file, minus its extension
402 --
403 -- ext
404 --      The filename extension of the source file (usually "hs" or "lhs").
405
406 mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
407 mkHomeModLocation dflags mod src_filename = do
408    let (basename,extension) = splitExtension src_filename
409    mkHomeModLocation2 dflags mod basename extension
410
411 mkHomeModLocation2 :: DynFlags
412                    -> ModuleName
413                    -> FilePath  -- Of source module, without suffix
414                    -> String    -- Suffix
415                    -> IO ModLocation
416 mkHomeModLocation2 dflags mod src_basename ext = do
417    let mod_basename = moduleNameSlashes mod
418
419    obj_fn  <- mkObjPath  dflags src_basename mod_basename
420    hi_fn   <- mkHiPath   dflags src_basename mod_basename
421
422    return (ModLocation{ ml_hs_file   = Just (src_basename <.> ext),
423                         ml_hi_file   = hi_fn,
424                         ml_obj_file  = obj_fn })
425
426 mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String
427                     -> IO ModLocation
428 mkHiOnlyModLocation dflags hisuf path basename
429  = do let full_basename = path </> basename
430       obj_fn  <- mkObjPath  dflags full_basename basename
431       return ModLocation{    ml_hs_file   = Nothing,
432                              ml_hi_file   = full_basename <.> hisuf,
433                                 -- Remove the .hi-boot suffix from
434                                 -- hi_file, if it had one.  We always
435                                 -- want the name of the real .hi file
436                                 -- in the ml_hi_file field.
437                              ml_obj_file  = obj_fn
438                   }
439
440 -- | Constructs the filename of a .o file for a given source file.
441 -- Does /not/ check whether the .o file exists
442 mkObjPath
443   :: DynFlags
444   -> FilePath           -- the filename of the source file, minus the extension
445   -> String             -- the module name with dots replaced by slashes
446   -> IO FilePath
447 mkObjPath dflags basename mod_basename
448   = do  let
449                 odir = objectDir dflags
450                 osuf = objectSuf dflags
451         
452                 obj_basename | Just dir <- odir = dir </> mod_basename
453                              | otherwise        = basename
454
455         return (obj_basename <.> osuf)
456
457 -- | Constructs the filename of a .hi file for a given source file.
458 -- Does /not/ check whether the .hi file exists
459 mkHiPath
460   :: DynFlags
461   -> FilePath           -- the filename of the source file, minus the extension
462   -> String             -- the module name with dots replaced by slashes
463   -> IO FilePath
464 mkHiPath dflags basename mod_basename
465   = do  let
466                 hidir = hiDir dflags
467                 hisuf = hiSuf dflags
468
469                 hi_basename | Just dir <- hidir = dir </> mod_basename
470                             | otherwise         = basename
471
472         return (hi_basename <.> hisuf)
473
474
475 -- -----------------------------------------------------------------------------
476 -- Filenames of the stub files
477
478 -- We don't have to store these in ModLocations, because they can be derived
479 -- from other available information, and they're only rarely needed.
480
481 mkStubPaths
482   :: DynFlags
483   -> ModuleName
484   -> ModLocation
485   -> (FilePath,FilePath,FilePath)
486
487 mkStubPaths dflags mod location
488   = let
489         stubdir = stubDir dflags
490
491         mod_basename = moduleNameSlashes mod
492         src_basename = dropExtension $ expectJust "mkStubPaths" 
493                                                   (ml_hs_file location)
494
495         stub_basename0
496             | Just dir <- stubdir = dir </> mod_basename
497             | otherwise           = src_basename
498
499         stub_basename = stub_basename0 ++ "_stub"
500
501         -- this is the filename we're going to use when
502         -- \#including the stub_h file from the .hc file.
503         -- Without -stubdir, we just #include the basename
504         -- (eg. for a module A.B, we #include "B_stub.h"),
505         -- relying on the fact that we add an implicit -I flag
506         -- for the directory in which the source file resides
507         -- (see DriverPipeline.hs).  With -stubdir, we
508         -- \#include "A/B.h", assuming that the user has added
509         -- -I<dir> along with -stubdir <dir>.
510         include_basename
511                 | Just _ <- stubdir = mod_basename 
512                 | otherwise         = takeFileName src_basename
513      in
514         (stub_basename <.> "c",
515          stub_basename <.> "h",
516          (include_basename ++ "_stub") <.> "h")
517         -- the _stub.o filename is derived from the ml_obj_file.
518
519 -- -----------------------------------------------------------------------------
520 -- findLinkable isn't related to the other stuff in here, 
521 -- but there's no other obvious place for it
522
523 findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
524 findObjectLinkableMaybe mod locn
525    = do let obj_fn = ml_obj_file locn
526         maybe_obj_time <- modificationTimeIfExists obj_fn
527         case maybe_obj_time of
528           Nothing -> return Nothing
529           Just obj_time -> liftM Just (findObjectLinkable mod obj_fn obj_time)
530
531 -- Make an object linkable when we know the object file exists, and we know
532 -- its modification time.
533 findObjectLinkable :: Module -> FilePath -> ClockTime -> IO Linkable
534 findObjectLinkable mod obj_fn obj_time = do
535   let stub_fn = (dropExtension obj_fn ++ "_stub") <.> "o"
536   stub_exist <- doesFileExist stub_fn
537   if stub_exist
538         then return (LM obj_time mod [DotO obj_fn, DotO stub_fn])
539         else return (LM obj_time mod [DotO obj_fn])
540
541 -- -----------------------------------------------------------------------------
542 -- Error messages
543
544 cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
545 cannotFindModule = cantFindErr (sLit "Could not find module")
546
547 cannotFindInterface  :: DynFlags -> ModuleName -> FindResult -> SDoc
548 cannotFindInterface = cantFindErr (sLit "Failed to load interface for")
549
550 cantFindErr :: LitString -> DynFlags -> ModuleName -> FindResult -> SDoc
551 cantFindErr cannot_find _dflags mod_name (FoundMultiple pkgs)
552   = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon) 2 (
553        sep [ptext (sLit "it was found in multiple packages:"),
554                 hsep (map (text.packageIdString) pkgs)]
555     )
556 cantFindErr cannot_find dflags mod_name find_result
557   = hang (ptext cannot_find <+> quotes (ppr mod_name) <> colon)
558        2 more_info
559   where
560     more_info
561       = case find_result of
562             NoPackage pkg
563                 -> ptext (sLit "no package matching") <+> quotes (ppr pkg) <+>
564                    ptext (sLit "was found")
565
566             NotFound files mb_pkg mod_hiddens pkg_hiddens
567                 | Just pkg <- mb_pkg, pkg /= thisPackage dflags
568                 -> not_found_in_package pkg files
569
570                 | null files && null mod_hiddens && null pkg_hiddens
571                 -> ptext (sLit "it is not a module in the current program, or in any known package.")
572
573                 | otherwise
574                 -> vcat (map pkg_hidden pkg_hiddens) $$
575                    vcat (map mod_hidden mod_hiddens) $$ 
576                    tried_these files
577
578             NotFoundInPackage pkg
579                 -> ptext (sLit "it is not in package") <+> quotes (ppr pkg)
580
581             _ -> panic "cantFindErr"
582
583     build_tag = buildTag dflags
584
585     not_found_in_package pkg files
586        | build_tag /= ""
587        = let
588             build = if build_tag == "p" then "profiling"
589                                         else "\"" ++ build_tag ++ "\""
590          in
591          ptext (sLit "Perhaps you haven't installed the ") <> text build <>
592          ptext (sLit " libraries for package ") <> quotes (ppr pkg) <> char '?' $$
593          tried_these files
594
595        | otherwise
596        = ptext (sLit "There are files missing in the ") <> quotes (ppr pkg) <>
597          ptext (sLit " package,") $$
598          ptext (sLit "try running 'ghc-pkg check'.") $$
599          tried_these files
600
601     tried_these files
602         | null files = empty
603         | verbosity dflags < 3 =
604               ptext (sLit "Use -v to see a list of the files searched for.")
605         | otherwise =
606                hang (ptext (sLit "locations searched:")) 2 $ vcat (map text files)
607         
608     pkg_hidden pkg =
609         ptext (sLit "it is a member of the hidden package") <+> quotes (ppr pkg)
610
611     mod_hidden pkg =
612         ptext (sLit "it is a hidden module in the package") <+> quotes (ppr pkg)
613 \end{code}