[project @ 2002-02-18 12:41:01 by sewardj]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
index 0e8c898..07b0780 100644 (file)
@@ -2,7 +2,7 @@
 --
 -- GHC Driver
 --
--- (c) Simon Marlow 2000
+-- (c) The University of Glasgow 2002
 --
 -----------------------------------------------------------------------------
 
@@ -11,7 +11,6 @@
 module DriverPipeline (
 
        -- interfaces for the batch-mode driver
-   GhcMode(..), getGhcMode, v_GhcMode,
    genPipeline, runPipeline, pipeLoop,
 
        -- interfaces for the compilation manager (interpreted/batch-mode)
@@ -33,7 +32,7 @@ import DriverUtil
 import DriverMkDepend
 import DriverPhases
 import DriverFlags
-import SysTools                ( newTempName, addFilesToClean, getSysMan )
+import SysTools                ( newTempName, addFilesToClean, getSysMan, copy )
 import qualified SysTools      
 import HscMain
 import Finder
@@ -46,7 +45,9 @@ import Config
 import Panic
 import Util
 
+#ifdef GHCI
 import Time            ( getClockTime )
+#endif
 import Directory
 import System
 import IOExts
@@ -57,34 +58,6 @@ import Monad
 import Maybe
 
 import PackedString
-import MatchPS
-
------------------------------------------------------------------------------
--- GHC modes of operation
-
-modeFlag :: String -> Maybe GhcMode
-modeFlag "-M"           = Just $ DoMkDependHS
-modeFlag "--mk-dll"      = Just $ DoMkDLL
-modeFlag "-E"           = Just $ StopBefore Hsc
-modeFlag "-C"           = Just $ StopBefore HCc
-modeFlag "-S"           = Just $ StopBefore As
-modeFlag "-c"           = Just $ StopBefore Ln
-modeFlag "--make"        = Just $ DoMake
-modeFlag "--interactive" = Just $ DoInteractive
-modeFlag _               = Nothing
-
-getGhcMode :: [String]
-        -> IO ( [String]   -- rest of command line
-              , GhcMode
-              , String     -- "GhcMode" flag
-              )
-getGhcMode flags 
-  = case my_partition modeFlag flags of
-       ([]   , rest) -> return (rest, DoLink,  "") -- default is to do linking
-       ([(flag,one)], rest) -> return (rest, one, flag)
-       (_    , _   ) -> 
-         throwDyn (UsageError 
-               "only one of the flags -M, -E, -C, -S, -c, --make, --interactive, -mk-dll is allowed")
 
 -----------------------------------------------------------------------------
 -- genPipeline
@@ -135,7 +108,10 @@ genPipeline todo stop_flag persistent_output lang (filename,suffix)
    split      <- readIORef v_Split_object_files
    mangle     <- readIORef v_Do_asm_mangling
    keep_hc    <- readIORef v_Keep_hc_files
+#ifdef ILX
    keep_il    <- readIORef v_Keep_il_files
+   keep_ilx   <- readIORef v_Keep_ilx_files
+#endif
    keep_raw_s <- readIORef v_Keep_raw_s_files
    keep_s     <- readIORef v_Keep_s_files
    osuf       <- readIORef v_Object_suf
@@ -158,29 +134,34 @@ genPipeline todo stop_flag persistent_output lang (filename,suffix)
 
    let
    ----------- -----  ----   ---   --   --  -  -  -
-    pipeline
-      | todo == DoMkDependHS = [ Unlit, Cpp, HsPp, MkDependHS ]
+    pipeline = preprocess ++ compile
+
+    preprocess
+       | haskellish = [ Unlit, Cpp, HsPp ]
+       | otherwise  = [ ]
+
+    compile
+      | todo == DoMkDependHS = [ MkDependHS ]
+
+      | cish = [ Cc, As ]
 
       | haskellish = 
        case real_lang of
-       HscC    | split && mangle -> [ Unlit, Cpp, HsPp, Hsc, HCc, Mangle, 
-                                       SplitMangle, SplitAs ]
-               | mangle          -> [ Unlit, Cpp, HsPp, Hsc, HCc, Mangle, As ]
+       HscC    | split && mangle -> [ Hsc, HCc, Mangle, SplitMangle, SplitAs ]
+               | mangle          -> [ Hsc, HCc, Mangle, As ]
                | split           -> not_valid
-               | otherwise       -> [ Unlit, Cpp, HsPp, Hsc, HCc, As ]
+               | otherwise       -> [ Hsc, HCc, As ]
 
-       HscAsm  | split           -> [ Unlit, Cpp, HsPp, Hsc, SplitMangle, SplitAs ]
-               | otherwise       -> [ Unlit, Cpp, HsPp, Hsc, As ]
+       HscAsm  | split           -> [ Hsc, SplitMangle, SplitAs ]
+               | otherwise       -> [ Hsc, As ]
 
        HscJava | split           -> not_valid
                | otherwise       -> error "not implemented: compiling via Java"
 #ifdef ILX
        HscILX  | split           -> not_valid
-               | otherwise       -> [ Unlit, Cpp, HsPp, Hsc, Ilx2Il, Ilasm ]
+               | otherwise       -> [ Hsc, Ilx2Il, Ilasm ]
 #endif
-       HscNothing                -> [ Unlit, Cpp, HsPp, Hsc ]
-
-      | cish      = [ Cc, As ]
+       HscNothing                -> [ Hsc, HCc ] -- HCc is a dummy stop phase
 
       | otherwise = [ ]  -- just pass this file through to the linker
 
@@ -195,6 +176,7 @@ genPipeline todo stop_flag persistent_output lang (filename,suffix)
                        StopBefore phase      -> phase
                        DoMkDependHS          -> Ln
                        DoLink                -> Ln
+                       DoMkDLL               -> Ln
    ----------- -----  ----   ---   --   --  -  -  -
 
        -- this shouldn't happen.
@@ -208,8 +190,9 @@ genPipeline todo stop_flag persistent_output lang (filename,suffix)
    when (start_phase `elem` pipeline && 
         (stop_phase /= Ln && stop_phase `notElem` pipeline))
         (throwDyn (UsageError 
-                   ("flag " ++ stop_flag
-                    ++ " is incompatible with source file `" ++ filename ++ "'")))
+                   ("flag `" ++ stop_flag
+                    ++ "' is incompatible with source file `"
+                    ++ filename ++ "'" ++ show pipeline ++ show stop_phase)))
    let
        -- .o and .hc suffixes can be overriden by command-line options:
       myPhaseInputExt Ln  | Just s <- osuf  = s
