[project @ 2000-11-14 17:41:04 by sewardj]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
index 06735fe..f1e9618 100644 (file)
@@ -1,5 +1,5 @@
 -----------------------------------------------------------------------------
--- $Id: DriverPipeline.hs,v 1.9 2000/10/27 11:48:55 sewardj Exp $
+-- $Id: DriverPipeline.hs,v 1.25 2000/11/14 17:41:04 sewardj Exp $
 --
 -- GHC Driver
 --
@@ -14,10 +14,10 @@ module DriverPipeline (
    genPipeline, runPipeline,
 
        -- interfaces for the compilation manager (interpreted/batch-mode)
-   preprocess, compile,
+   preprocess, compile, CompResult(..),
 
        -- batch-mode linking interface
-   doLink,
+   doLink
   ) where
 
 #include "HsVersions.h"
@@ -37,13 +37,10 @@ import Module
 import CmdLineOpts
 import Config
 import Util
-import MkIface         ( pprIface )
 
-import Posix
 import Directory
 import System
 import IOExts
--- import Posix                commented out temp by SLPJ to get going on windows
 import Exception
 
 import IO
@@ -122,6 +119,8 @@ data IntermediateFileType
 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,
@@ -129,14 +128,14 @@ genPipeline
              String)                -- output file suffix
          ]     
 
-genPipeline todo stop_flag 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
+   osuf       <- readIORef v_Object_suf
 
    let
    ----------- -----  ----   ---   --   --  -  -  -
@@ -147,9 +146,9 @@ genPipeline todo stop_flag 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
    ----------- -----  ----   ---   --   --  -  -  -
@@ -198,6 +197,10 @@ genPipeline todo stop_flag filename
 
    let
    ----------- -----  ----   ---   --   --  -  -  -
+      myPhaseInputExt Ln = case osuf of Nothing -> phaseInputExt Ln
+                                       Just s  -> s
+      myPhaseInputExt other = phaseInputExt other
+
       annotatePipeline
         :: [Phase]             -- raw pipeline
         -> Phase               -- phase to stop before
@@ -205,13 +208,14 @@ genPipeline todo stop_flag filename
       annotatePipeline []     _    = []
       annotatePipeline (Ln:_) _    = []
       annotatePipeline (phase:next_phase:ps) stop = 
-         (phase, keep_this_output, phaseInputExt next_phase)
+         (phase, keep_this_output, myPhaseInputExt next_phase)
             : annotatePipeline (next_phase:ps) stop
          where
                keep_this_output
-                    | next_phase == stop = Persistent
-                    | otherwise =
-                       case next_phase of
+                    | next_phase == stop 
+                     = if persistent_output then Persistent else Temporary
+                    | otherwise
+                    = case next_phase of
                             Ln -> Persistent
                             Mangle | keep_raw_s -> Persistent
                             As     | keep_s     -> Persistent
@@ -263,12 +267,6 @@ pipeLoop ((phase, keep, o_suffix):phases)
                return ofile
        else do -- carry on ...
 
-       -- sadly, ghc -E is supposed to write the file to stdout.  We
-       -- generate <file>.cpp, so we also have to cat the file here.
-     when (null phases && phase == Cpp) $
-       run_something "Dump pre-processed file to stdout"
-                     ("cat " ++ output_fn)
-
      pipeLoop phases output_fn do_linking use_ofile orig_basename orig_suffix
 
   where
@@ -279,8 +277,7 @@ pipeLoop ((phase, keep, o_suffix):phases)
                       Just s  -> return s
                       Nothing -> error "outputFileName"
               else if keep == Persistent
-                          then do f <- odir_ify (orig_basename ++ '.':suffix)
-                                  osuf_ify f
+                          then odir_ify (orig_basename ++ '.':suffix)
                           else newTempName suffix
 
 -------------------------------------------------------------------------------
@@ -297,9 +294,15 @@ run_phase Unlit _basename _suff input_fn output_fn
 -------------------------------------------------------------------------------
 -- Cpp phase 
 
-run_phase Cpp _basename _suff input_fn output_fn
+run_phase Cpp basename suff input_fn output_fn
   = do src_opts <- getOptionsFromSource input_fn
-       _ <- processArgs dynamic_flags src_opts []
+       unhandled_flags <- processArgs dynamic_flags src_opts []
+
+       when (not (null unhandled_flags)) 
+            (throwDyn (OtherError (
+                          basename ++ "." ++ suff 
+                          ++ ": static flags are not allowed in {-# OPTIONS #-} pragmas:\n\t" 
+                          ++ unwords unhandled_flags)) (ExitFailure 1))
 
        do_cpp <- readState cpp_flag
        if do_cpp
@@ -339,9 +342,9 @@ run_phase MkDependHS basename suff input_fn _output_fn = do
 
    deps <- mapM (findDependency basename) imports
 
-   osuf_opt <- readIORef v_Output_suf
+   osuf_opt <- readIORef v_Object_suf
    let osuf = case osuf_opt of
