[project @ 2003-07-18 13:18:06 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / Finder.lhs
index 673bdb9..f3c8597 100644 (file)
 
 \begin{code}
 module Finder (
-    initFinder,        -- :: PackageConfigInfo -> IO (), 
-    findModule         -- :: ModuleName -> IO (Maybe (Module, ModuleLocation))
+    flushFinderCache,  -- :: IO ()
+
+    findModule,                -- :: ModuleName 
+                       --   -> IO (Either [FilePath] (Module, ModLocation))
+
+    findPackageModule,  -- :: ModuleName
+                       --   -> IO (Either [FilePath] (Module, ModLocation))
+
+    mkHomeModLocation, -- :: ModuleName -> FilePath -> IO ModLocation
+
+    findLinkable,      -- :: ModuleName -> ModLocation -> IO (Maybe Linkable)
+
+    hiBootExt,         -- :: String
+    hiBootVerExt,      -- :: String
+
   ) where
 
 #include "HsVersions.h"
 
-import HscTypes                ( ModuleLocation(..) )
-import CmStaticInfo
-import DriverPhases
-import DriverState
 import Module
-import FiniteMap
+import UniqFM          ( filterUFM )
+import HscTypes                ( Linkable(..), Unlinked(..) )
+import DriverState
+import DriverUtil
+import FastString
+import Config
 import Util
 
-import IOExts
-import Directory
+import DATA_IOREF      ( IORef, writeIORef, readIORef )
+
 import List
+import Directory
 import IO
 import Monad
-import Outputable      ( showSDoc, ppr )       -- debugging only
-\end{code}
 
-The Finder provides a thin filesystem abstraction to the rest of the
-compiler.  For a given module, it knows (a) which package the module
-lives in, so it can make a Module from a ModuleName, and (b) where the
-source, interface, and object files for a module live.
-
-\begin{code}
-
--- v_PkgDirCache caches contents of package directories, never expunged
-GLOBAL_VAR(v_PkgDirCache,    error "no pkg cache!",  FiniteMap String (PackageName, FilePath))
-
--- v_HomeDirCache caches contents of home directories, 
--- expunged whenever we create a new finder.
-GLOBAL_VAR(v_HomeDirCache,   Nothing,  Maybe (FiniteMap String FilePath))
-
-
-initFinder :: PackageConfigInfo -> IO ()
-initFinder pkgs 
-  = do {       -- expunge our home cache
-       ; writeIORef v_HomeDirCache Nothing
-               -- lazilly fill in the package cache
-       ; writeIORef v_PkgDirCache (unsafePerformIO (newPkgCache pkgs))
-       
--- Debug output
---     ; pkg_dbg_info <- readIORef v_PkgDirCache
---     ; putStrLn (unlines (map show (fmToList pkg_dbg_info)))
-       }
-
-findModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
-findModule name
-  = do         { hPutStr stderr ("findModule: " ++ moduleNameUserString name ++ " ... ")
-       ; maybe_m <- findModule_wrk name
-       ; case maybe_m of
-            Nothing -> hPutStrLn stderr "Not Found"
-            Just mm -> hPutStrLn stderr (showSDoc (ppr (snd mm)))
-       ; return maybe_m
-       }
-
-findModule_wrk :: ModuleName -> IO (Maybe (Module, ModuleLocation))
-findModule_wrk name
-  = do { j <- maybeHomeModule name
-       ; case j of
-           Just home_module -> return (Just home_module)
-           Nothing              -> maybePackageModule name
-       }
-
-maybeHomeModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
+-- -----------------------------------------------------------------------------
+-- The Finder
+
+-- The Finder provides a thin filesystem abstraction to the rest of the
+-- compiler.  For a given module, it knows (a) whether the module lives
+-- in the home package or in another package, so it can make a Module
+-- from a ModuleName, and (b) where the source, interface, and object
+-- files for a module live.
+-- 
+-- It does *not* know which particular package a module lives in, because
+-- that information is only contained in the interface file.
+
+-- -----------------------------------------------------------------------------
+-- The finder's cache
+
+GLOBAL_VAR(finder_cache, emptyModuleEnv, ModuleEnv (Module,ModLocation))
+
+-- remove all the home modules from the cache; package modules are
+-- assumed to not move around during a session.
+flushFinderCache :: IO ()
+flushFinderCache = do
+  fm <- readIORef finder_cache
+  writeIORef finder_cache (filterUFM (not . isHomeModule . fst) fm)
+
+addToFinderCache :: ModuleName -> (Module,ModLocation) -> IO ()
+addToFinderCache mod_name stuff = do
+  fm <- readIORef finder_cache
+  writeIORef finder_cache (extendModuleEnvByName fm mod_name stuff)
+
+lookupFinderCache :: ModuleName -> IO (Maybe (Module,ModLocation))
+lookupFinderCache mod_name = do
+  fm <- readIORef finder_cache
+  return $! lookupModuleEnvByName fm mod_name
+
+-- -----------------------------------------------------------------------------
+-- Locating modules
+
+-- This is the main interface to the finder, which maps ModuleNames to
+-- Modules and ModLocations.
+--
+-- The Module contains one crucial bit of information about a module:
+-- whether it lives in the current ("home") package or not (see Module
+-- for more details).
+--
+-- The ModLocation contains the names of all the files associated with
+-- that module: its source file, .hi file, object file, etc.
+
+findModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
+findModule name = do
+  r <- lookupFinderCache name
+  case r of
+   Just result -> return (Right result)
+   Nothing -> do  
+       j <- maybeHomeModule name
+       case j of
+        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 (Right result)
+   Nothing     -> findPackageMod name
+
+hiBootExt = "hi-boot"
+hiBootVerExt = "hi-boot-" ++ cHscIfaceFileVersion
+
+maybeHomeModule :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
 maybeHomeModule mod_name = do
-   home_cache <- readIORef v_HomeDirCache
-
-   home_map <- 
-     case home_cache of
-       Nothing -> do
-          -- populate the home dir cache, using the import path (the import 
-          -- path is changed by -i flags on the command line, and defaults 
-          -- to ["."]).
-          home_imports <- readIORef v_Import_paths
-          let extendFM fm path = do
-                  contents <- getDirectoryContents' path
-                   let clean_contents = filter isUsefulFile contents
-                  return (addListToFM fm (zip clean_contents (repeat path)))
-          home_map <- foldM extendFM emptyFM home_imports
-          writeIORef v_HomeDirCache (Just home_map)
-          return home_map
-
-        Just home_map -> return home_map
-
-   let basename = moduleNameString mod_name
-       hs  = basename ++ ".hs"
-       lhs = basename ++ ".lhs"
-
-   case lookupFM home_map hs of {
-       Just path -> mkHomeModuleLocn mod_name (path ++ '/':basename) hs;
-       Nothing ->
-
-   case lookupFM home_map lhs of {
-       Just path ->  mkHomeModuleLocn mod_name (path ++ '/':basename) lhs;
-       Nothing -> return Nothing
-
-   }}
-
-mkHomeModuleLocn mod_name basename source_fn = do
-
-   -- figure out the .hi file name: it lives in the same dir as the
-   -- source, unless there's a -ohi flag on the command line.
-   ohi    <- readIORef v_Output_hi
-   hisuf  <- readIORef v_Hi_suf
-   let hifile = case ohi of
-                  Nothing -> basename ++ '.':hisuf
-                  Just fn -> fn
-
-   -- figure out the .o file name.  It also lives in the same dir
-   -- as the source, but can be overriden by a -odir flag.
-   o_file <- odir_ify (basename ++ '.':phaseInputExt Ln) >>= osuf_ify
-
-   return (Just (mkHomeModule mod_name,
-                 ModuleLocation{
-                   hs_file  = source_fn,
-                   hi_file  = hifile,
-                   obj_file = o_file
-                }
-       ))
-
-
-newPkgCache :: [Package] -> IO (FiniteMap String (PackageName, FilePath))
-newPkgCache pkgs = do
-    let extendFM fm pkg = do
-           let dirs = import_dirs pkg
-               pkg_name = _PK_ (name pkg)
-           let addDir fm dir = do
-                   contents <- getDirectoryContents' dir
-                   let clean_contents = filter isUsefulFile contents
-                   return (addListToFM fm (zip clean_contents 
-                                              (repeat (pkg_name,dir))))
-           foldM addDir fm dirs
-    
-    pkg_map <- foldM extendFM emptyFM pkgs
-    return pkg_map
-
-
-maybePackageModule :: ModuleName -> IO (Maybe (Module, ModuleLocation))
-maybePackageModule mod_name = do
-  pkg_cache <- readIORef v_PkgDirCache
-
-  -- hi-suffix for packages depends on the build tag.
+   home_path <- readIORef v_Import_paths
+   hisuf     <- readIORef v_Hi_suf
+   mode      <- readIORef v_GhcMode
+
+   let
+     source_exts = 
+      [ ("hs",   mkHomeModLocationSearched mod_name)
+      , ("lhs",  mkHomeModLocationSearched mod_name)
+      ]
+     
+     hi_exts = [ (hisuf,  mkHiOnlyModLocation hisuf mod_name) ]
+     
+     boot_exts =
+       [ (hiBootVerExt, mkHiOnlyModLocation hisuf mod_name)
+       , (hiBootExt,    mkHiOnlyModLocation hisuf mod_name)
+       ]
+
+       -- In compilation manager modes, we look for source files in the home
+       -- package because we can compile these automatically.  In one-shot
+       -- compilation mode we look for .hi and .hi-boot files only.
+       --
+       -- When generating dependencies, we're interested in either category.
+       --
+     exts
+         | mode == DoMkDependHS   = hi_exts ++ source_exts ++ boot_exts
+         | isCompManagerMode mode = source_exts
+        | otherwise {-one-shot-} = hi_exts ++ boot_exts
+
+   searchPathExts home_path mod_name exts
+       
+-- -----------------------------------------------------------------------------
+-- Looking for a package module
+
+findPackageMod :: ModuleName -> IO (Either [FilePath] (Module, ModLocation))
+findPackageMod mod_name = do
+  mode     <- readIORef v_GhcMode
+  imp_dirs <- getPackageImportPath -- including the 'auto' ones
+
+   -- hi-suffix for packages depends on the build tag.
   package_hisuf <-
        do tag <- readIORef v_Build_tag
           if null tag
                then return "hi"
                else return (tag ++ "_hi")
 
-  let basename = moduleNameString mod_name
-      hi = basename ++ '.':package_hisuf
-
-  case lookupFM pkg_cache hi of
-       Nothing -> return Nothing
-       Just (pkg_name,path) -> 
-           return (Just (mkModule mod_name pkg_name,
-                         ModuleLocation{ 
-                               hs_file  = "error:_package_module;_no_source",
-                               hi_file  = path ++ '/':hi,
-                               obj_file = "error:_package_module;_no_object"
-                          }
-                  ))
-
-isUsefulFile fn
-   = let suffix = (reverse . takeWhile (/= '.') . reverse) fn
-     in  suffix `elem` ["hi", "hs", "lhs", "hi-boot", "hi-boot-5"]
-
-getDirectoryContents' d
-   = IO.catch (getDirectoryContents d)
-         (\_ -> do hPutStr stderr 
-                         ("WARNING: error while reading directory " ++ d)
-                   return []
-         )
-        
+  let
+     hi_exts =
+        [ (package_hisuf, mkPackageModLocation package_hisuf mod_name) ]
+
+     source_exts = 
+       [ ("hs",   mkPackageModLocation package_hisuf mod_name)
+       , ("lhs",  mkPackageModLocation package_hisuf mod_name)
+       ]
+     
+     -- mkdependHS needs to look for source files in packages too, so
+     -- that we can make dependencies between package before they have
+     -- been built.
+     exts 
+      | mode == DoMkDependHS = hi_exts ++ source_exts
+      | otherwise = hi_exts
+
+      -- we never look for a .hi-boot file in an external package;
+      -- .hi-boot files only make sense for the home package.
+  searchPathExts imp_dirs mod_name exts
+
+-- -----------------------------------------------------------------------------
+-- General path searching
+
+searchPathExts
+  :: [FilePath]                -- paths to search
+  -> ModuleName                -- module name
+  -> [ (
+       String,                                         -- suffix
+       String -> String -> String -> IO (Module, ModLocation)  -- action
+       )
+     ] 
+  -> IO (Either [FilePath] (Module, ModLocation))
+
+searchPathExts path mod_name exts = search to_search
+  where
+    basename = dots_to_slashes (moduleNameUserString mod_name)
+
+    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
+
+mkHiOnlyModLocation hisuf mod_name path basename _ext = do
+  -- basename == dots_to_slashes (moduleNameUserString mod_name)
+  loc <- hiOnlyModLocation path basename hisuf
+  let result = (mkHomeModule mod_name, loc)
+  addToFinderCache mod_name result
+  return result
+
+mkPackageModLocation hisuf mod_name path basename _ext = do
+  -- basename == dots_to_slashes (moduleNameUserString mod_name)
+  loc <- hiOnlyModLocation path basename hisuf
+  let result = (mkPackageModule mod_name, loc)
+  addToFinderCache mod_name result
+  return result
+
+hiOnlyModLocation path basename hisuf 
+ = do { obj_fn <- mkObjPath path basename ;
+        return (ModLocation{ ml_hspp_file = Nothing,
+                            ml_hs_file   = Nothing,
+                            ml_hi_file   = path ++ '/':basename ++ '.':hisuf,
+                               -- Remove the .hi-boot suffix from
+                               -- hi_file, if it had one.  We always
+                               -- want the name of the real .hi file
+                               -- in the ml_hi_file field.
+                            ml_obj_file  = obj_fn
+                 })}
+
+-- -----------------------------------------------------------------------------
+-- Constructing a home module location
+
+-- This is where we construct the ModLocation for a module in the home
+-- package, for which we have a source file.  It is called from three
+-- places:
+--
+--  (a) Here in the finder, when we are searching for a module to import,
+--      using the search path (-i option).
+--
+--  (b) The compilation manager, when constructing the ModLocation for
+--      a "root" module (a source file named explicitly on the command line
+--      or in a :load command in GHCi).
+--
+--  (c) The driver in one-shot mode, when we need to construct a
+--      ModLocation for a source file named on the command-line.
+--
+-- Parameters are:
+--
+-- mod_name
+--      The name of the module
+--
+-- path
+--      (a): The search path component where the source file was found.
+--      (b) and (c): "."
+--
+-- src_basename
+--      (a): dots_to_slashes (moduleNameUserString mod_name)
+--      (b) and (c): The filename of the source file, minus its extension
+--
+-- ext
+--     The filename extension of the source file (usually "hs" or "lhs").
+
+mkHomeModLocation mod_name src_filename = do
+   let mod_basename = dots_to_slashes (moduleNameUserString mod_name)
+       (basename,extension) = splitFilename src_filename
+
+   case my_prefix_match (reverse mod_basename) (reverse basename) of
+       Just ""   ->
+          mkHomeModLocationSearched mod_name "."  mod_basename extension
+       Just rest -> do
+          let path = reverse (dropWhile (=='/') rest)
+          mkHomeModLocationSearched mod_name path mod_basename extension
+       Nothing   -> do
+         hPutStrLn stderr ("Warning: " ++ src_filename ++
+                                ": filename and module name do not match")
+         let (dir,basename,ext) = splitFilename3 src_filename
+         mkHomeModLocationSearched mod_name dir basename ext
+
+mkHomeModLocationSearched mod_name path src_basename ext = do
+   hisuf  <- readIORef v_Hi_suf
+   hidir  <- readIORef v_Hi_dir
+
+   let mod_basename = dots_to_slashes (moduleNameUserString mod_name)
+
+   obj_fn <- mkObjPath path mod_basename
+
+   let  -- hi filename, always follows the module name
+       hi_path | Just d <- hidir = d
+              | otherwise       = path
+
+       hi_fn = hi_path ++ '/':mod_basename ++ '.':hisuf
+
+       -- source filename
+       source_fn = path ++ '/':src_basename ++ '.':ext
+
+       result = ( mkHomeModule mod_name,
+                 ModLocation{ ml_hspp_file = Nothing,
+                              ml_hs_file   = Just source_fn,
+                              ml_hi_file   = hi_fn,
+                              ml_obj_file  = obj_fn,
+                      })
+
+   addToFinderCache mod_name result
+   return result
+
+mkObjPath :: FilePath -> String -> IO FilePath
+-- Construct the filename of a .o file.
+-- Does *not* check whether the .o file exists
+mkObjPath path basename
+  = do  odir   <- readIORef v_Output_dir
+       osuf   <- readIORef v_Object_suf
+
+       let obj_path | Just d <- odir = d
+                    | otherwise      = path
+
+        return (obj_path ++ '/':basename ++ '.':osuf)
+
+-- -----------------------------------------------------------------------------
+-- findLinkable isn't related to the other stuff in here, 
+-- but there's no other obvious place for it
+
+findLinkable :: ModuleName -> ModLocation -> IO (Maybe Linkable)
+findLinkable mod locn
+   = do let obj_fn = ml_obj_file locn
+       obj_exist <- doesFileExist obj_fn
+        if not obj_exist 
+         then return Nothing 
+         else 
+         do let stub_fn = case splitFilename3 obj_fn of
+                             (dir, base, ext) -> dir ++ "/" ++ base ++ "_stub.o"
+            stub_exist <- doesFileExist stub_fn
+            obj_time <- getModificationTime obj_fn
+            if stub_exist
+             then return (Just (LM obj_time mod [DotO obj_fn, DotO stub_fn]))
+             else return (Just (LM obj_time mod [DotO obj_fn]))
+
+-- -----------------------------------------------------------------------------
+-- Utils
+
+dots_to_slashes = map (\c -> if c == '.' then '/' else c)
+
 \end{code}