[project @ 2000-12-12 12:10:08 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
index 6ebf319..c0951ac 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverPipeline.hs,v 1.21 2000/11/13 17:12:37 sewardj Exp $
+-- $Id: DriverPipeline.hs,v 1.40 2000/12/07 16:39:40 simonmar Exp $
 --
 -- GHC Driver
 --
@@ -22,8 +22,9 @@ module DriverPipeline (
 
 #include "HsVersions.h"
 
-import CmSummarise
-import CmLink
+import CmStaticInfo ( GhciMode(..) )
+import CmTypes
+import GetImports
 import DriverState
 import DriverUtil
 import DriverMkDepend
@@ -34,10 +35,12 @@ import TmpFiles
 import HscTypes
 import Outputable
 import Module
+import ErrUtils
 import CmdLineOpts
 import Config
 import Util
 
+import Time            ( getClockTime )
 import Directory
 import System
 import IOExts
@@ -92,7 +95,7 @@ getGhcMode flags
 -- what the suffix of the intermediate files should be, etc.
 
 -- The following compilation pipeline algorithm is fairly hacky.  A
--- better way to do this would be to express the whole comilation as a
+-- better way to do this would be to express the whole compilation as a
 -- data flow DAG, where the nodes are the intermediate files and the
 -- edges are the compilation phases.  This framework would also work
 -- nicely if a haskell dependency generator was included in the
@@ -108,18 +111,19 @@ getGhcMode flags
 -- concurrently, automatically taking advantage of extra processors on
 -- the host machine.  For example, when compiling two Haskell files
 -- where one depends on the other, the data flow graph would determine
--- that the C compiler from the first comilation can be overlapped
--- with the hsc comilation for the second file.
+-- that the C compiler from the first compilation can be overlapped
+-- with the hsc compilation for the second file.
 
 data IntermediateFileType
   = Temporary
   | Persistent
-  deriving (Eq)
+  deriving (Eq, Show)
 
 genPipeline
    :: GhcMode          -- when to stop
    -> String           -- "stop after" flag (for error messages)
    -> Bool             -- True => output is persistent
+   -> HscLang          -- preferred output language for hsc
    -> String           -- original filename
    -> IO [             -- list of phases to run for this file
             (Phase,
@@ -127,11 +131,10 @@ genPipeline
              String)                -- output file suffix
          ]     
 
-genPipeline todo stop_flag persistent_output filename
+genPipeline todo stop_flag persistent_output lang filename 
  = do
    split      <- readIORef v_Split_object_files
    mangle     <- readIORef v_Do_asm_mangling
-   lang       <- readIORef v_Hsc_Lang
    keep_hc    <- readIORef v_Keep_hc_files
    keep_raw_s <- readIORef v_Keep_raw_s_files
    keep_s     <- readIORef v_Keep_s_files
@@ -146,9 +149,9 @@ genPipeline todo stop_flag persistent_output filename
     haskellish = haskellish_suffix suffix
     cish = cish_suffix suffix
 
-   -- for a .hc file, or if the -C flag is given, we need to force lang to HscC
-    real_lang | suffix == "hc"  = HscC
-             | otherwise       = lang
+   -- for a .hc file we need to force lang to HscC
+    real_lang | start_phase == HCc  = HscC
+             | otherwise           = lang
 
    let
    ----------- -----  ----   ---   --   --  -  -  -
@@ -286,7 +289,7 @@ pipeLoop ((phase, keep, o_suffix):phases)
 run_phase Unlit _basename _suff input_fn output_fn
   = do unlit <- readIORef v_Pgm_L
        unlit_flags <- getOpts opt_L
-       run_something "Literate pre-processor"
+       runSomething "Literate pre-processor"
          ("echo '# 1 \"" ++input_fn++"\"' > "++output_fn++" && "
           ++ unlit ++ ' ':input_fn ++ " - >> " ++ output_fn)
        return True
@@ -316,8 +319,9 @@ run_phase Cpp basename suff input_fn output_fn
            let include_paths = map (\p -> "-I"++p) (cmdline_include_paths
                                                        ++ pkg_include_dirs)
 
-           verb <- is_verbose
-           run_something "C pre-processor" 
+           verb <- getVerbFlag
+
+           runSomething "C pre-processor" 
                (unwords
                           (["echo '{-# LINE 1 \"" ++ input_fn ++ "\" -}'", ">", output_fn, "&&",
                     cpp, verb] 
@@ -327,7 +331,7 @@ run_phase Cpp basename suff input_fn output_fn
                    ++ [ "-x", "c", input_fn, ">>", output_fn ]
                   ))
          else do
-           run_something "Ineffective C pre-processor"
+           runSomething "Ineffective C pre-processor"
                   ("echo '{-# LINE 1 \""  ++ input_fn ++ "\" -}' > " 
                    ++ output_fn ++ " && cat " ++ input_fn
                    ++ " >> " ++ output_fn)
@@ -338,9 +342,11 @@ run_phase Cpp basename suff input_fn output_fn
 
 run_phase MkDependHS basename suff input_fn _output_fn = do 
    src <- readFile input_fn
-   let imports = getImports src
+   let (import_sources, import_normals, module_name) = getImports src
 
-   deps <- mapM (findDependency basename) imports
+   deps_sources <- mapM (findDependency True basename)  import_sources
+   deps_normals <- mapM (findDependency False basename) import_normals
+   let deps = deps_sources ++ deps_normals
 
    osuf_opt <- readIORef v_Object_suf
    let osuf = case osuf_opt of
@@ -410,8 +416,7 @@ run_phase Hsc basename suff input_fn output_fn
        ohi    <- readIORef v_Output_hi
        hisuf  <- readIORef v_Hi_suf
        let hifile = case ohi of
-                          Nothing -> current_dir ++ "/" ++ basename
-                                       ++ "." ++ hisuf
+                          Nothing -> basename ++ '.':hisuf
                           Just fn -> fn
 
   -- figure out if the source has changed, for recompilation avoidance.
@@ -425,7 +430,8 @@ run_phase Hsc basename suff input_fn output_fn
   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
        do_recomp <- readIORef v_Recomp
        todo <- readIORef v_GhcMode
-        o_file <- odir_ify (basename ++ '.':phaseInputExt Ln)
+        o_file' <- odir_ify (basename ++ '.':phaseInputExt Ln)
+        o_file <- osuf_ify o_file'
        source_unchanged <- 
           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
             then return False
@@ -451,7 +457,8 @@ run_phase Hsc basename suff input_fn output_fn
 
   -- run the compiler!
         pcs <- initPersistentCompilerState
-       result <- hscMain dyn_flags{ hscOutName = output_fn }
+       result <- hscMain OneShot
+                          dyn_flags{ hscOutName = output_fn }
                          source_unchanged
                          location
                          Nothing        -- no iface
@@ -463,8 +470,14 @@ run_phase Hsc basename suff input_fn output_fn
 
            HscFail pcs -> throwDyn (PhaseFailed "hsc" (ExitFailure 1));
 
-           HscOK details maybe_iface maybe_stub_h maybe_stub_c 
-                       _maybe_interpreted_code pcs -> do
+            HscNoRecomp pcs details iface -> 
+               do {
+                 runSomething "Touching object file" ("touch " ++ o_file);
+                 return False;
+               };
+
+           HscRecomp pcs details iface maybe_stub_h maybe_stub_c 
+                     _maybe_interpreted_code -> do
 
            -- deal with stubs
        maybe_stub_o <- dealWithStubs basename maybe_stub_h maybe_stub_c
@@ -472,8 +485,7 @@ run_phase Hsc basename suff input_fn output_fn
                Nothing -> return ()
                Just stub_o -> add v_Ld_inputs stub_o
 
-        let keep_going = case maybe_iface of Just _ -> True; Nothing -> False
-       return keep_going
+       return True
     }
 
 -----------------------------------------------------------------------------
@@ -520,7 +532,7 @@ run_phase cc_phase _basename _suff input_fn output_fn
        mangle <- readIORef v_Do_asm_mangling
        (md_c_flags, md_regd_c_flags) <- machdepCCOpts
 
-        verb <- is_verbose
+        verb <- getVerbFlag
 
        o2 <- readIORef v_minus_o2_for_C
        let opt_flag | o2        = "-O2"
@@ -534,7 +546,7 @@ run_phase cc_phase _basename _suff input_fn output_fn
 
        excessPrecision <- readIORef v_Excess_precision
 
-       run_something "C Compiler"
+       runSomething "C Compiler"
         (unwords ([ cc, "-x", "c", cc_help, "-o", output_fn ]
                   ++ md_c_flags
                   ++ (if cc_phase == HCc && mangle
@@ -544,9 +556,6 @@ run_phase cc_phase _basename _suff input_fn output_fn
                   ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
                   ++ cc_opts
                   ++ split_opt
-#ifdef mingw32_TARGET_OS
-                   ++ [" -mno-cygwin"]
-#endif
                   ++ (if excessPrecision then [] else [ "-ffloat-store" ])
                   ++ include_paths
                   ++ pkg_extra_cc_opts
@@ -567,7 +576,7 @@ run_phase Mangle _basename _suff input_fn output_fn
            then do n_regs <- readState stolen_x86_regs
                    return [ show n_regs ]
            else return []
-       run_something "Assembly Mangler"
+       runSomething "Assembly Mangler"
        (unwords (mangler : 
                     mangler_opts
                  ++ [ input_fn, output_fn ]
@@ -591,7 +600,7 @@ run_phase SplitMangle _basename _suff input_fn _output_fn
        -- allocate a tmp file to put the no. of split .s files in (sigh)
        n_files <- newTempName "n_files"
 
-       run_something "Split Assembly File"
+       runSomething "Split Assembly File"
         (unwords [ splitter
                  , input_fn
                  , split_s_prefix
@@ -608,12 +617,12 @@ run_phase SplitMangle _basename _suff input_fn _output_fn
 -- As phase
 
 run_phase As _basename _suff input_fn output_fn
-  = do         as <- readIORef v_Pgm_a
+  = do as <- readIORef v_Pgm_a
         as_opts <- getOpts opt_a
 
         cmdline_include_paths <- readIORef v_Include_paths
         let cmdline_include_flags = map (\p -> "-I"++p) cmdline_include_paths
-        run_something "Assembler"
+        runSomething "Assembler"
           (unwords (as : as_opts
                       ++ cmdline_include_flags
                       ++ [ "-c", input_fn, "-o",  output_fn ]
@@ -637,7 +646,7 @@ run_phase SplitAs basename _suff _input_fn _output_fn
                    let output_o = newdir real_odir 
                                        (basename ++ "__" ++ show n ++ ".o")
                    real_o <- osuf_ify output_o
-                   run_something "Assembler" 
+                   runSomething "Assembler" 
                            (unwords (as : as_opts
                                      ++ [ "-c", "-o", real_o, input_s ]
                            ))
@@ -651,7 +660,7 @@ run_phase SplitAs basename _suff _input_fn _output_fn
 doLink :: [String] -> IO ()
 doLink o_files = do
     ln <- readIORef v_Pgm_l
-    verb <- is_verbose
+    verb <- getVerbFlag
     static <- readIORef v_Static
     let imp = if static then "" else "_imp"
     no_hs_main <- readIORef v_NoHsMain
@@ -685,11 +694,12 @@ doLink o_files = do
 #ifdef mingw32_TARGET_OS
     let extra_os = if static || no_hs_main
                    then []
-                   else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
-                          head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
+--                   else [ head (lib_paths (head rts_pkg)) ++ "/Main.dll_o",
+--                          head (lib_paths (head std_pkg)) ++ "/PrelMain.dll_o" ]
+                    else []
 #endif
     (md_c_flags, _) <- machdepCCOpts
-    run_something "Linker"
+    runSomething "Linker"
        (unwords
         ([ ln, verb, "-o", output_fn ]
         ++ md_c_flags
@@ -719,7 +729,11 @@ doLink o_files = do
 preprocess :: FilePath -> IO FilePath
 preprocess filename =
   ASSERT(haskellish_file filename) 
-  do pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False filename
+  do init_driver_state <- readIORef v_InitDriverState
+     writeIORef v_Driver_state init_driver_state
+
+     pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
+                       defaultHscLang filename
      runPipeline pipeline filename False{-no linking-} False{-no -o flag-}
 
 
@@ -737,7 +751,11 @@ preprocess filename =
 -- the .hs file if necessary, and compiling up the .stub_c files to
 -- generate Linkables.
 
-compile :: ModSummary              -- summary, including source
+-- NB.  No old interface can also mean that the source has changed.
+
+compile :: GhciMode                -- distinguish batch from interactive
+        -> ModSummary              -- summary, including source
+       -> Bool                    -- source unchanged?
         -> Maybe ModIface          -- old interface, if available
         -> HomeSymbolTable         -- for home module ModDetails
        -> HomeIfaceTable          -- for home module Ifaces
@@ -745,34 +763,37 @@ compile :: ModSummary              -- summary, including source
         -> IO CompResult
 
 data CompResult
-   = CompOK   ModDetails  -- new details (HST additions)
-              (Maybe (ModIface, Linkable))
-                       -- summary and code; Nothing => compilation not reqd
-                       -- (old summary and code are still valid)
-              PersistentCompilerState  -- updated PCS
+   = CompOK   PersistentCompilerState  -- updated PCS
+              ModDetails  -- new details (HST additions)
+              ModIface    -- new iface   (HIT additions)
+              (Maybe Linkable)
+                       -- new code; Nothing => compilation was not reqd
+                       -- (old code is still valid)
 
    | CompErrs PersistentCompilerState  -- updated PCS
 
 
-compile summary old_iface hst hit pcs = do 
-   verb <- readIORef v_Verbose
-   when verb (hPutStrLn stderr 
-                 (showSDoc (text "compile: compiling" 
-                            <+> ppr (name_of_summary summary))))
-
+compile ghci_mode summary source_unchanged old_iface hst hit pcs = do 
    init_dyn_flags <- readIORef v_InitDynFlags
    writeIORef v_DynFlags init_dyn_flags
+   init_driver_state <- readIORef v_InitDriverState
+   writeIORef v_Driver_state init_driver_state
+
+   showPass init_dyn_flags 
+       (showSDoc (text "Compiling" <+> ppr (name_of_summary summary)))
 
-   let location = ms_location summary   
-   let input_fn = unJust (ml_hs_file location) "compile:hs"
+   let verb = verbosity init_dyn_flags
+   let location   = ms_location summary
+   let input_fn   = unJust "compile:hs" (ml_hs_file location) 
+   let input_fnpp = unJust "compile:hspp" (ml_hspp_file location)
 
-   when verb (hPutStrLn stderr ("compile: input file " ++ input_fn))
+   when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
 
-   opts <- getOptionsFromSource input_fn
+   opts <- getOptionsFromSource input_fnpp
    processArgs dynamic_flags opts []
    dyn_flags <- readIORef v_DynFlags
 
-   hsc_lang <- readIORef v_Hsc_Lang
+   let hsc_lang = hscLang dyn_flags
    output_fn <- case hsc_lang of
                    HscAsm         -> newTempName (phaseInputExt As)
                    HscC           -> newTempName (phaseInputExt HCc)
@@ -780,48 +801,52 @@ compile summary old_iface hst hit pcs = do
                    HscInterpreted -> return (error "no output file")
 
    -- run the compiler
-   hsc_result <- hscMain dyn_flags{ hscOutName = output_fn } 
-                        False -- (panic "compile:source_unchanged")
+   hsc_result <- hscMain ghci_mode dyn_flags{ hscOutName = output_fn } 
+                        source_unchanged
                          location old_iface hst hit pcs
 
-   case hsc_result of {
-      HscFail pcs -> return (CompErrs pcs);
+   case hsc_result of
+      HscFail pcs -> return (CompErrs pcs)
 
-      HscOK details maybe_iface 
-       maybe_stub_h maybe_stub_c maybe_interpreted_code pcs -> do
-          
-          -- if no compilation happened, bail out early
-          case maybe_iface of {
-               Nothing -> return (CompOK details Nothing pcs);
-               Just iface -> do
+      HscNoRecomp pcs details iface -> return (CompOK pcs details iface Nothing)
 
+      HscRecomp pcs details iface
+       maybe_stub_h maybe_stub_c maybe_interpreted_code -> do
+          
           let (basename, _) = splitFilename input_fn
           maybe_stub_o <- dealWithStubs basename maybe_stub_h maybe_stub_c
           let stub_unlinked = case maybe_stub_o of
                                  Nothing -> []
                                  Just stub_o -> [ DotO stub_o ]
 
-          hs_unlinked <-
+          (hs_unlinked, unlinked_time) <-
             case hsc_lang of
 
                -- in interpreted mode, just return the compiled code
                -- as our "unlinked" object.
                HscInterpreted -> 
                    case maybe_interpreted_code of
-                       Just (code,itbl_env) -> return [Trees code itbl_env]
-                       Nothing -> panic "compile: no interpreted code"
+                      Just (code,itbl_env) -> do tm <- getClockTime 
+                                                  return ([Trees code itbl_env], tm)
+                      Nothing -> panic "compile: no interpreted code"
 
                -- we're in batch mode: finish the compilation pipeline.
-               _other -> do pipe <- genPipeline (StopBefore Ln) "" True output_fn
-                            o_file <- runPipeline pipe output_fn False False
-                            return [ DotO o_file ]
+               _other -> do pipe <- genPipeline (StopBefore Ln) "" True 
+                                       hsc_lang output_fn
+                             -- runPipeline takes input_fn so it can split off 
+                             -- the base name and use it as the base of 
+                             -- the output object file.
+                             let (basename, suffix) = splitFilename input_fn
+                            o_file <- pipeLoop pipe output_fn False False 
+                                                basename suffix
+                             o_time <- getModificationTime o_file
+                            return ([DotO o_file], o_time)
+
+          let linkable = LM unlinked_time (moduleName (ms_mod summary)) 
+                            (hs_unlinked ++ stub_unlinked)
 
-          let linkable = LM (moduleName (ms_mod summary)) 
-                               (hs_unlinked ++ stub_unlinked)
+          return (CompOK pcs details iface (Just linkable))
 
-          return (CompOK details (Just (iface, linkable)) pcs)
-          }
-   }
 
 -----------------------------------------------------------------------------
 -- stub .h and .c files (for foreign export support)
@@ -835,7 +860,7 @@ dealWithStubs basename maybe_stub_h maybe_stub_c
        case maybe_stub_h of
           Nothing -> return ()
           Just tmp_stub_h -> do
-               run_something "Copy stub .h file"
+               runSomething "Copy stub .h file"
                                ("cp " ++ tmp_stub_h ++ ' ':stub_h)
        
                        -- #include <..._stub.h> in .hc file
@@ -845,15 +870,16 @@ dealWithStubs basename maybe_stub_h maybe_stub_c
        case maybe_stub_c of
           Nothing -> return Nothing
           Just tmp_stub_c -> do  -- copy the _stub.c file into the current dir
-               run_something "Copy stub .c file" 
+               runSomething "Copy stub .c file" 
                    (unwords [ 
                        "rm -f", stub_c, "&&",
-                       "echo \'#include \""++stub_h++"\"\' >"++stub_c, " &&",
+                       "echo \'#include \"Stg.h\"\n#include \""++stub_h++"\"\' >"++stub_c, " &&",
                        "cat", tmp_stub_c, ">> ", stub_c
                        ])
 
                        -- compile the _stub.c file w/ gcc
-               pipeline <- genPipeline (StopBefore Ln) "" True stub_c
+               pipeline <- genPipeline (StopBefore Ln) "" True 
+                               defaultHscLang stub_c
                stub_o <- runPipeline pipeline stub_c False{-no linking-} 
                                False{-no -o option-}