-                       Nothing -> "o"
+                       Nothing -> phaseInputExt Ln
                        Just s  -> s
 
    extra_suffixes <- readIORef v_Dep_suffixes
@@ -352,7 +355,7 @@ run_phase MkDependHS basename suff input_fn _output_fn = do
    
    hdl <- readIORef v_Dep_tmp_hdl
 
-       -- std dependeny of the object(s) on the source file
+       -- std dependency of the object(s) on the source file
    hPutStrLn hdl (unwords objs ++ " : " ++ basename ++ '.':suff)
 
    let genDep (dep, False {- not an hi file -}) = 
@@ -407,42 +410,40 @@ 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 ++ {-ToDo: modname!!-}basename
-                                       ++ hisuf
+                          Nothing -> basename ++ '.':hisuf
                           Just fn -> fn
 
   -- figure out if the source has changed, for recompilation avoidance.
   -- only do this if we're eventually going to generate a .o file.
   -- (ToDo: do when generating .hc files too?)
   --
-  -- Setting source_unchanged to "-fsource_unchanged" means that M.o seems
+  -- Setting source_unchanged to True means that M.o seems
   -- to be up to date wrt M.hs; so no need to recompile unless imports have
   -- changed (which the compiler itself figures out).
-  -- Setting source_unchanged to "" tells the compiler that M.o is out of
+  -- Setting source_unchanged to False tells the compiler that M.o is out of
   -- 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)
        source_unchanged <- 
           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
-            then return ""
+            then return False
             else do t1 <- getModificationTime (basename ++ '.':suff)
                     o_file_exists <- doesFileExist o_file
                     if not o_file_exists
-                       then return ""  -- Need to recompile
+                       then return False       -- Need to recompile
                        else do t2 <- getModificationTime o_file
                                if t2 > t1
-                                 then return "-fsource-unchanged"
-                                 else return ""
-
-   -- build a bogus ModSummary to pass to hscMain.
-       let summary = ModSummary {
-                       ms_mod = (mkModuleInThisPackage . mkModuleName)
-                                    {-ToDo: modname!!-}basename,
-                       ms_location = error "no loc",
-                       ms_ppsource = Just (input_fn, error "no fingerprint"),
-                       ms_imports = error "no imports"
-                    }
+                                 then return True
+                                 else return False
+
+   -- build a ModuleLocation to pass to hscMain.
+        let location = ModuleLocation {
+                          ml_hs_file   = Nothing,
+                          ml_hspp_file = Just input_fn,
+                          ml_hi_file   = Just hifile,
+                          ml_obj_file  = Just o_file
+                       }
 
   -- get the DynFlags
         dyn_flags <- readIORef v_DynFlags
@@ -450,7 +451,8 @@ run_phase Hsc basename suff input_fn output_fn
   -- run the compiler!
         pcs <- initPersistentCompilerState
        result <- hscMain dyn_flags{ hscOutName = output_fn }
-                         summary 
+                         source_unchanged
+                         location
                          Nothing        -- no iface
                          emptyModuleEnv -- HomeSymbolTable
                          emptyModuleEnv -- HomeIfaceTable
@@ -463,13 +465,14 @@ run_phase Hsc basename suff input_fn output_fn
            HscOK details maybe_iface maybe_stub_h maybe_stub_c 
                        _maybe_interpreted_code pcs -> do
 
-    -- deal with stubs
+           -- deal with stubs
        maybe_stub_o <- dealWithStubs basename maybe_stub_h maybe_stub_c
        case maybe_stub_o of
                Nothing -> return ()
                Just stub_o -> add v_Ld_inputs stub_o
 
-       return True
+        let keep_going = case maybe_iface of Just _ -> True; Nothing -> False
+       return keep_going
     }
 
 -----------------------------------------------------------------------------
@@ -524,6 +527,10 @@ run_phase cc_phase _basename _suff input_fn output_fn
 
        pkg_extra_cc_opts <- getPackageExtraCcOpts
 
+       split_objs <- readIORef v_Split_object_files
+       let split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
+                     | otherwise         = [ ]
+
        excessPrecision <- readIORef v_Excess_precision
 
        run_something "C Compiler"
@@ -535,6 +542,7 @@ run_phase cc_phase _basename _suff input_fn output_fn
                   ++ [ verb, "-S", "-Wimplicit", opt_flag ]
                   ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
                   ++ cc_opts
+                  ++ split_opt
 #ifdef mingw32_TARGET_OS
                    ++ [" -mno-cygwin"]
 #endif
@@ -574,7 +582,7 @@ run_phase SplitMangle _basename _suff input_fn _output_fn
 
        -- this is the prefix used for the split .s files
        tmp_pfx <- readIORef v_TmpDir
-       x <- getProcessID
+       x <- myGetProcessID
        let split_s_prefix = tmp_pfx ++ "/ghc" ++ show x
        writeIORef v_Split_prefix split_s_prefix
        addFilesToClean [split_s_prefix ++ "__*"] -- d:-)
