[project @ 2003-07-18 13:18:06 by simonmar]
authorsimonmar <unknown>
Fri, 18 Jul 2003 13:18:07 +0000 (13:18 +0000)
committersimonmar <unknown>
Fri, 18 Jul 2003 13:18:07 +0000 (13:18 +0000)
Revision to the filename policy changes of yesterday.  This fixes the
broken stage2 and library builds.

The new story is this:

  A Haskell source filename should take the form

<path>/<basename>.<extension>

  where

<path>      is any directory
<basename>  is the name of the module, with dots replaced by slashes.
<extension> is ".hs" or ".lhs".

  given a source filename in this form, GHC will produce object and
  interface files named respectively:

        <hidir>/<basename>.<hisuf>
<odir>/<basename>.<osuf>

  where

<hidir>   is the value of the -hidir flag, if one was given, or
  the value of <path> from the source file otherwise.

<odir>    the same, for the -odir flag.

        <osuf>   the object suffix (settable with the -osuf flag)
<hisuf>   the hi suffix (settable with the -hisuf flag)

For example, if I have a module A.B.C, in source file foo/A/B/C.hs,
then GHC will create foo/A/B/C.hi and foo/A/B/C.o.

If GHC is given a source filename which is *not* of the form
<path>/<basename>.<extension>, then it uses a different strategy.
This happens if the filename does not follow the module name.  In this
case, GHC will set <path> to be the directory in which the source file
resides, and <basename> to the module name with dots replaced by
slashes, and then use the rules above.

For example, if we put module A.B.C in foo/bar/baz.hs, then GHC will
produce foo/bar/A/B/C.o and foo/bar/A/B/C.hi.

ghc/compiler/compMan/CompManager.lhs
ghc/compiler/main/DriverMkDepend.hs
ghc/compiler/main/DriverPipeline.hs
ghc/compiler/main/Finder.lhs

index 9f79a16..b321497 100644 (file)
@@ -1235,11 +1235,10 @@ summariseFile file
    = do hspp_fn <- preprocess file
         (srcimps,imps,mod_name) <- getImportsFromFile hspp_fn
 
-        let (basename, ext) = splitFilename file
-            -- GHC.Prim doesn't exist physically, so don't go looking for it.
+        let -- GHC.Prim doesn't exist physically, so don't go looking for it.
             the_imps = filter (/= gHC_PRIM_Name) imps
 
-       (mod, location) <- mkHomeModLocation mod_name "." basename ext
+       (mod, location) <- mkHomeModLocation mod_name file
 
         src_timestamp
            <- case ml_hs_file location of 
index 3faa06c..f01faf3 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverMkDepend.hs,v 1.29 2003/07/17 12:04:53 simonmar Exp $
+-- $Id: DriverMkDepend.hs,v 1.30 2003/07/18 13:18:07 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -133,25 +133,23 @@ beginMkDependHS = do
 doMkDependHSPhase basename suff input_fn
  = do src <- readFile input_fn
       let (import_sources, import_normals, mod_name) = getImports src
-      (_, location') <- mkHomeModLocation mod_name "." basename suff
+      let orig_fn = basename ++ '.':suff
+      (_, location') <- mkHomeModLocation mod_name orig_fn
 
       -- take -ohi into account if present
       ohi <- readIORef v_Output_hi
       let location | Just fn <- ohi = location'{ ml_hi_file = fn }
                   | otherwise      = location'
 
-      let orig_fn = basename ++ '.':suff
       deps_sources <- mapM (findDependency True  orig_fn) import_sources
       deps_normals <- mapM (findDependency False orig_fn) import_normals
       let deps = deps_sources ++ deps_normals
 
       osuf <- readIORef v_Object_suf
-
       extra_suffixes <- readIORef v_Dep_suffixes
-      let suffixes = osuf : map (++ ('_':osuf)) extra_suffixes
-          ofiles = map (\suf -> basename ++ '.':suf) suffixes
-
-      objs <- mapM odir_ify ofiles
+      let suffixes = map (++ ('_':osuf)) extra_suffixes
+         obj_file = ml_obj_file location
+          objs = obj_file : map (replaceFilenameSuffix obj_file) suffixes
 
        -- Handle for file that accumulates dependencies 
       hdl <- readIORef v_Dep_tmp_hdl
index 24c804e..81ef08d 100644 (file)
@@ -576,7 +576,7 @@ runPhase Hsc basename suff input_fn get_output_fn _maybe_loc = do
               getImportsFromFile input_fn
 
   -- build a ModLocation to pass to hscMain.
-       (mod, location') <- mkHomeModLocation mod_name "." basename suff
+       (mod, location') <- mkHomeModLocation mod_name (basename ++ '.':suff)
 
   -- take -ohi into account if present
        ohi <- readIORef v_Output_hi
index 8564ef0..f3c8597 100644 (file)
@@ -13,8 +13,7 @@ module Finder (
     findPackageModule,  -- :: ModuleName
                        --   -> IO (Either [FilePath] (Module, ModLocation))
 
-    mkHomeModLocation, -- :: ModuleName -> String -> FilePath 
-                       --      -> IO ModLocation
+    mkHomeModLocation, -- :: ModuleName -> FilePath -> IO ModLocation
 
     findLinkable,      -- :: ModuleName -> ModLocation -> IO (Maybe Linkable)
 
@@ -29,7 +28,7 @@ import Module
 import UniqFM          ( filterUFM )
 import HscTypes                ( Linkable(..), Unlinked(..) )
 import DriverState
-import DriverUtil      ( split_longest_prefix, splitFilename3 )
+import DriverUtil
 import FastString
 import Config
 import Util
@@ -121,8 +120,8 @@ maybeHomeModule mod_name = do
 
    let
      source_exts = 
-      [ ("hs",   mkHomeModLocation mod_name)
-      , ("lhs",  mkHomeModLocation mod_name)
+      [ ("hs",   mkHomeModLocationSearched mod_name)
+      , ("lhs",  mkHomeModLocationSearched mod_name)
       ]
      
      hi_exts = [ (hisuf,  mkHiOnlyModLocation hisuf mod_name) ]
@@ -266,7 +265,7 @@ hiOnlyModLocation path basename hisuf
 --
 -- path
 --      (a): The search path component where the source file was found.
---      (b) and (c): Nothing
+--      (b) and (c): "."
 --
 -- src_basename
 --      (a): dots_to_slashes (moduleNameUserString mod_name)
@@ -275,7 +274,23 @@ hiOnlyModLocation path basename hisuf
 -- ext
 --     The filename extension of the source file (usually "hs" or "lhs").
 
-mkHomeModLocation mod_name path src_basename ext = do
+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