@@ -236,6 +219,7 @@ genPipeline todo stop_flag persistent_output lang (filename,suffix)
                             As     | keep_s     -> Persistent
                             HCc    | keep_hc    -> Persistent
 #ifdef ILX
+                            Ilx2Il | keep_ilx   -> Persistent
                             Ilasm  | keep_il    -> Persistent
 #endif
                             _other              -> Temporary
@@ -285,7 +269,21 @@ pipeLoop (all_phases@((phase, keep, o_suffix):phases))
              ofile <- outputFileName True keep final_suffix
              return (ofile, final_suffix)
           -- carry on ...
-       Just fn -> 
+       Just fn -> do
+               {-
+                 Check to see whether we've reached the end of the
+                 pipeline, but did so with an ineffective last stage.
+                 (i.e., it returned the input_fn as the output filename).
+                 
+                 If we did and the output is persistent, copy the contents
+                 of input_fn into the file where the pipeline's output is
+                 expected to end up.
+               -}
+             atEnd <- finalStage (null phases)
+             when (atEnd && fn == input_fn)
+                  (copy "Saving away compilation pipeline's output"
+                        input_fn
+                        output_fn)
               {-
               Notice that in order to keep the invariant that we can
               determine a compilation pipeline's 'start phase' just
@@ -306,9 +304,14 @@ pipeLoop (all_phases@((phase, keep, o_suffix):phases))
               pipeLoop phases (fn, o_suffix) do_linking use_ofile
                                orig_basename orig_suffix
   where
+     finalStage lastPhase = do
+       o_file <- readIORef v_Output_file
+       return (lastPhase && not do_linking && use_ofile && isJust o_file)
+
      outputFileName last_phase keep suffix
        = do o_file <- readIORef v_Output_file
-            if last_phase && not do_linking && use_ofile && isJust o_file
+            atEnd  <- finalStage last_phase
+            if atEnd
               then case o_file of 
                       Just s  -> return s
                       Nothing -> error "outputFileName"
@@ -615,8 +618,15 @@ run_phase cc_phase basename suff input_fn output_fn
                      | otherwise         = [ ]
 
        excessPrecision <- readIORef v_Excess_precision
-       SysTools.runCc ([ SysTools.Option "-x", SysTools.Option "c"
-                       , SysTools.FileOption "" input_fn
+
+       -- force the C compiler to interpret this file as C when
+       -- compiling .hc files, by adding the -x c option.
+       let langopt
+               | cc_phase == HCc = [ SysTools.Option "-x", SysTools.Option "c"]
+               | otherwise       = [ ]
+
+       SysTools.runCc (langopt ++
+                       [ SysTools.FileOption "" input_fn
                        , SysTools.Option "-o"
                        , SysTools.FileOption "" output_fn
                        ]
@@ -702,7 +712,7 @@ run_phase SplitAs basename _suff _input_fn output_fn
 
        odir <- readIORef v_Output_dir
        let real_odir = case odir of
-                               Nothing -> basename
+                               Nothing -> basename ++ "_split"
                                Just d  -> d
 
        let assemble_file n
@@ -901,8 +911,7 @@ doLink o_files = do
                      ++ pkg_extra_ld_opts
                      ++ extra_ld_opts
                      ++ if static && not no_hs_main then
-                           [ "-u", prefixUnderscore "PrelMain_mainIO_closure",
-                             "-u", prefixUnderscore "__stginit_PrelMain"] 
+                           [ "-u", prefixUnderscore "Main_zdmain_closure"] 
                         else []))
 
     -- parallel only: move binary to another dir -- HWL
@@ -971,9 +980,9 @@ doMkDLL o_files = do
         ++ pkg_lib_path_opts
         ++ pkg_lib_opts
         ++ pkg_extra_ld_opts
-         ++ (case findPS (packString (concat extra_ld_opts)) (packString "--def") of
-               Nothing -> [ "--export-all" ]
-              Just _  -> [ "" ])
+         ++ (if "--def" `elem` (concatMap words extra_ld_opts)
+              then [ "" ]
+               else [ "--export-all" ])
         ++ extra_ld_opts
        ))
 