@@ -643,6 +651,10 @@ doLink :: [String] -> IO ()
 doLink o_files = do
     ln <- readIORef v_Pgm_l
     verb <- is_verbose
+    static <- readIORef v_Static
+    let imp = if static then "" else "_imp"
+    no_hs_main <- readIORef v_NoHsMain
+
     o_file <- readIORef v_Output_file
     let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
 
@@ -653,7 +665,7 @@ doLink o_files = do
     let lib_path_opts = map ("-L"++) lib_paths
 
     pkg_libs <- getPackageLibraries
-    let pkg_lib_opts = map (\lib -> "-l"++lib) pkg_libs
+    let pkg_lib_opts = map (\lib -> "-l" ++ lib ++ imp) pkg_libs
 
     libs <- readIORef v_Cmdline_libraries
     let lib_opts = map ("-l"++) (reverse libs)
@@ -667,10 +679,24 @@ doLink o_files = do
        -- opts from -optl-<blah>
     extra_ld_opts <- getStaticOpts v_Opt_l
 
+    rts_pkg <- getPackageDetails ["rts"]
+    std_pkg <- getPackageDetails ["std"]
+#ifdef mingw32_TARGET_OS
+    let extra_os = if static || no_hs_main
+                   then []
+--                   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"
-       (unwords 
+       (unwords
         ([ ln, verb, "-o", output_fn ]
+        ++ md_c_flags
         ++ o_files
+#ifdef mingw32_TARGET_OS
+        ++ extra_os
+#endif
         ++ extra_ld_inputs
         ++ lib_path_opts
         ++ lib_opts
@@ -678,6 +704,11 @@ doLink o_files = do
         ++ pkg_lib_opts
         ++ pkg_extra_ld_opts
         ++ extra_ld_opts
+#ifdef mingw32_TARGET_OS
+         ++ if static then [ "-u _PrelMain_mainIO_closure" , "-u ___init_PrelMain"] else []
+#else
+        ++ [ "-u PrelMain_mainIO_closure" , "-u __init_PrelMain"]
+#endif
        )
        )
 
@@ -688,7 +719,8 @@ doLink o_files = do
 preprocess :: FilePath -> IO FilePath
 preprocess filename =
   ASSERT(haskellish_file filename) 
-  do pipeline <- genPipeline (StopBefore Hsc) ("preprocess") filename
+  do pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
+                       defaultHscLang filename
      runPipeline pipeline filename False{-no linking-} False{-no -o flag-}
 
 
@@ -731,18 +763,18 @@ compile summary old_iface hst hit pcs = do
 
    init_dyn_flags <- readIORef v_InitDynFlags
    writeIORef v_DynFlags init_dyn_flags
-   
-   let input_fn = case ms_ppsource summary of
-                       Just (ppsource, fingerprint) -> ppsource
-                       Nothing -> hs_file (ms_location summary)
 
-   when verb (hPutStrLn stderr ("compile: input file " ++ input_fn))
+   let location   = ms_location summary   
+   let input_fn   = unJust (ml_hs_file location) "compile:hs"
+   let input_fnpp = unJust (ml_hspp_file location) "compile:hspp"
+
+   when verb (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)
@@ -751,7 +783,8 @@ compile summary old_iface hst hit pcs = do
 
    -- run the compiler
    hsc_result <- hscMain dyn_flags{ hscOutName = output_fn } 
-                         summary old_iface hst hit pcs
+                        False -- (panic "compile:source_unchanged")
+                         location old_iface hst hit pcs
 
    case hsc_result of {
       HscFail pcs -> return (CompErrs pcs);
@@ -764,7 +797,7 @@ compile summary old_iface hst hit pcs = do
                Nothing -> return (CompOK details Nothing pcs);
                Just iface -> do
 
-          let (basename, _) = splitFilename (hs_file (ms_location summary))
+          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 -> []
@@ -781,7 +814,8 @@ compile summary old_iface hst hit pcs = do
                        Nothing -> panic "compile: no interpreted code"
 
                -- we're in batch mode: finish the compilation pipeline.
-               _other -> do pipe <- genPipeline (StopBefore Ln) "" output_fn
+               _other -> do pipe <- genPipeline (StopBefore Ln) "" True 
+                                       hsc_lang output_fn
                             o_file <- runPipeline pipe output_fn False False
                             return [ DotO o_file ]
 
@@ -822,7 +856,8 @@ dealWithStubs basename maybe_stub_h maybe_stub_c
                        ])
 
                        -- compile the _stub.c file w/ gcc
-               pipeline <- genPipeline (StopBefore Ln) "" stub_c
+               pipeline <- genPipeline (StopBefore Ln) "" True 
+                               defaultHscLang stub_c
                stub_o <- runPipeline pipeline stub_c False{-no linking-} 
                                False{-no -o option-}