[project @ 2003-07-17 12:04:50 by simonmar]
[ghc-hetmet.git] / ghc / compiler / compMan / CompManager.lhs
index 517b824..9f79a16 100644 (file)
@@ -57,7 +57,7 @@ where
 #include "HsVersions.h"
 
 import DriverPipeline  ( CompResult(..), preprocess, compile, link )
-import DriverState     ( v_Output_file )
+import DriverState     ( v_Output_file, v_NoHsMain )
 import DriverPhases
 import DriverUtil
 import Finder
@@ -232,9 +232,9 @@ moduleNameToModule hpt mn = do
     _not_a_home_module -> do
          maybe_stuff <- findModule mn
          case maybe_stuff of
-           Nothing -> throwDyn (CmdLineError ("can't find module `"
+           Left _ -> throwDyn (CmdLineError ("can't find module `"
                                    ++ moduleNameUserString mn ++ "'"))
-           Just (m,_) -> return m
+           Right (m,_) -> return m
 
 cmGetContext :: CmState -> IO ([String],[String])
 cmGetContext CmState{ic=ic} = 
@@ -571,7 +571,7 @@ cmLoadModules cmstate1 dflags mg2unsorted
                    valid_old_linkables
 
         when (verb >= 2) $
-           putStrLn (showSDoc (text "Stable modules:" 
+           hPutStrLn stderr (showSDoc (text "Stable modules:" 
                                <+> sep (map (text.moduleNameUserString) stable_mods)))
 
        -- Unload any modules which are going to be re-linked this
@@ -638,15 +638,22 @@ cmLoadModules cmstate1 dflags mg2unsorted
              -- clean up after ourselves
              cleanTempFilesExcept verb (ppFilesFromSummaries modsDone)
 
-             -- issue a warning for the confusing case where the user said '-o foo'
-             -- but we're not going to do any linking.
              ofile <- readIORef v_Output_file
-             when (ghci_mode == Batch && isJust ofile && not a_root_is_Main
+             no_hs_main <- readIORef v_NoHsMain
+
+             -- Issue a warning for the confusing case where the user
+             -- said '-o foo' but we're not going to do any linking.
+             -- We attempt linking if either (a) one of the modules is
+             -- called Main, or (b) the user said -no-hs-main, indicating
+             -- that main() is going to come from somewhere else.
+             --
+             let do_linking = a_root_is_Main || no_hs_main
+             when (ghci_mode == Batch && isJust ofile && not do_linking
                     && verb > 0) $
                 hPutStrLn stderr "Warning: output was redirected with -o, but no output will be generated\nbecause there is no Main module."
 
              -- link everything together
-              linkresult <- link ghci_mode dflags a_root_is_Main (hptLinkables hpt3)
+              linkresult <- link ghci_mode dflags do_linking hpt3 
 
              cmLoadFinish Succeeded linkresult 
                           hpt3 modsDone ghci_mode pcs3
@@ -673,7 +680,7 @@ cmLoadModules cmstate1 dflags mg2unsorted
              cleanTempFilesExcept verb (ppFilesFromSummaries mods_to_keep)
 
              -- Link everything together
-              linkresult <- link ghci_mode dflags False (hptLinkables hpt4)
+              linkresult <- link ghci_mode dflags False hpt4
 
              cmLoadFinish Failed linkresult 
                           hpt4 mods_to_keep ghci_mode pcs3
@@ -704,12 +711,21 @@ ppFilesFromSummaries summaries
   = [ fn | Just fn <- map toPpFile summaries ]
   where
    toPpFile sum
-     | hspp /= ml_hs_file loc = hspp
-     | otherwise              = Nothing
+     | not (isSameFilePath hspp hs) = hspp
+     | otherwise                    = Nothing
     where
       loc  = ms_location sum
       hspp = ml_hspp_file loc
+      hs   = ml_hs_file loc
+      
+       -- better make extra sure 'a' and 'b' are in canonical form 
+       -- before using this equality test.
+      isSameFilePath a b = fmap normalise a == fmap normalise b
 
+      -- a hack, because sometimes we strip off the leading "./" from a 
+      -- a filename.
+      normalise ('.':'/':f) = f
+      normalise f = f
 
 -----------------------------------------------------------------------------
 -- getValidLinkables
@@ -1162,15 +1178,13 @@ downsweep roots old_summaries
         getSummary (currentMod,nm)
            = do found <- findModule nm
                case found of
-                  Just (mod, location) -> do
+                  Right (mod, location) -> do
                        let old_summary = findModInSummaries old_summaries mod
                        summarise mod location old_summary
 
-                  Nothing -> 
-                       throwDyn (CmdLineError 
-                                   ("can't find module `" 
-                                     ++ showSDoc (ppr nm) ++ "' (while processing " 
-                                    ++ show currentMod ++ ")"))
+                  Left files -> do
+                       dflags <- getDynFlags
+                       throwDyn (noModError dflags currentMod nm files)
 
         -- loop invariant: env doesn't contain package modules
         loop :: [(FilePath,ModuleName)] -> ModuleEnv ModSummary -> IO [ModSummary]
@@ -1191,6 +1205,18 @@ downsweep roots old_summaries
                 loop new_imps (extendModuleEnvList env 
                                [ (ms_mod s, s) | s <- new_home_summaries ])
 
+-- ToDo: we don't have a proper line number for this error
+noModError dflags loc mod_nm files = ProgramError (showSDoc (
+  hang (text loc <> colon) 4 $
+    (text "Can't find module" <+> quotes (ppr mod_nm) $$ extra)
+  ))
+  where
+   extra
+    | verbosity dflags < 3 =
+        text "(use -v to see a list of the files searched for)"
+    | otherwise =
+        hang (ptext SLIT("locations searched:")) 4 (vcat (map text files))
+
 -----------------------------------------------------------------------------
 -- Summarising modules
 
@@ -1209,12 +1235,11 @@ summariseFile file
    = do hspp_fn <- preprocess file
         (srcimps,imps,mod_name) <- getImportsFromFile hspp_fn
 
-        let (path, basename, ext) = splitFilename3 file
+        let (basename, ext) = splitFilename file
             -- 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 True{-is a root-}
-                               path basename ext
+       (mod, location) <- mkHomeModLocation mod_name "." basename ext
 
         src_timestamp
            <- case ml_hs_file location of