@@ -1035,7 +1044,7 @@ compile ghci_mode summary source_unchanged have_object
 
 
    showPass dyn_flags 
-       (showSDoc (text "Compiling" <+> ppr (name_of_summary summary)))
+       (showSDoc (text "Compiling" <+> ppr (modSummaryName summary)))
 
    let verb      = verbosity dyn_flags
    let location   = ms_location summary
@@ -1052,7 +1061,9 @@ compile ghci_mode summary source_unchanged have_object
        (basename, _) = splitFilename input_fn
        
    keep_hc <- readIORef v_Keep_hc_files
+#ifdef ILX
    keep_il <- readIORef v_Keep_il_files
+#endif
    keep_s  <- readIORef v_Keep_s_files
 
    output_fn <- 
@@ -1104,7 +1115,6 @@ compile ghci_mode summary source_unchanged have_object
 
       HscRecomp pcs details iface
        stub_h_exists stub_c_exists maybe_interpreted_code -> do
-          
           let 
           maybe_stub_o <- compileStub dyn_flags' stub_c_exists
           let stub_unlinked = case maybe_stub_o of
@@ -1138,7 +1148,7 @@ compile ghci_mode summary source_unchanged have_object
                              o_time <- getModificationTime o_file
                             return ([DotO o_file], o_time)
 
-          let linkable = LM unlinked_time (moduleName (ms_mod summary)) 
+          let linkable = LM unlinked_time (modSummaryName summary)
                             (hs_unlinked ++ stub_unlinked)
 
           return (CompOK pcs details iface (Just linkable))