Fix some validation errors
[ghc-hetmet.git] / compiler / main / DriverPipeline.hs
index b1a8189..afbd03e 100644 (file)
@@ -1,3 +1,7 @@
+{-# OPTIONS -fno-cse #-}
+{-# LANGUAGE NamedFieldPuns #-}
+-- -fno-cse is needed for GLOBAL_VAR's to behave properly
+
 -----------------------------------------------------------------------------
 --
 -- GHC Driver
 -----------------------------------------------------------------------------
 
 module DriverPipeline (
-       -- Run a series of compilation steps in a pipeline, for a
-       -- collection of source files.
+        -- Run a series of compilation steps in a pipeline, for a
+        -- collection of source files.
    oneShot, compileFile,
 
-       -- Interfaces for the batch-mode driver
-   staticLink,
-
-       -- Interfaces for the compilation manager (interpreted/batch-mode)
-   preprocess, 
-   compile, CompResult(..), 
-   link, 
+        -- Interfaces for the batch-mode driver
+   linkBinary,
 
-        -- DLL building
-   doMkDLL,
+        -- Interfaces for the compilation manager (interpreted/batch-mode)
+   preprocess,
+   compile, compile',
+   link,
 
   ) where
 
@@ -30,164 +31,184 @@ import Packages
 import HeaderInfo
 import DriverPhases
 import SysTools
-import qualified SysTools      
 import HscMain
 import Finder
 import HscTypes
 import Outputable
 import Module
-import UniqFM          ( eltsUFM )
+import UniqFM           ( eltsUFM )
 import ErrUtils
 import DynFlags
-import StaticFlags     ( v_Ld_inputs, opt_Static, WayName(..) )
+import StaticFlags      ( v_Ld_inputs, opt_PIC, opt_Static, WayName(..) )
 import Config
 import Panic
 import Util
-import StringBuffer    ( hGetStringBuffer )
-import BasicTypes      ( SuccessFlag(..) )
-import Maybes          ( expectJust )
-import ParserCoreUtils ( getCoreModuleName )
-import SrcLoc          ( unLoc )
-import SrcLoc          ( Located(..) )
-
-import Control.Exception as Exception
-import Data.IORef      ( readIORef, writeIORef, IORef )
-import GHC.Exts                ( Int(..) )
+import StringBuffer     ( hGetStringBuffer )
+import BasicTypes       ( SuccessFlag(..) )
+import Maybes           ( expectJust )
+import ParserCoreUtils  ( getCoreModuleName )
+import SrcLoc
+import FastString
+import LlvmCodeGen      ( llvmFixupAsm )
+import MonadUtils
+import Platform
+
+import Exception
+import Data.IORef       ( readIORef )
 import System.Directory
+import System.FilePath
 import System.IO
-import SYSTEM_IO_ERROR as IO
 import Control.Monad
-import Data.List       ( isSuffixOf )
+import Data.List        ( isSuffixOf )
 import Data.Maybe
-import System.Exit
-import System.Cmd
 import System.Environment
+import Data.Char
 
 -- ---------------------------------------------------------------------------
 -- Pre-process
 
--- Just preprocess a file, put the result in a temp. file (used by the
+-- | Just preprocess a file, put the result in a temp. file (used by the
 -- compilation manager during the summary phase).
 --
 -- We return the augmented DynFlags, because they contain the result
 -- of slurping in the OPTIONS pragmas
 
-preprocess :: DynFlags -> (FilePath, Maybe Phase) -> IO (DynFlags, FilePath)
-preprocess dflags (filename, mb_phase) =
-  ASSERT2(isJust mb_phase || isHaskellSrcFilename filename, text filename) 
-  runPipeline anyHsc dflags (filename, mb_phase) 
-        Nothing Temporary Nothing{-no ModLocation-}
+preprocess :: HscEnv
+           -> (FilePath, Maybe Phase) -- ^ filename and starting phase
+           -> IO (DynFlags, FilePath)
+preprocess hsc_env (filename, mb_phase) =
+  ASSERT2(isJust mb_phase || isHaskellSrcFilename filename, text filename)
+  runPipeline anyHsc hsc_env (filename, mb_phase)
+        Nothing Temporary Nothing{-no ModLocation-} Nothing{-no stub-}
 
 -- ---------------------------------------------------------------------------
--- Compile
 
+-- | Compile
+--
 -- Compile a single module, under the control of the compilation manager.
 --
 -- This is the interface between the compilation manager and the
 -- compiler proper (hsc), where we deal with tedious details like
--- reading the OPTIONS pragma from the source file, and passing the
--- output of hsc through the C compiler.
-
+-- reading the OPTIONS pragma from the source file, converting the
+-- C or assembly that GHC produces into an object file, and compiling
+-- FFI stub files.
+--
 -- NB.  No old interface can also mean that the source has changed.
 
 compile :: HscEnv
-       -> ModSummary
-       -> Maybe Linkable       -- Just linkable <=> source unchanged
-        -> Maybe ModIface       -- Old interface, if available
-        -> Int -> Int
-        -> IO CompResult
-
-data CompResult
-   = CompOK   ModDetails       -- New details
-              ModIface         -- New iface
-              (Maybe Linkable) -- a Maybe, for the same reasons as hm_linkable
-
-   | CompErrs 
-
-
-compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do 
-
-   let dflags0     = ms_hspp_opts mod_summary
-       this_mod    = ms_mod mod_summary
-       src_flavour = ms_hsc_src mod_summary
-
-       have_object 
-              | Just l <- maybe_old_linkable, isObjectLinkable l = True
-              | otherwise = False
-
-   -- FIXME: We need to know whether or not we're recompiling the file. Move this to HscMain?
-   --showPass dflags0 ("Compiling " ++ showModMsg have_object mod_summary)
-
-   let location          = ms_location mod_summary
-   let input_fn   = expectJust "compile:hs" (ml_hs_file location) 
-   let input_fnpp = ms_hspp_file mod_summary
+        -> ModSummary      -- ^ summary for module being compiled
+        -> Int             -- ^ module N ...
+        -> Int             -- ^ ... of M
+        -> Maybe ModIface  -- ^ old interface, if we have one
+        -> Maybe Linkable  -- ^ old linkable, if we have one
+        -> IO HomeModInfo   -- ^ the complete HomeModInfo, if successful
+
+compile = compile' (hscCompileNothing, hscCompileInteractive, hscCompileBatch)
+
+compile' :: 
+           (Compiler (HscStatus, ModIface, ModDetails),
+            Compiler (InteractiveStatus, ModIface, ModDetails),
+            Compiler (HscStatus, ModIface, ModDetails))
+        -> HscEnv
+        -> ModSummary      -- ^ summary for module being compiled
+        -> Int             -- ^ module N ...
+        -> Int             -- ^ ... of M
+        -> Maybe ModIface  -- ^ old interface, if we have one
+        -> Maybe Linkable  -- ^ old linkable, if we have one
+        -> IO HomeModInfo   -- ^ the complete HomeModInfo, if successful
+
+compile' (nothingCompiler, interactiveCompiler, batchCompiler)
+        hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
+ = do
+   let dflags0     = ms_hspp_opts summary
+       this_mod    = ms_mod summary
+       src_flavour = ms_hsc_src summary
+       location    = ms_location summary
+       input_fn    = expectJust "compile:hs" (ml_hs_file location)
+       input_fnpp  = ms_hspp_file summary
 
    debugTraceMsg dflags0 2 (text "compile: input file" <+> text input_fnpp)
 
-   let (basename, _) = splitFilename input_fn
+   let basename = dropExtension input_fn
 
   -- We add the directory in which the .hs files resides) to the import path.
   -- This is needed when we try to compile the .hc file later, if it
   -- imports a _stub.h file that we created here.
-   let current_dir = directoryOf basename
+   let current_dir = case takeDirectory basename of
+                     "" -> "." -- XXX Hack
+                     d -> d
        old_paths   = includePaths dflags0
        dflags      = dflags0 { includePaths = current_dir : old_paths }
+       hsc_env     = hsc_env0 {hsc_dflags = dflags}
 
    -- Figure out what lang we're generating
-   let hsc_lang = hscMaybeAdjustTarget dflags StopLn src_flavour (hscTarget dflags)
+   let hsc_lang = hscTarget dflags
    -- ... and what the next phase should be
    let next_phase = hscNextPhase dflags src_flavour hsc_lang
    -- ... and what file to generate the output into
-   output_fn <- getOutputFilename next_phase 
-                       Temporary basename dflags next_phase (Just location)
+   output_fn <- getOutputFilename next_phase
+                        Temporary basename dflags next_phase (Just location)
 
    let dflags' = dflags { hscTarget = hsc_lang,
-                               hscOutName = output_fn,
-                               extCoreName = basename ++ ".hcr" }
+                                hscOutName = output_fn,
+                                extCoreName = basename ++ ".hcr" }
+   let hsc_env' = hsc_env { hsc_dflags = dflags' }
 
-   -- -no-recomp should also work with --make
+   -- -fforce-recomp should also work with --make
    let force_recomp = dopt Opt_ForceRecomp dflags
        source_unchanged = isJust maybe_old_linkable && not force_recomp
-       hsc_env' = hsc_env { hsc_dflags = dflags' }
        object_filename = ml_obj_file location
 
-   let getStubLinkable False = return []
-       getStubLinkable True
-           = do stub_o <- compileStub dflags' this_mod location
-                return [ DotO stub_o ]
-
-       handleBatch (HscNoRecomp, iface, details)
+   let handleBatch HscNoRecomp
            = ASSERT (isJust maybe_old_linkable)
-             return (CompOK details iface maybe_old_linkable)
-       handleBatch (HscRecomp hasStub, iface, details)
+             return maybe_old_linkable
+
+       handleBatch (HscRecomp hasStub _)
            | isHsBoot src_flavour
-               = return (CompOK details iface Nothing)
+               = do when (isObjectTarget hsc_lang) $ -- interpreted reaches here too
+                       liftIO $ SysTools.touch dflags' "Touching object file"
+                                   object_filename
+                    return maybe_old_linkable
+
            | otherwise
-               = do stub_unlinked <- getStubLinkable hasStub
-                    (hs_unlinked, unlinked_time) <-
+               = do (hs_unlinked, unlinked_time) <-
                         case hsc_lang of
-                          HscNothing
-                            -> return ([], ms_hs_date mod_summary)
+                          HscNothing ->
+                            return ([], ms_hs_date summary)
                           -- We're in --make mode: finish the compilation pipeline.
-                          _other
-                            -> do runPipeline StopLn dflags (output_fn,Nothing)
+                          _other -> do
+                            maybe_stub_o <- case hasStub of
+                               Nothing -> return Nothing
+                               Just stub_c -> do
+                                 stub_o <- compileStub hsc_env' stub_c
+                                 return (Just stub_o)
+                            _ <- runPipeline StopLn hsc_env' (output_fn,Nothing)
                                               (Just basename)
                                               Persistent
                                               (Just location)
+                                              maybe_stub_o
                                   -- The object filename comes from the ModLocation
-                                  o_time <- getModificationTime object_filename
-                                  return ([DotO object_filename], o_time)
-                    let linkable = LM unlinked_time this_mod
-                                  (hs_unlinked ++ stub_unlinked)
-                    return (CompOK details iface (Just linkable))
+                            o_time <- getModificationTime object_filename
+                            return ([DotO object_filename], o_time)
+                    
+                    let linkable = LM unlinked_time this_mod hs_unlinked
+                    return (Just linkable)
 
-       handleInterpreted (InteractiveNoRecomp, iface, details)
+       handleInterpreted HscNoRecomp
            = ASSERT (isJust maybe_old_linkable)
-             return (CompOK details iface maybe_old_linkable)
-       handleInterpreted (InteractiveRecomp hasStub comp_bc, iface, details)
-           = do stub_unlinked <- getStubLinkable hasStub
-                let hs_unlinked = [BCOs comp_bc]
-                    unlinked_time = ms_hs_date mod_summary
+             return maybe_old_linkable
+       handleInterpreted (HscRecomp _hasStub Nothing)
+           = ASSERT (isHsBoot src_flavour)
+             return maybe_old_linkable
+       handleInterpreted (HscRecomp hasStub (Just (comp_bc, modBreaks)))
+           = do stub_o <- case hasStub of
+                            Nothing -> return []
+                            Just stub_c -> do
+                              stub_o <- compileStub hsc_env' stub_c
+                              return [DotO stub_o]
+
+                let hs_unlinked = [BCOs comp_bc modBreaks]
+                    unlinked_time = ms_hs_date summary
                   -- Why do we use the timestamp of the source file here,
                   -- rather than the current time?  This works better in
                   -- the case where the local clock is out of sync
@@ -195,25 +216,24 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do
                   -- if the source is modified, then the linkable will
                   -- be out of date.
                 let linkable = LM unlinked_time this_mod
-                               (hs_unlinked ++ stub_unlinked)
-                return (CompOK details iface (Just linkable))
-
-   let runCompiler compiler handle
-           = do mbResult <- compiler hsc_env' mod_summary
-                                     source_unchanged old_iface
-                                     (Just (mod_index, nmods))
-                case mbResult of
-                  Nothing     -> return CompErrs
-                  Just result -> handle result
+                               (hs_unlinked ++ stub_o)
+                return (Just linkable)
+
+   let -- runCompiler :: Compiler result -> (result -> Maybe Linkable)
+       --            -> m HomeModInfo
+       runCompiler compiler handle
+           = do (result, iface, details)
+                    <- compiler hsc_env' summary source_unchanged mb_old_iface
+                                (Just (mod_index, nmods))
+                linkable <- handle result
+                return (HomeModInfo{ hm_details  = details,
+                                     hm_iface    = iface,
+                                     hm_linkable = linkable })
    -- run the compiler
    case hsc_lang of
-     HscInterpreted | not (isHsBoot src_flavour) -- We can't compile boot files to
-                                                 -- bytecode so don't even try.
-         -> runCompiler hscCompileInteractive handleInterpreted
-     HscNothing
-         -> runCompiler hscCompileNothing handleBatch
-     _other
-         -> runCompiler hscCompileBatch handleBatch
+      HscInterpreted -> runCompiler interactiveCompiler handleInterpreted
+      HscNothing     -> runCompiler nothingCompiler     handleBatch
+      _other         -> runCompiler batchCompiler       handleBatch
 
 -----------------------------------------------------------------------------
 -- stub .h and .c files (for foreign export support)
@@ -221,39 +241,24 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do
 -- The _stub.c file is derived from the haskell source file, possibly taking
 -- into account the -stubdir option.
 --
--- Consequently, we derive the _stub.o filename from the haskell object
--- filename.  
---
--- This isn't necessarily the same as the object filename we
--- would get if we just compiled the _stub.c file using the pipeline.
--- For example:
---
---    ghc src/A.hs -odir obj
--- 
--- results in obj/A.o, and src/A_stub.c.  If we compile src/A_stub.c with
--- -odir obj, we would get obj/src/A_stub.o, which is wrong; we want
--- obj/A_stub.o.
-
-compileStub :: DynFlags -> Module -> ModLocation -> IO FilePath
-compileStub dflags mod location = do
-       let (o_base, o_ext) = splitFilename (ml_obj_file location)
-           stub_o = o_base ++ "_stub" `joinFileExt` o_ext
+-- The object file created by compiling the _stub.c file is put into a
+-- temporary file, which will be later combined with the main .o file
+-- (see the MergeStubs phase).
 
-       -- compile the _stub.c file w/ gcc
-       let (stub_c,_) = mkStubPaths dflags (moduleName mod) location
-       runPipeline StopLn dflags (stub_c,Nothing)  Nothing
-               (SpecificFile stub_o) Nothing{-no ModLocation-}
-
-       return stub_o
+compileStub :: HscEnv -> FilePath -> IO FilePath
+compileStub hsc_env stub_c = do
+        (_, stub_o) <- runPipeline StopLn hsc_env (stub_c,Nothing)  Nothing
+                                   Temporary Nothing{-no ModLocation-} Nothing
 
+        return stub_o
 
 -- ---------------------------------------------------------------------------
 -- Link
 
-link :: GhcLink                        -- interactive or batch
-     -> DynFlags               -- dynamic flags
-     -> Bool                   -- attempt linking in batch mode?
-     -> HomePackageTable       -- what to link
+link :: GhcLink                 -- interactive or batch
+     -> DynFlags                -- dynamic flags
+     -> Bool                    -- attempt linking in batch mode?
+     -> HomePackageTable        -- what to link
      -> IO SuccessFlag
 
 -- For the moment, in the batch linker, we don't bother to tell doLink
@@ -263,167 +268,248 @@ link :: GhcLink                 -- interactive or batch
 -- exports main, i.e., we have good reason to believe that linking
 -- will succeed.
 
-#ifdef GHCI
-link LinkInMemory dflags batch_attempt_linking hpt
-    = do -- Not Linking...(demand linker will do the job)
-        return Succeeded
-#endif
+link LinkInMemory _ _ _
+    = if cGhcWithInterpreter == "YES"
+      then -- Not Linking...(demand linker will do the job)
+           return Succeeded
+      else panicBadLink LinkInMemory
 
-link NoLink dflags batch_attempt_linking hpt
+link NoLink _ _ _
    = return Succeeded
 
 link LinkBinary dflags batch_attempt_linking hpt
+   = link' dflags batch_attempt_linking hpt
+
+link LinkDynLib dflags batch_attempt_linking hpt
+   = link' dflags batch_attempt_linking hpt
+
+panicBadLink :: GhcLink -> a
+panicBadLink other = panic ("link: GHC not built to link this way: " ++
+                            show other)
+
+link' :: DynFlags                -- dynamic flags
+      -> Bool                    -- attempt linking in batch mode?
+      -> HomePackageTable        -- what to link
+      -> IO SuccessFlag
+
+link' dflags batch_attempt_linking hpt
    | batch_attempt_linking
-   = do 
-       let 
-           home_mod_infos = eltsUFM hpt
+   = do
+        let
+            home_mod_infos = eltsUFM hpt
 
-           -- the packages we depend on
-           pkg_deps  = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos
+            -- the packages we depend on
+            pkg_deps  = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos
 
-           -- the linkables to link
-           linkables = map (expectJust "link".hm_linkable) home_mod_infos
+            -- the linkables to link
+            linkables = map (expectJust "link".hm_linkable) home_mod_infos
 
         debugTraceMsg dflags 3 (text "link: linkables are ..." $$ vcat (map ppr linkables))
 
-       -- check for the -no-link flag
-       if isNoLink (ghcLink dflags)
-         then do debugTraceMsg dflags 3 (text "link(batch): linking omitted (-c flag given).")
-                 return Succeeded
-         else do
+        -- check for the -no-link flag
+        if isNoLink (ghcLink dflags)
+          then do debugTraceMsg dflags 3 (text "link(batch): linking omitted (-c flag given).")
+                  return Succeeded
+          else do
 
-       let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
-           obj_files = concatMap getOfiles linkables
+        let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
+            obj_files = concatMap getOfiles linkables
 
-           exe_file = exeFileName dflags
+            exe_file = exeFileName dflags
 
-       -- if the modification time on the executable is later than the
-       -- modification times on all of the objects, then omit linking
-       -- (unless the -no-recomp flag was given).
-       e_exe_time <- IO.try $ getModificationTime exe_file
-       let linking_needed 
-               | Left _  <- e_exe_time = True
-               | Right t <- e_exe_time = 
-                       any (t <) (map linkableTime linkables)
+        linking_needed <- linkingNeeded dflags linkables pkg_deps
 
-       if not (dopt Opt_ForceRecomp dflags) && not linking_needed
-          then do debugTraceMsg dflags 2 (text exe_file <+> ptext SLIT("is up to date, linking not required."))
-                  return Succeeded
-          else do
+        if not (dopt Opt_ForceRecomp dflags) && not linking_needed
+           then do debugTraceMsg dflags 2 (text exe_file <+> ptext (sLit "is up to date, linking not required."))
+                   return Succeeded
+           else do
 
-       debugTraceMsg dflags 1 (ptext SLIT("Linking") <+> text exe_file
-                                <+> text "...")
+        debugTraceMsg dflags 1 (ptext (sLit "Linking") <+> text exe_file
+                                 <+> text "...")
 
-       -- Don't showPass in Batch mode; doLink will do that for us.
-       let link = case ghcLink dflags of
-               MkDLL       -> doMkDLL
-               LinkBinary  -> staticLink
-       link dflags obj_files pkg_deps
+        -- Don't showPass in Batch mode; doLink will do that for us.
+        let link = case ghcLink dflags of
+                LinkBinary  -> linkBinary
+                LinkDynLib  -> linkDynLib
+                other       -> panicBadLink other
+        link dflags obj_files pkg_deps
 
         debugTraceMsg dflags 3 (text "link: done")
 
-       -- staticLink only returns if it succeeds
+        -- linkBinary only returns if it succeeds
         return Succeeded
 
    | otherwise
    = do debugTraceMsg dflags 3 (text "link(batch): upsweep (partially) failed OR" $$
                                 text "   Main.main not exported; not linking.")
         return Succeeded
-      
+
+
+linkingNeeded :: DynFlags -> [Linkable] -> [PackageId] -> IO Bool
+linkingNeeded dflags linkables pkg_deps = do
+        -- if the modification time on the executable is later than the
+        -- modification times on all of the objects and libraries, then omit
+        -- linking (unless the -fforce-recomp flag was given).
+  let exe_file = exeFileName dflags
+  e_exe_time <- tryIO $ getModificationTime exe_file
+  case e_exe_time of
+    Left _  -> return True
+    Right t -> do
+        -- first check object files and extra_ld_inputs
+        extra_ld_inputs <- readIORef v_Ld_inputs
+        e_extra_times <- mapM (tryIO . getModificationTime) extra_ld_inputs
+        let (errs,extra_times) = splitEithers e_extra_times
+        let obj_times =  map linkableTime linkables ++ extra_times
+        if not (null errs) || any (t <) obj_times
+            then return True
+            else do
+
+        -- next, check libraries. XXX this only checks Haskell libraries,
+        -- not extra_libraries or -l things from the command line.
+        let pkg_map = pkgIdMap (pkgState dflags)
+            pkg_hslibs  = [ (libraryDirs c, lib)
+                          | Just c <- map (lookupPackage pkg_map) pkg_deps,
+                            lib <- packageHsLibs dflags c ]
+
+        pkg_libfiles <- mapM (uncurry findHSLib) pkg_hslibs
+        if any isNothing pkg_libfiles then return True else do
+        e_lib_times <- mapM (tryIO . getModificationTime)
+                          (catMaybes pkg_libfiles)
+        let (lib_errs,lib_times) = splitEithers e_lib_times
+        if not (null lib_errs) || any (t <) lib_times
+           then return True
+           else checkLinkInfo dflags pkg_deps exe_file
+
+-- Returns 'False' if it was, and we can avoid linking, because the
+-- previous binary was linked with "the same options".
+checkLinkInfo :: DynFlags -> [PackageId] -> FilePath -> IO Bool
+checkLinkInfo dflags pkg_deps exe_file
+ | isWindowsTarget || isDarwinTarget
+ -- ToDo: Windows and OS X do not use the ELF binary format, so
+ -- readelf does not work there.  We need to find another way to do
+ -- this.
+ = return False -- conservatively we should return True, but not
+                -- linking in this case was the behaviour for a long
+                -- time so we leave it as-is.
+ | otherwise
+ = do
+   link_info <- getLinkInfo dflags pkg_deps
+   debugTraceMsg dflags 3 $ text ("Link info: " ++ link_info)
+   m_exe_link_info <- readElfSection dflags ghcLinkInfoSectionName exe_file
+   debugTraceMsg dflags 3 $ text ("Exe link info: " ++ show m_exe_link_info)
+   return (Just link_info /= m_exe_link_info)
+
+ghcLinkInfoSectionName :: String
+ghcLinkInfoSectionName = ".debug-ghc-link-info"
+   -- if we use the ".debug" prefix, then strip will strip it by default
+
+findHSLib :: [String] -> String -> IO (Maybe FilePath)
+findHSLib dirs lib = do
+  let batch_lib_file = "lib" ++ lib <.> "a"
+  found <- filterM doesFileExist (map (</> batch_lib_file) dirs)
+  case found of
+    [] -> return Nothing
+    (x:_) -> return (Just x)
 
 -- -----------------------------------------------------------------------------
 -- Compile files in one-shot mode.
 
-oneShot :: DynFlags -> Phase -> [(String, Maybe Phase)] -> IO ()
-oneShot dflags stop_phase srcs = do
-  o_files <- mapM (compileFile dflags stop_phase) srcs
-  doLink dflags stop_phase o_files
+oneShot :: HscEnv -> Phase -> [(String, Maybe Phase)] -> IO ()
+oneShot hsc_env stop_phase srcs = do
+  o_files <- mapM (compileFile hsc_env stop_phase) srcs
+  doLink (hsc_dflags hsc_env) stop_phase o_files
 
-compileFile :: DynFlags -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
-compileFile dflags stop_phase (src, mb_phase) = do
+compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
+compileFile hsc_env stop_phase (src, mb_phase) = do
    exists <- doesFileExist src
-   when (not exists) $ 
-       throwDyn (CmdLineError ("does not exist: " ++ src))
-   
+   when (not exists) $
+        ghcError (CmdLineError ("does not exist: " ++ src))
+
    let
-       split     = dopt Opt_SplitObjs dflags
-       mb_o_file = outputFile dflags
-       ghc_link  = ghcLink dflags      -- Set by -c or -no-link
+        dflags = hsc_dflags hsc_env
+        split     = dopt Opt_SplitObjs dflags
+        mb_o_file = outputFile dflags
+        ghc_link  = ghcLink dflags      -- Set by -c or -no-link
 
-       -- When linking, the -o argument refers to the linker's output. 
-       -- otherwise, we use it as the name for the pipeline's output.
+        -- When linking, the -o argument refers to the linker's output.
+        -- otherwise, we use it as the name for the pipeline's output.
         output
-        | StopLn <- stop_phase, not (isNoLink ghc_link) = Persistent
-               -- -o foo applies to linker
-        | Just o_file <- mb_o_file = SpecificFile o_file
-               -- -o foo applies to the file we are compiling now
-        | otherwise = Persistent
-
-        stop_phase' = case stop_phase of 
-                       As | split -> SplitAs
-                       other      -> stop_phase
-
-   (_, out_file) <- runPipeline stop_phase' dflags
-                         (src, mb_phase) Nothing output 
-                          Nothing{-no ModLocation-}
+         | StopLn <- stop_phase, not (isNoLink ghc_link) = Persistent
+                -- -o foo applies to linker
+         | Just o_file <- mb_o_file = SpecificFile o_file
+                -- -o foo applies to the file we are compiling now
+         | otherwise = Persistent
+
+        stop_phase' = case stop_phase of
+                        As | split -> SplitAs
+                        _          -> stop_phase
+
+   ( _, out_file) <- runPipeline stop_phase' hsc_env
+                            (src, mb_phase) Nothing output
+                            Nothing{-no ModLocation-} Nothing
    return out_file
 
 
 doLink :: DynFlags -> Phase -> [FilePath] -> IO ()
 doLink dflags stop_phase o_files
   | not (isStopLn stop_phase)
-  = return ()          -- We stopped before the linking phase
+  = return ()           -- We stopped before the linking phase
 
   | otherwise
   = case ghcLink dflags of
-       NoLink     -> return ()
-       LinkBinary -> staticLink dflags o_files link_pkgs
-       MkDLL      -> doMkDLL dflags o_files link_pkgs
-  where
-   -- Always link in the haskell98 package for static linking.  Other
-   -- packages have to be specified via the -package flag.
-    link_pkgs = [haskell98PackageId]
+        NoLink     -> return ()
+        LinkBinary -> linkBinary dflags o_files []
+        LinkDynLib -> linkDynLib dflags o_files []
+        other      -> panicBadLink other
 
 
 -- ---------------------------------------------------------------------------
--- Run a compilation pipeline, consisting of multiple phases.
 
+data PipelineOutput
+  = Temporary
+        -- ^ Output should be to a temporary file: we're going to
+        -- run more compilation steps on this output later.
+  | Persistent
+        -- ^ We want a persistent file, i.e. a file in the current directory
+        -- derived from the input filename, but with the appropriate extension.
+        -- eg. in "ghc -c Foo.hs" the output goes into ./Foo.o.
+  | SpecificFile FilePath
+        -- ^ The output must go into the specified file.
+
+-- | Run a compilation pipeline, consisting of multiple phases.
+--
 -- This is the interface to the compilation pipeline, which runs
 -- a series of compilation steps on a single source file, specifying
 -- at which stage to stop.
-
+--
 -- The DynFlags can be modified by phases in the pipeline (eg. by
--- GHC_OPTIONS pragmas), and the changes affect later phases in the
+-- OPTIONS_GHC pragmas), and the changes affect later phases in the
 -- pipeline.
-
-data PipelineOutput 
-  = Temporary
-       -- output should be to a temporary file: we're going to
-       -- run more compilation steps on this output later
-  | Persistent
-       -- we want a persistent file, i.e. a file in the current directory
-       -- derived from the input filename, but with the appropriate extension.
-       -- eg. in "ghc -c Foo.hs" the output goes into ./Foo.o.
-  | SpecificFile FilePath
-       -- the output must go into the specified file.
-
 runPipeline
-  :: Phase                     -- When to stop
-  -> DynFlags                  -- Dynamic flags
-  -> (FilePath,Maybe Phase)     -- Input filename (and maybe -x suffix)
-  -> Maybe FilePath             -- original basename (if different from ^^^)
-  -> PipelineOutput            -- Output filename
-  -> Maybe ModLocation          -- A ModLocation, if this is a Haskell module
-  -> IO (DynFlags, FilePath)   -- (final flags, output filename)
-
-runPipeline stop_phase dflags (input_fn, mb_phase) mb_basename output maybe_loc
+  :: Phase                      -- ^ When to stop
+  -> HscEnv                     -- ^ Compilation environment
+  -> (FilePath,Maybe Phase)     -- ^ Input filename (and maybe -x suffix)
+  -> Maybe FilePath             -- ^ original basename (if different from ^^^)
+  -> PipelineOutput             -- ^ Output filename
+  -> Maybe ModLocation          -- ^ A ModLocation, if this is a Haskell module
+  -> Maybe FilePath             -- ^ stub object, if we have one
+  -> IO (DynFlags, FilePath)     -- ^ (final flags, output filename)
+
+runPipeline stop_phase hsc_env0 (input_fn, mb_phase)
+            mb_basename output maybe_loc maybe_stub_o
   = do
-  let (input_basename, suffix) = splitFilename input_fn
+  let dflags0 = hsc_dflags hsc_env0
+      (input_basename, suffix) = splitExtension input_fn
+      suffix' = drop 1 suffix -- strip off the .
       basename | Just b <- mb_basename = b
                | otherwise             = input_basename
 
-       -- If we were given a -x flag, then use that phase to start from
-      start_phase = fromMaybe (startPhase suffix) mb_phase
+      -- Decide where dump files should go based on the pipeline output
+      dflags = dflags0 { dumpPrefix = Just (basename ++ ".") }
+      hsc_env = hsc_env0 {hsc_dflags = dflags}
+
+        -- If we were given a -x flag, then use that phase to start from
+      start_phase = fromMaybe (startPhase suffix') mb_phase
 
   -- We want to catch cases of "you can't get there from here" before
   -- we start the pipeline, because otherwise it will just run off the
@@ -433,18 +519,26 @@ runPipeline stop_phase dflags (input_fn, mb_phase) mb_basename output maybe_loc
   -- before B in a normal compilation pipeline.
 
   when (not (start_phase `happensBefore` stop_phase)) $
-       throwDyn (UsageError 
-                   ("cannot compile this file to desired target: "
-                      ++ input_fn))
+        ghcError (UsageError
+                    ("cannot compile this file to desired target: "
+                       ++ input_fn))
 
   -- this is a function which will be used to calculate output file names
   -- as we go along (we partially apply it to some of its inputs here)
   let get_output_fn = getOutputFilename stop_phase output basename
 
   -- Execute the pipeline...
-  (dflags', output_fn, maybe_loc) <- 
-       pipeLoop dflags start_phase stop_phase input_fn 
-                basename suffix get_output_fn maybe_loc
+  let env   = PipeEnv{ stop_phase,
+                       src_basename = basename,
+                       src_suffix = suffix',
+                       output_spec = output }
+
+      state = PipeState{ hsc_env, maybe_loc, maybe_stub_o = maybe_stub_o }
+
+  (state', output_fn) <- unP (pipeLoop start_phase input_fn) env state
+
+  let PipeState{ hsc_env=hsc_env', maybe_loc } = state'
+      dflags' = hsc_dflags hsc_env'
 
   -- Sometimes, a compilation phase doesn't actually generate any output
   -- (eg. the CPP phase when -fcpp is not turned on).  If we end on this
@@ -452,45 +546,112 @@ runPipeline stop_phase dflags (input_fn, mb_phase) mb_basename output maybe_loc
   -- copy the file, remembering to prepend a {-# LINE #-} pragma so that
   -- further compilation stages can tell what the original filename was.
   case output of
-    Temporary -> 
-       return (dflags', output_fn)
-    _other ->
-       do final_fn <- get_output_fn dflags' stop_phase maybe_loc
-          when (final_fn /= output_fn) $ do
+    Temporary ->
+        return (dflags', output_fn)
+    _other -> 
+        do final_fn <- get_output_fn dflags' stop_phase maybe_loc
+           when (final_fn /= output_fn) $ do
               let msg = ("Copying `" ++ output_fn ++"' to `" ++ final_fn ++ "'")
                   line_prag = Just ("{-# LINE 1 \"" ++ input_fn ++ "\" #-}\n")
-             copyWithHeader dflags msg line_prag output_fn final_fn
-          return (dflags', final_fn)
-
-
-
-pipeLoop :: DynFlags -> Phase -> Phase 
-        -> FilePath  -> String -> Suffix
-        -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath)
-        -> Maybe ModLocation
-        -> IO (DynFlags, FilePath, Maybe ModLocation)
+              copyWithHeader dflags msg line_prag output_fn final_fn
+           return (dflags', final_fn)
 
-pipeLoop dflags phase stop_phase 
-        input_fn orig_basename orig_suff 
-        orig_get_output_fn maybe_loc
-
-  | phase `eqPhase` stop_phase           -- All done
-  = return (dflags, input_fn, maybe_loc)
+-- -----------------------------------------------------------------------------
+-- The pipeline uses a monad to carry around various bits of information
+
+-- PipeEnv: invariant information passed down
+data PipeEnv = PipeEnv {
+       stop_phase   :: Phase,       -- ^ Stop just before this phase
+       src_basename :: String,      -- ^ basename of original input source
+       src_suffix   :: String,      -- ^ its extension
+       output_spec  :: PipelineOutput -- ^ says where to put the pipeline output
+  }
+
+-- PipeState: information that might change during a pipeline run
+data PipeState = PipeState {
+       hsc_env   :: HscEnv,
+          -- ^ only the DynFlags change in the HscEnv.  The DynFlags change
+          -- at various points, for example when we read the OPTIONS_GHC
+          -- pragmas in the Cpp phase.
+       maybe_loc :: Maybe ModLocation,
+          -- ^ the ModLocation.  This is discovered during compilation,
+          -- in the Hsc phase where we read the module header.
+       maybe_stub_o :: Maybe FilePath
+          -- ^ the stub object.  This is set by the Hsc phase if a stub
+          -- object was created.  The stub object will be joined with
+          -- the main compilation object using "ld -r" at the end.
+  }
+
+getPipeEnv :: CompPipeline PipeEnv
+getPipeEnv = P $ \env state -> return (state, env)
+
+getPipeState :: CompPipeline PipeState
+getPipeState = P $ \_env state -> return (state, state)
+
+getDynFlags :: CompPipeline DynFlags
+getDynFlags = P $ \_env state -> return (state, hsc_dflags (hsc_env state))
+
+setDynFlags :: DynFlags -> CompPipeline ()
+setDynFlags dflags = P $ \_env state ->
+  return (state{hsc_env= (hsc_env state){ hsc_dflags = dflags }}, ())
+
+setModLocation :: ModLocation -> CompPipeline ()
+setModLocation loc = P $ \_env state ->
+  return (state{ maybe_loc = Just loc }, ())
+
+setStubO :: FilePath -> CompPipeline ()
+setStubO stub_o = P $ \_env state ->
+  return (state{ maybe_stub_o = Just stub_o }, ())
+
+newtype CompPipeline a = P { unP :: PipeEnv -> PipeState -> IO (PipeState, a) }
+
+instance Monad CompPipeline where
+  return a = P $ \_env state -> return (state, a)
+  P m >>= k = P $ \env state -> do (state',a) <- m env state
+                                   unP (k a) env state'
+
+io :: IO a -> CompPipeline a
+io m = P $ \_env state -> do a <- m; return (state, a)
+
+phaseOutputFilename :: Phase{-next phase-} -> CompPipeline FilePath
+phaseOutputFilename next_phase = do
+  PipeEnv{stop_phase, src_basename, output_spec} <- getPipeEnv
+  PipeState{maybe_loc, hsc_env} <- getPipeState
+  let dflags = hsc_dflags hsc_env
+  io $ getOutputFilename stop_phase output_spec
+                         src_basename dflags next_phase maybe_loc
 
-  | not (phase `happensBefore` stop_phase)
-       -- Something has gone wrong.  We'll try to cover all the cases when
-       -- this could happen, so if we reach here it is a panic.
-       -- eg. it might happen if the -C flag is used on a source file that
-       -- has {-# OPTIONS -fasm #-}.
-  = panic ("pipeLoop: at phase " ++ show phase ++ 
-          " but I wanted to stop at phase " ++ show stop_phase)
+-- ---------------------------------------------------------------------------
+-- outer pipeline loop
+
+-- | pipeLoop runs phases until we reach the stop phase
+pipeLoop :: Phase -> FilePath -> CompPipeline FilePath
+pipeLoop phase input_fn = do
+  PipeEnv{stop_phase} <- getPipeEnv
+  PipeState{hsc_env}  <- getPipeState
+  case () of
+   _ | phase `eqPhase` stop_phase            -- All done
+     -> return input_fn
+
+     | not (phase `happensBefore` stop_phase)
+        -- Something has gone wrong.  We'll try to cover all the cases when
+        -- this could happen, so if we reach here it is a panic.
+        -- eg. it might happen if the -C flag is used on a source file that
+        -- has {-# OPTIONS -fasm #-}.
+     -> panic ("pipeLoop: at phase " ++ show phase ++
+           " but I wanted to stop at phase " ++ show stop_phase)
+
+     | otherwise
+     -> do io $ debugTraceMsg (hsc_dflags hsc_env) 4
+                         (ptext (sLit "Running phase") <+> ppr phase)
+           dflags <- getDynFlags
+           (next_phase, output_fn) <- runPhase phase input_fn dflags
+           pipeLoop next_phase output_fn
 
-  | otherwise 
-  = do { (next_phase, dflags', maybe_loc, output_fn)
-               <- runPhase phase stop_phase dflags orig_basename 
-                           orig_suff input_fn orig_get_output_fn maybe_loc
-       ; pipeLoop dflags' next_phase stop_phase output_fn
-                  orig_basename orig_suff orig_get_output_fn maybe_loc }
+-- -----------------------------------------------------------------------------
+-- In each phase, we need to know into what filename to generate the
+-- output.  All the logic about which filenames we generate output
+-- into is embodied in the following function.
 
 getOutputFilename
   :: Phase -> PipelineOutput -> String
@@ -498,51 +659,51 @@ getOutputFilename
 getOutputFilename stop_phase output basename
  = func
  where
-       func dflags next_phase maybe_location
-          | is_last_phase, Persistent <- output     = persistent_fn
-          | is_last_phase, SpecificFile f <- output = return f
-          | keep_this_output                        = persistent_fn
-          | otherwise                               = newTempName dflags suffix
-          where
-               hcsuf      = hcSuf dflags
-               odir       = objectDir dflags
-               osuf       = objectSuf dflags
-               keep_hc    = dopt Opt_KeepHcFiles dflags
-               keep_raw_s = dopt Opt_KeepRawSFiles dflags
-               keep_s     = dopt Opt_KeepSFiles dflags
-
-               myPhaseInputExt HCc    = hcsuf
-               myPhaseInputExt StopLn = osuf
-               myPhaseInputExt other  = phaseInputExt other
-
-               is_last_phase = next_phase `eqPhase` stop_phase
-
-               -- sometimes, we keep output from intermediate stages
-               keep_this_output = 
-                    case next_phase of
-                            StopLn              -> True
-                            Mangle | keep_raw_s -> True
-                            As     | keep_s     -> True
-                            HCc    | keep_hc    -> True
-                            _other              -> False
-
-               suffix = myPhaseInputExt next_phase
-
-               -- persistent object files get put in odir
-               persistent_fn 
-                  | StopLn <- next_phase = return odir_persistent
-                  | otherwise            = return persistent
-
-               persistent = basename `joinFileExt` suffix
-
-               odir_persistent
-                  | Just loc <- maybe_location = ml_obj_file loc
-                  | Just d <- odir = d `joinFileName` persistent
-                  | otherwise      = persistent
+        func dflags next_phase maybe_location
+           | is_last_phase, Persistent <- output     = persistent_fn
+           | is_last_phase, SpecificFile f <- output = return f
+           | keep_this_output                        = persistent_fn
+           | otherwise                               = newTempName dflags suffix
+           where
+                hcsuf      = hcSuf dflags
+                odir       = objectDir dflags
+                osuf       = objectSuf dflags
+                keep_hc    = dopt Opt_KeepHcFiles dflags
+                keep_s     = dopt Opt_KeepSFiles dflags
+                keep_bc    = dopt Opt_KeepLlvmFiles dflags
+
+                myPhaseInputExt HCc       = hcsuf
+                myPhaseInputExt MergeStub = osuf
+                myPhaseInputExt StopLn    = osuf
+                myPhaseInputExt other     = phaseInputExt other
+
+                is_last_phase = next_phase `eqPhase` stop_phase
+
+                -- sometimes, we keep output from intermediate stages
+                keep_this_output =
+                     case next_phase of
+                             As      | keep_s     -> True
+                             LlvmOpt | keep_bc    -> True
+                             HCc     | keep_hc    -> True
+                             _other               -> False
+
+                suffix = myPhaseInputExt next_phase
+
+                -- persistent object files get put in odir
+                persistent_fn
+                   | StopLn <- next_phase = return odir_persistent
+                   | otherwise            = return persistent
+
+                persistent = basename <.> suffix
+
+                odir_persistent
+                   | Just loc <- maybe_location = ml_obj_file loc
+                   | Just d <- odir = d </> persistent
+                   | otherwise      = persistent
 
 
 -- -----------------------------------------------------------------------------
--- Each phase in the pipeline returns the next phase to execute, and the
+-- | Each phase in the pipeline returns the next phase to execute, and the
 -- name of the file in which the output was placed.
 --
 -- We must do things dynamically this way, because we often don't know
@@ -550,142 +711,178 @@ getOutputFilename stop_phase output basename
 -- compilation: for example, an {-# OPTIONS -fasm #-} at the beginning
 -- of a source file can change the latter stages of the pipeline from
 -- taking the via-C route to using the native code generator.
+--
+runPhase :: Phase       -- ^ Run this phase
+         -> FilePath    -- ^ name of the input file
+         -> DynFlags    -- ^ for convenience, we pass the current dflags in
+         -> CompPipeline (Phase,               -- next phase to run
+                          FilePath)            -- output filename
+
+        -- Invariant: the output filename always contains the output
+        -- Interesting case: Hsc when there is no recompilation to do
+        --                   Then the output filename is still a .o file
 
-runPhase :: Phase      -- Do this phase first
-        -> Phase       -- Stop just before this phase
-        -> DynFlags
-        -> String      -- basename of original input source
-        -> String      -- its extension
-        -> FilePath    -- name of file which contains the input to this phase.
-        -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath)
-                       -- how to calculate the output filename
-        -> Maybe ModLocation           -- the ModLocation, if we have one
-        -> IO (Phase,                  -- next phase
-               DynFlags,               -- new dynamic flags
-               Maybe ModLocation,      -- the ModLocation, if we have one
-               FilePath)               -- output filename
-
-       -- Invariant: the output filename always contains the output
-       -- Interesting case: Hsc when there is no recompilation to do
-       --                   Then the output filename is still a .o file 
 
 -------------------------------------------------------------------------------
--- Unlit phase 
+-- Unlit phase
+
+runPhase (Unlit sf) input_fn dflags
+  = do
+       output_fn <- phaseOutputFilename (Cpp sf)
 
-runPhase (Unlit sf) _stop dflags _basename _suff input_fn get_output_fn maybe_loc
-  = do let unlit_flags = getOpts dflags opt_L
-       -- The -h option passes the file name for unlit to put in a #line directive
-       output_fn <- get_output_fn dflags (Cpp sf) maybe_loc
+       let unlit_flags = getOpts dflags opt_L
+           flags = map SysTools.Option unlit_flags ++
+                   [ -- The -h option passes the file name for unlit to
+                     -- put in a #line directive
+                     SysTools.Option     "-h"
+                     -- cpp interprets \b etc as escape sequences,
+                     -- so we use / for filenames in pragmas
+                   , SysTools.Option $ reslash Forwards $ normalise input_fn
+                   , SysTools.FileOption "" input_fn
+                   , SysTools.FileOption "" output_fn
+                   ]
 
-       SysTools.runUnlit dflags 
-               (map SysTools.Option unlit_flags ++
-                                 [ SysTools.Option     "-h"
-                         , SysTools.Option     input_fn
-                         , SysTools.FileOption "" input_fn
-                         , SysTools.FileOption "" output_fn
-                         ])
+       io $ SysTools.runUnlit dflags flags
 
-       return (Cpp sf, dflags, maybe_loc, output_fn)
+       return (Cpp sf, output_fn)
 
 -------------------------------------------------------------------------------
 -- Cpp phase : (a) gets OPTIONS out of file
---            (b) runs cpp if necessary
+--             (b) runs cpp if necessary
+
+runPhase (Cpp sf) input_fn dflags0
+  = do
+       src_opts <- io $ getOptionsFromFile dflags0 input_fn
+       (dflags1, unhandled_flags, warns)
+           <- io $ parseDynamicNoPackageFlags dflags0 src_opts
+       setDynFlags dflags1
+       io $ checkProcessArgsResult unhandled_flags
 
-runPhase (Cpp sf) _stop dflags0 basename suff input_fn get_output_fn maybe_loc
-  = do src_opts <- getOptionsFromFile input_fn
-       (dflags,unhandled_flags) <- parseDynamicFlags dflags0 (map unLoc src_opts)
-       checkProcessArgsResult unhandled_flags (basename `joinFileExt` suff)
+       if not (xopt Opt_Cpp dflags1) then do
+           -- we have to be careful to emit warnings only once.
+           unless (dopt Opt_Pp dflags1) $ io $ handleFlagWarnings dflags1 warns
 
-       if not (dopt Opt_Cpp dflags) then
            -- no need to preprocess CPP, just pass input file along
-          -- to the next phase of the pipeline.
-          return (HsPp sf, dflags, maybe_loc, input_fn)
-       else do
-           output_fn <- get_output_fn dflags (HsPp sf) maybe_loc
-           doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn
-           return (HsPp sf, dflags, maybe_loc, output_fn)
+           -- to the next phase of the pipeline.
+           return (HsPp sf, input_fn)
+        else do
+            output_fn <- phaseOutputFilename (HsPp sf)
+            io $ doCpp dflags1 True{-raw-} False{-no CC opts-} input_fn output_fn
+            -- re-read the pragmas now that we've preprocessed the file
+            -- See #2464,#3457
+            src_opts <- io $ getOptionsFromFile dflags0 output_fn
+            (dflags2, unhandled_flags, warns)
+                <- io $ parseDynamicNoPackageFlags dflags0 src_opts
+            io $ checkProcessArgsResult unhandled_flags
+            unless (dopt Opt_Pp dflags2) $ io $ handleFlagWarnings dflags2 warns
+            -- the HsPp pass below will emit warnings
+
+            setDynFlags dflags2
+
+            return (HsPp sf, output_fn)
 
 -------------------------------------------------------------------------------
--- HsPp phase 
+-- HsPp phase
 
-runPhase (HsPp sf) _stop dflags basename suff input_fn get_output_fn maybe_loc
-  = do if not (dopt Opt_Pp dflags) then
+runPhase (HsPp sf) input_fn dflags
+  = do
+       if not (dopt Opt_Pp dflags) then
            -- no need to preprocess, just pass input file along
-          -- to the next phase of the pipeline.
-          return (Hsc sf, dflags, maybe_loc, input_fn)
-       else do
-           let hspp_opts = getOpts dflags opt_F
-           let orig_fn = basename `joinFileExt` suff
-           output_fn <- get_output_fn dflags (Hsc sf) maybe_loc
-           SysTools.runPp dflags
-                          ( [ SysTools.Option     orig_fn
-                            , SysTools.Option     input_fn
-                            , SysTools.FileOption "" output_fn
-                            ] ++
-                            map SysTools.Option hspp_opts
-                          )
-           return (Hsc sf, dflags, maybe_loc, output_fn)
+           -- to the next phase of the pipeline.
+          return (Hsc sf, input_fn)
+        else do
+            let hspp_opts = getOpts dflags opt_F
+            PipeEnv{src_basename, src_suffix} <- getPipeEnv
+            let orig_fn = src_basename <.> src_suffix
+            output_fn <- phaseOutputFilename (Hsc sf)
+            io $ SysTools.runPp dflags
+                           ( [ SysTools.Option     orig_fn
+                             , SysTools.Option     input_fn
+                             , SysTools.FileOption "" output_fn
+                             ] ++
+                             map SysTools.Option hspp_opts
+                           )
+
+            -- re-read pragmas now that we've parsed the file (see #3674)
+            src_opts <- io $ getOptionsFromFile dflags output_fn
+            (dflags1, unhandled_flags, warns)
+                <- io $ parseDynamicNoPackageFlags dflags src_opts
+            setDynFlags dflags1
+            io $ checkProcessArgsResult unhandled_flags
+            io $ handleFlagWarnings dflags1 warns
+
+            return (Hsc sf, output_fn)
 
 -----------------------------------------------------------------------------
 -- Hsc phase
 
 -- Compilation of a single module, in "legacy" mode (_not_ under
 -- the direction of the compilation manager).
-runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _maybe_loc 
- = do  -- normal Hsc mode, not mkdependHS
+runPhase (Hsc src_flavour) input_fn dflags0
+ = do   -- normal Hsc mode, not mkdependHS
+
+        PipeEnv{ stop_phase=stop,
+                 src_basename=basename,
+                 src_suffix=suff } <- getPipeEnv
 
   -- we add the current directory (i.e. the directory in which
-  -- the .hs files resides) to the import path, since this is
+  -- the .hs files resides) to the include path, since this is
   -- what gcc does, and it's probably what you want.
-       let current_dir = directoryOf basename
-       
-           paths = includePaths dflags0
-           dflags = dflags0 { includePaths = current_dir : paths }
-       
+        let current_dir = case takeDirectory basename of
+                      "" -> "." -- XXX Hack
+                      d -> d
+
+            paths = includePaths dflags0
+            dflags = dflags0 { includePaths = current_dir : paths }
+
+        setDynFlags dflags
+
   -- gather the imports and module name
-        (hspp_buf,mod_name) <- 
+        (hspp_buf,mod_name,imps,src_imps) <- io $
             case src_flavour of
-               ExtCoreFile -> do {  -- no explicit imports in ExtCore input.
-                                 ; m <- getCoreModuleName input_fn
-                                 ; return (Nothing, mkModuleName m) }
+                ExtCoreFile -> do  -- no explicit imports in ExtCore input.
+                    m <- getCoreModuleName input_fn
+                    return (Nothing, mkModuleName m, [], [])
 
-               other -> do { buf <- hGetStringBuffer input_fn
-                           ; (_,_,L _ mod_name) <- getImports dflags buf input_fn
-                           ; return (Just buf, mod_name) }
+                _           -> do
+                    buf <- hGetStringBuffer input_fn
+                    (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename <.> suff)
+                    return (Just buf, mod_name, imps, src_imps)
 
   -- Build a ModLocation to pass to hscMain.
   -- The source filename is rather irrelevant by now, but it's used
-  -- by hscMain for messages.  hscMain also needs 
+  -- by hscMain for messages.  hscMain also needs
   -- the .hi and .o filenames, and this is as good a way
-  -- as any to generate them, and better than most. (e.g. takes 
+  -- as any to generate them, and better than most. (e.g. takes
   -- into accout the -osuf flags)
-       location1 <- mkHomeModLocation2 dflags mod_name basename suff
+        location1 <- io $ mkHomeModLocation2 dflags mod_name basename suff
 
   -- Boot-ify it if necessary
-       let location2 | isHsBoot src_flavour = addBootSuffixLocn location1
-                     | otherwise            = location1 
-                                       
+        let location2 | isHsBoot src_flavour = addBootSuffixLocn location1
+                      | otherwise            = location1
+
 
   -- Take -ohi into account if present
   -- This can't be done in mkHomeModuleLocation because
   -- it only applies to the module being compiles
-       let ohi = outputHi dflags
-           location3 | Just fn <- ohi = location2{ ml_hi_file = fn }
-                     | otherwise      = location2
+        let ohi = outputHi dflags
+            location3 | Just fn <- ohi = location2{ ml_hi_file = fn }
+                      | otherwise      = location2
 
   -- Take -o into account if present
   -- Very like -ohi, but we must *only* do this if we aren't linking
   -- (If we're linking then the -o applies to the linked thing, not to
   -- the object file for one module.)
   -- Note the nasty duplication with the same computation in compileFile above
-       let expl_o_file = outputFile dflags
-           location4 | Just ofile <- expl_o_file
-                     , isNoLink (ghcLink dflags)
-                     = location3 { ml_obj_file = ofile }
-                     | otherwise = location3
+        let expl_o_file = outputFile dflags
+            location4 | Just ofile <- expl_o_file
+                      , isNoLink (ghcLink dflags)
+                      = location3 { ml_obj_file = ofile }
+                      | otherwise = location3
 
-           o_file = ml_obj_file location4      -- The real object file
+            o_file = ml_obj_file location4      -- The real object file
 
+        setModLocation location4
 
   -- Figure out if the source has changed, for recompilation avoidance.
   --
@@ -694,101 +891,111 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma
   -- changed (which the compiler itself figures out).
   -- 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.
-       src_timestamp <- getModificationTime (basename `joinFileExt` suff)
+        src_timestamp <- io $ getModificationTime (basename <.> suff)
 
-       let force_recomp = dopt Opt_ForceRecomp dflags
-       source_unchanged <- 
+        let force_recomp = dopt Opt_ForceRecomp dflags
+            hsc_lang = hscTarget dflags
+        source_unchanged <- io $
           if force_recomp || not (isStopLn stop)
-               -- Set source_unchanged to False unconditionally if
-               --      (a) recompilation checker is off, or
-               --      (b) we aren't going all the way to .o file (e.g. ghc -S)
-            then return False  
-               -- Otherwise look at file modification dates
-            else do o_file_exists <- doesFileExist o_file
-                    if not o_file_exists
-                       then return False       -- Need to recompile
-                       else do t2 <- getModificationTime o_file
-                               if t2 > src_timestamp
-                                 then return True
-                                 else return False
+                -- Set source_unchanged to False unconditionally if
+                --      (a) recompilation checker is off, or
+                --      (b) we aren't going all the way to .o file (e.g. ghc -S)
+             then return False
+                -- Otherwise look at file modification dates
+             else do o_file_exists <- doesFileExist o_file
+                     if not o_file_exists
+                        then return False       -- Need to recompile
+                        else do t2 <- getModificationTime o_file
+                                if t2 > src_timestamp
+                                  then return True
+                                  else return False
 
   -- get the DynFlags
-       let hsc_lang = hscMaybeAdjustTarget dflags stop src_flavour (hscTarget dflags)
-       let next_phase = hscNextPhase dflags src_flavour hsc_lang
-       output_fn  <- get_output_fn dflags next_phase (Just location4)
+        let next_phase = hscNextPhase dflags src_flavour hsc_lang
+        output_fn  <- phaseOutputFilename next_phase
 
         let dflags' = dflags { hscTarget = hsc_lang,
-                              hscOutName = output_fn,
-                              extCoreName = basename ++ ".hcr" }
+                               hscOutName = output_fn,
+                               extCoreName = basename ++ ".hcr" }
 
-       hsc_env <- newHscEnv dflags'
+        setDynFlags dflags'
+        PipeState{hsc_env=hsc_env'} <- getPipeState
 
   -- Tell the finder cache about this module
-       mod <- addHomeModuleToFinder hsc_env mod_name location4
+        mod <- io $ addHomeModuleToFinder hsc_env' mod_name location4
 
   -- Make the ModSummary to hand to hscMain
-       let
-           unused_field = panic "runPhase:ModSummary field"
-               -- Some fields are not looked at by hscMain
-           mod_summary = ModSummary {  ms_mod       = mod, 
-                                       ms_hsc_src   = src_flavour,
-                                       ms_hspp_file = input_fn,
+        let
+            mod_summary = ModSummary {  ms_mod       = mod,
+                                        ms_hsc_src   = src_flavour,
+                                        ms_hspp_file = input_fn,
                                         ms_hspp_opts = dflags,
-                                       ms_hspp_buf  = hspp_buf,
-                                       ms_location  = location4,
-                                       ms_hs_date   = src_timestamp,
-                                       ms_obj_date  = Nothing,
-                                       ms_imps      = unused_field,
-                                       ms_srcimps   = unused_field }
+                                        ms_hspp_buf  = hspp_buf,
+                                        ms_location  = location4,
+                                        ms_hs_date   = src_timestamp,
+                                        ms_obj_date  = Nothing,
+                                        ms_imps      = imps,
+                                        ms_srcimps   = src_imps }
 
   -- run the compiler!
-       mbResult <- hscCompileOneShot hsc_env
-                         mod_summary source_unchanged 
-                         Nothing       -- No iface
+        result <- io $ hscCompileOneShot hsc_env'
+                          mod_summary source_unchanged
+                          Nothing       -- No iface
                           Nothing       -- No "module i of n" progress info
 
-       case mbResult of
-          Nothing -> throwDyn (PhaseFailed "hsc" (ExitFailure 1))
-          Just HscNoRecomp
-              -> do SysTools.touch dflags' "Touching object file" o_file
+        case result of
+          HscNoRecomp
+              -> do io $ SysTools.touch dflags' "Touching object file" o_file
                     -- The .o file must have a later modification date
                     -- than the source file (else we wouldn't be in HscNoRecomp)
                     -- but we touch it anyway, to keep 'make' happy (we think).
-                    return (StopLn, dflags', Just location4, o_file)
-          Just (HscRecomp hasStub)
-              -> do when hasStub $
-                         do stub_o <- compileStub dflags' mod location4
-                            consIORef v_Ld_inputs stub_o
-                    -- In the case of hs-boot files, generate a dummy .o-boot 
+                    return (StopLn, o_file)
+          (HscRecomp hasStub _)
+              -> do case hasStub of
+                      Nothing -> return ()
+                      Just stub_c ->
+                         do stub_o <- io $ compileStub hsc_env' stub_c
+                            setStubO stub_o
+                    -- In the case of hs-boot files, generate a dummy .o-boot
                     -- stamp file for the benefit of Make
                     when (isHsBoot src_flavour) $
-                      SysTools.touch dflags' "Touching object file" o_file
-                    return (next_phase, dflags', Just location4, output_fn)
+                      io $ SysTools.touch dflags' "Touching object file" o_file
+                    return (next_phase, output_fn)
 
 -----------------------------------------------------------------------------
 -- Cmm phase
 
-runPhase CmmCpp stop dflags basename suff input_fn get_output_fn maybe_loc
+runPhase CmmCpp input_fn dflags
   = do
-       output_fn <- get_output_fn dflags Cmm maybe_loc
-       doCpp dflags False{-not raw-} True{-include CC opts-} input_fn output_fn        
-       return (Cmm, dflags, maybe_loc, output_fn)
+       output_fn <- phaseOutputFilename Cmm
+       io $ doCpp dflags False{-not raw-} True{-include CC opts-}
+              input_fn output_fn
+       return (Cmm, output_fn)
 
-runPhase Cmm stop dflags basename suff input_fn get_output_fn maybe_loc
+runPhase Cmm input_fn dflags
   = do
-       let hsc_lang = hscMaybeAdjustTarget dflags stop HsSrcFile (hscTarget dflags)
-       let next_phase = hscNextPhase dflags HsSrcFile hsc_lang
-       output_fn <- get_output_fn dflags next_phase maybe_loc
+        PipeEnv{src_basename} <- getPipeEnv
+        let hsc_lang = hscTarget dflags
+
+        let next_phase = hscNextPhase dflags HsSrcFile hsc_lang
+
+        output_fn <- phaseOutputFilename next_phase
 
         let dflags' = dflags { hscTarget = hsc_lang,
-                              hscOutName = output_fn,
-                              extCoreName = basename ++ ".hcr" }
+                               hscOutName = output_fn,
+                               extCoreName = src_basename ++ ".hcr" }
 
-       ok <- hscCmmFile dflags' input_fn
+        setDynFlags dflags'
+        PipeState{hsc_env} <- getPipeState
 
-       when (not ok) $ throwDyn (PhaseFailed "cmm" (ExitFailure 1))
+        io $ hscCompileCmmFile hsc_env input_fn
 
-       return (next_phase, dflags, maybe_loc, output_fn)
+        -- XXX: catch errors above and convert them into ghcError?  Original
+        -- code was:
+        --
+        --when (not ok) $ ghcError (PhaseFailed "cmm" (ExitFailure 1))
+
+        return (next_phase, output_fn)
 
 -----------------------------------------------------------------------------
 -- Cc phase
@@ -796,288 +1003,482 @@ runPhase Cmm stop dflags basename suff input_fn get_output_fn maybe_loc
 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
 -- way too many hacks, and I can't say I've ever used it anyway.
 
-runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc
-   | cc_phase `eqPhase` Cc || cc_phase `eqPhase` Ccpp || cc_phase `eqPhase` HCc
-   = do        let cc_opts = getOpts dflags opt_c
-           hcc = cc_phase `eqPhase` HCc
+runPhase cc_phase input_fn dflags
+   | cc_phase `eqPhase` Cc || cc_phase `eqPhase` Ccpp || cc_phase `eqPhase` HCc || cc_phase `eqPhase` Cobjc
+   = do
+        let cc_opts = getOpts dflags opt_c
+            hcc = cc_phase `eqPhase` HCc
 
-               let cmdline_include_paths = includePaths dflags
+        let cmdline_include_paths = includePaths dflags
 
-       -- HC files have the dependent packages stamped into them
-       pkgs <- if hcc then getHCFilePackages input_fn else return []
+        -- HC files have the dependent packages stamped into them
+        pkgs <- if hcc then io $ getHCFilePackages input_fn else return []
 
-       -- add package include paths even if we're just compiling .c
-       -- files; this is the Value Add(TM) that using ghc instead of
-       -- gcc gives you :)
-        pkg_include_dirs <- getPackageIncludePath dflags pkgs
+        -- add package include paths even if we're just compiling .c
+        -- files; this is the Value Add(TM) that using ghc instead of
+        -- gcc gives you :)
+        pkg_include_dirs <- io $ getPackageIncludePath dflags pkgs
         let include_paths = foldr (\ x xs -> "-I" : x : xs) []
-                             (cmdline_include_paths ++ pkg_include_dirs)
+                              (cmdline_include_paths ++ pkg_include_dirs)
 
-       let (md_c_flags, md_regd_c_flags) = machdepCCOpts dflags
+        let gcc_extra_viac_flags = extraGccViaCFlags dflags
         let pic_c_flags = picCCOpts dflags
 
-        let verb = getVerbFlag dflags
+        let verbFlags = getVerbFlags dflags
 
-       pkg_extra_cc_opts <- getPackageExtraCcOpts dflags pkgs
+        -- cc-options are not passed when compiling .hc files.  Our
+        -- hc code doesn't not #include any header files anyway, so these
+        -- options aren't necessary.
+        pkg_extra_cc_opts <- io $
+          if cc_phase `eqPhase` HCc
+             then return []
+             else getPackageExtraCcOpts dflags pkgs
 
-       let split_objs = dopt Opt_SplitObjs dflags
-           split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
-                     | otherwise         = [ ]
-
-       let excessPrecision = dopt Opt_ExcessPrecision dflags
-
-       let cc_opt | optLevel dflags >= 2 = "-O2"
-                  | otherwise            = "-O"
+#ifdef darwin_TARGET_OS
+        pkg_framework_paths <- io $ getPackageFrameworkPath dflags pkgs
+        let cmdline_framework_paths = frameworkPaths dflags
+        let framework_paths = map ("-F"++)
+                        (cmdline_framework_paths ++ pkg_framework_paths)
+#endif
 
-       -- Decide next phase
-       
-        let mangle = dopt Opt_DoAsmMangling dflags
-            next_phase
-               | hcc && mangle     = Mangle
-               | otherwise         = As
-       output_fn <- get_output_fn dflags next_phase maybe_loc
+        let split_objs = dopt Opt_SplitObjs dflags
+            split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
+                      | otherwise         = [ ]
+
+        let cc_opt | optLevel dflags >= 2 = "-O2"
+                   | otherwise            = "-O"
+
+        -- Decide next phase
+
+        let next_phase = As
+        output_fn <- phaseOutputFilename next_phase
+
+        let
+          more_hcc_opts =
+                -- on x86 the floating point regs have greater precision
+                -- than a double, which leads to unpredictable results.
+                -- By default, we turn this off with -ffloat-store unless
+                -- the user specified -fexcess-precision.
+                (if platformArch (targetPlatform dflags) == ArchX86 &&
+                    not (dopt Opt_ExcessPrecision dflags)
+                        then [ "-ffloat-store" ]
+                        else []) ++
+
+                -- gcc's -fstrict-aliasing allows two accesses to memory
+                -- to be considered non-aliasing if they have different types.
+                -- This interacts badly with the C code we generate, which is
+                -- very weakly typed, being derived from C--.
+                ["-fno-strict-aliasing"]
+
+        let gcc_lang_opt | cc_phase `eqPhase` Ccpp  = "c++"
+                         | cc_phase `eqPhase` Cobjc = "objective-c"
+                         | otherwise                = "c"
+        io $ SysTools.runCc dflags (
+                -- force the C compiler to interpret this file as C when
+                -- compiling .hc files, by adding the -x c option.
+                -- Also useful for plain .c files, just in case GHC saw a
+                -- -x c option.
+                        [ SysTools.Option "-x", SysTools.Option gcc_lang_opt
+                        , SysTools.FileOption "" input_fn
+                        , SysTools.Option "-o"
+                        , SysTools.FileOption "" output_fn
+                        ]
+                       ++ map SysTools.Option (
+                          pic_c_flags
+
+                -- Stub files generated for foreign exports references the runIO_closure
+                -- and runNonIO_closure symbols, which are defined in the base package.
+                -- These symbols are imported into the stub.c file via RtsAPI.h, and the
+                -- way we do the import depends on whether we're currently compiling
+                -- the base package or not.
+                       ++ (if platformOS (targetPlatform dflags) == OSMinGW32 &&
+                              thisPackage dflags == basePackageId
+                                then [ "-DCOMPILING_BASE_PACKAGE" ]
+                                else [])
 
-       let
-         more_hcc_opts =
-#if i386_TARGET_ARCH
-               -- on x86 the floating point regs have greater precision
-               -- than a double, which leads to unpredictable results.
-               -- By default, we turn this off with -ffloat-store unless
-               -- the user specified -fexcess-precision.
-               (if excessPrecision then [] else [ "-ffloat-store" ]) ++
-#endif
-               -- gcc's -fstrict-aliasing allows two accesses to memory
-               -- to be considered non-aliasing if they have different types.
-               -- This interacts badly with the C code we generate, which is
-               -- very weakly typed, being derived from C--.
-               ["-fno-strict-aliasing"]
-
-
-
-       SysTools.runCc dflags (
-               -- force the C compiler to interpret this file as C when
-               -- compiling .hc files, by adding the -x c option.
-               -- Also useful for plain .c files, just in case GHC saw a 
-               -- -x c option.
-                       [ SysTools.Option "-x", if cc_phase `eqPhase` Ccpp
-                                                then SysTools.Option "c++" else SysTools.Option "c"] ++
-                       [ SysTools.FileOption "" input_fn
-                       , SysTools.Option "-o"
-                       , SysTools.FileOption "" output_fn
-                       ]
-                      ++ map SysTools.Option (
-                         md_c_flags
-                       ++ pic_c_flags
-#ifdef sparc_TARGET_ARCH
         -- We only support SparcV9 and better because V8 lacks an atomic CAS
         -- instruction. Note that the user can still override this
-       -- (e.g., -mcpu=ultrasparc) as GCC picks the "best" -mcpu flag
-       -- regardless of the ordering.
+        -- (e.g., -mcpu=ultrasparc) as GCC picks the "best" -mcpu flag
+        -- regardless of the ordering.
         --
         -- This is a temporary hack.
-                       ++ ["-mcpu=v9"]
-#endif
-                      ++ (if hcc && mangle
-                            then md_regd_c_flags
-                            else [])
-                      ++ (if hcc 
-                            then more_hcc_opts
-                            else [])
-                      ++ [ verb, "-S", "-Wimplicit", cc_opt ]
-                      ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
-                      ++ cc_opts
-                      ++ split_opt
-                      ++ include_paths
-                      ++ pkg_extra_cc_opts
-#ifdef HAVE_GCC_HAS_WRAPV
-                  -- We need consistent integer overflow (trac #952)
-               ++ ["-fwrapv"]
+                       ++ (if platformArch (targetPlatform dflags) == ArchSPARC
+                           then ["-mcpu=v9"]
+                           else [])
+
+                       ++ (if hcc
+                             then gcc_extra_viac_flags ++ more_hcc_opts
+                             else [])
+                       ++ verbFlags
+                       ++ [ "-S", "-Wimplicit", cc_opt ]
+                       ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
+#ifdef darwin_TARGET_OS
+                       ++ framework_paths
 #endif
-                      ))
+                       ++ cc_opts
+                       ++ split_opt
+                       ++ include_paths
+                       ++ pkg_extra_cc_opts
+                       ))
 
-       return (next_phase, dflags, maybe_loc, output_fn)
+        return (next_phase, output_fn)
 
-       -- ToDo: postprocess the output from gcc
+        -- ToDo: postprocess the output from gcc
 
 -----------------------------------------------------------------------------
--- Mangle phase
+-- Splitting phase
 
-runPhase Mangle stop dflags _basename _suff input_fn get_output_fn maybe_loc
-   = do let mangler_opts = getOpts dflags opt_m
+runPhase SplitMangle input_fn dflags
+  = do  -- tmp_pfx is the prefix used for the split .s files
 
-#if i386_TARGET_ARCH
-        machdep_opts <- return [ show (stolen_x86_regs dflags) ]
-#else
-       machdep_opts <- return []
-#endif
+        split_s_prefix <- io $ SysTools.newTempName dflags "split"
+        let n_files_fn = split_s_prefix
+
+        io $ SysTools.runSplit dflags
+                          [ SysTools.FileOption "" input_fn
+                          , SysTools.FileOption "" split_s_prefix
+                          , SysTools.FileOption "" n_files_fn
+                          ]
+
+        -- Save the number of split files for future references
+        s <- io $ readFile n_files_fn
+        let n_files = read s :: Int
+            dflags' = dflags { splitInfo = Just (split_s_prefix, n_files) }
 
-       let split = dopt Opt_SplitObjs dflags
-            next_phase
-               | split = SplitMangle
-               | otherwise = As
-       output_fn <- get_output_fn dflags next_phase maybe_loc
+        setDynFlags dflags'
 
-       SysTools.runMangle dflags (map SysTools.Option mangler_opts
-                         ++ [ SysTools.FileOption "" input_fn
-                            , SysTools.FileOption "" output_fn
-                            ]
-                         ++ map SysTools.Option machdep_opts)
+        -- Remember to delete all these files
+        io $ addFilesToClean dflags' [ split_s_prefix ++ "__" ++ show n ++ ".s"
+                                     | n <- [1..n_files]]
 
-       return (next_phase, dflags, maybe_loc, output_fn)
+        return (SplitAs, "**splitmangle**")
+          -- we don't use the filename
 
 -----------------------------------------------------------------------------
--- Splitting phase
+-- As phase
 
-runPhase SplitMangle stop dflags _basename _suff input_fn get_output_fn maybe_loc
-  = do  -- tmp_pfx is the prefix used for the split .s files
-       -- We also use it as the file to contain the no. of split .s files (sigh)
-       split_s_prefix <- SysTools.newTempName dflags "split"
-       let n_files_fn = split_s_prefix
+runPhase As input_fn dflags
+  = do
+        let as_opts =  getOpts dflags opt_a
+        let cmdline_include_paths = includePaths dflags
 
-       SysTools.runSplit dflags
-                         [ SysTools.FileOption "" input_fn
-                         , SysTools.FileOption "" split_s_prefix
-                         , SysTools.FileOption "" n_files_fn
-                         ]
+        next_phase <- maybeMergeStub
+        output_fn <- phaseOutputFilename next_phase
 
-       -- Save the number of split files for future references
-       s <- readFile n_files_fn
-       let n_files = read s :: Int
-       writeIORef v_Split_info (split_s_prefix, n_files)
+        -- we create directories for the object file, because it
+        -- might be a hierarchical module.
+        io $ createDirectoryHierarchy (takeDirectory output_fn)
 
-       -- Remember to delete all these files
-       addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s"
-                       | n <- [1..n_files]]
+        io $ SysTools.runAs dflags
+                       (map SysTools.Option as_opts
+                       ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
 
-       return (SplitAs, dflags, maybe_loc, "**splitmangle**")
-         -- we don't use the filename
+        -- We only support SparcV9 and better because V8 lacks an atomic CAS
+        -- instruction so we have to make sure that the assembler accepts the
+        -- instruction set. Note that the user can still override this
+        -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
+        -- regardless of the ordering.
+        --
+        -- This is a temporary hack.
+                       ++ (if platformArch (targetPlatform dflags) == ArchSPARC
+                           then [SysTools.Option "-mcpu=v9"]
+                           else [])
 
------------------------------------------------------------------------------
--- As phase
+                       ++ [ SysTools.Option "-c"
+                          , SysTools.FileOption "" input_fn
+                          , SysTools.Option "-o"
+                          , SysTools.FileOption "" output_fn
+                          ])
 
-runPhase As stop dflags _basename _suff input_fn get_output_fn maybe_loc
-  = do let as_opts =  getOpts dflags opt_a
-        let cmdline_include_paths = includePaths dflags
+        return (next_phase, output_fn)
 
-       output_fn <- get_output_fn dflags StopLn maybe_loc
 
-       -- we create directories for the object file, because it
-       -- might be a hierarchical module.
-       createDirectoryHierarchy (directoryOf output_fn)
+runPhase SplitAs _input_fn dflags
+  = do
+        -- we'll handle the stub_o file in this phase, so don't MergeStub,
+        -- just jump straight to StopLn afterwards.
+        let next_phase = StopLn
+        output_fn <- phaseOutputFilename next_phase
+
+        let base_o = dropExtension output_fn
+            osuf = objectSuf dflags
+            split_odir  = base_o ++ "_" ++ osuf ++ "_split"
+
+        io $ createDirectoryHierarchy split_odir
+
+        -- remove M_split/ *.o, because we're going to archive M_split/ *.o
+        -- later and we don't want to pick up any old objects.
+        fs <- io $ getDirectoryContents split_odir
+        io $ mapM_ removeFile $
+                map (split_odir </>) $ filter (osuf `isSuffixOf`) fs
+
+        let as_opts = getOpts dflags opt_a
+
+        let (split_s_prefix, n) = case splitInfo dflags of
+                                  Nothing -> panic "No split info"
+                                  Just x -> x
+
+        let split_s   n = split_s_prefix ++ "__" ++ show n <.> "s"
+
+            split_obj :: Int -> FilePath
+            split_obj n = split_odir </>
+                          takeFileName base_o ++ "__" ++ show n <.> osuf
+
+        let assemble_file n
+              = SysTools.runAs dflags
+                         (map SysTools.Option as_opts ++
 
-       SysTools.runAs dflags   
-                      (map SysTools.Option as_opts
-                      ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
-#ifdef sparc_TARGET_ARCH
         -- We only support SparcV9 and better because V8 lacks an atomic CAS
-       -- instruction so we have to make sure that the assembler accepts the
+        -- instruction so we have to make sure that the assembler accepts the
         -- instruction set. Note that the user can still override this
-       -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
-       -- regardless of the ordering.
-       --
-       -- This is a temporary hack.
-                      ++ [ SysTools.Option "-mcpu=v9" ]
-#endif
-                      ++ [ SysTools.Option "-c"
-                         , SysTools.FileOption "" input_fn
-                         , SysTools.Option "-o"
-                         , SysTools.FileOption "" output_fn
-                         ])
-
-       return (StopLn, dflags, maybe_loc, output_fn)
-
-
-runPhase SplitAs stop dflags basename _suff _input_fn get_output_fn maybe_loc
-  = do  
-       output_fn <- get_output_fn dflags StopLn maybe_loc
-
-       let (base_o, _) = splitFilename output_fn
-           split_odir  = base_o ++ "_split"
-           osuf = objectSuf dflags
-
-       createDirectoryHierarchy split_odir
-
-       -- remove M_split/ *.o, because we're going to archive M_split/ *.o
-       -- later and we don't want to pick up any old objects.
-       fs <- getDirectoryContents split_odir 
-       mapM_ removeFile $ map (split_odir `joinFileName`)
-                        $ filter (osuf `isSuffixOf`) fs
-
-       let as_opts = getOpts dflags opt_a
-
-       (split_s_prefix, n) <- readIORef v_Split_info
-
-       let split_s   n = split_s_prefix ++ "__" ++ show n `joinFileExt` "s"
-           split_obj n = split_odir `joinFileName`
-                               filenameOf base_o ++ "__" ++ show n
-                                       `joinFileExt` osuf
-
-       let assemble_file n
-             = SysTools.runAs dflags
-                        (map SysTools.Option as_opts ++
-                        [ SysTools.Option "-c"
-                        , SysTools.Option "-o"
-                        , SysTools.FileOption "" (split_obj n)
-                        , SysTools.FileOption "" (split_s n)
-                        ])
-       
-       mapM_ assemble_file [1..n]
-
-       -- and join the split objects into a single object file:
-       let ld_r args = SysTools.runLink dflags ([ 
-                               SysTools.Option "-nostdlib",
-                               SysTools.Option "-nodefaultlibs",
-                               SysTools.Option "-Wl,-r", 
-                               SysTools.Option ld_x_flag, 
-                               SysTools.Option "-o", 
-                               SysTools.FileOption "" output_fn ] ++ args)
-            ld_x_flag | null cLD_X = ""
-                     | otherwise  = "-Wl,-x"     
-
-       if cLdIsGNULd == "YES"
-           then do 
-                 let script = split_odir `joinFileName` "ld.script"
-                 writeFile script $
-                     "INPUT(" ++ unwords (map split_obj [1..n]) ++ ")"
-                 ld_r [SysTools.FileOption "" script]
-           else do
-                 ld_r (map (SysTools.FileOption "" . split_obj) [1..n])
-
-       return (StopLn, dflags, maybe_loc, output_fn)
+        -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
+        -- regardless of the ordering.
+        --
+        -- This is a temporary hack.
+                          (if platformArch (targetPlatform dflags) == ArchSPARC
+                           then [SysTools.Option "-mcpu=v9"]
+                           else []) ++
+
+                          [ SysTools.Option "-c"
+                          , SysTools.Option "-o"
+                          , SysTools.FileOption "" (split_obj n)
+                          , SysTools.FileOption "" (split_s n)
+                          ])
+
+        io $ mapM_ assemble_file [1..n]
+
+        -- Note [pipeline-split-init]
+        -- If we have a stub file, it may contain constructor
+        -- functions for initialisation of this module.  We can't
+        -- simply leave the stub as a separate object file, because it
+        -- will never be linked in: nothing refers to it.  We need to
+        -- ensure that if we ever refer to the data in this module
+        -- that needs initialisation, then we also pull in the
+        -- initialisation routine.
+        --
+        -- To that end, we make a DANGEROUS ASSUMPTION here: the data
+        -- that needs to be initialised is all in the FIRST split
+        -- object.  See Note [codegen-split-init].
+
+        PipeState{maybe_stub_o} <- getPipeState
+        case maybe_stub_o of
+            Nothing     -> return ()
+            Just stub_o -> io $ do
+                     tmp_split_1 <- newTempName dflags osuf
+                     let split_1 = split_obj 1
+                     copyFile split_1 tmp_split_1
+                     removeFile split_1
+                     joinObjectFiles dflags [tmp_split_1, stub_o] split_1
 
+        -- join them into a single .o file
+        io $ joinObjectFiles dflags (map split_obj [1..n]) output_fn
+
+        return (next_phase, output_fn)
+
+-----------------------------------------------------------------------------
+-- LlvmOpt phase
+
+runPhase LlvmOpt input_fn dflags
+  = do
+    let lo_opts = getOpts dflags opt_lo
+    let opt_lvl = max 0 (min 2 $ optLevel dflags)
+    -- don't specify anything if user has specified commands. We do this for
+    -- opt but not llc since opt is very specifically for optimisation passes
+    -- only, so if the user is passing us extra options we assume they know
+    -- what they are doing and don't get in the way.
+    let optFlag = if null lo_opts
+                     then [SysTools.Option (llvmOpts !! opt_lvl)]
+                     else []
+
+    output_fn <- phaseOutputFilename LlvmLlc
+
+    io $ SysTools.runLlvmOpt dflags
+               ([ SysTools.FileOption "" input_fn,
+                    SysTools.Option "-o",
+                    SysTools.FileOption "" output_fn]
+                ++ optFlag
+                ++ map SysTools.Option lo_opts)
+
+    return (LlvmLlc, output_fn)
+  where 
+        -- we always (unless -optlo specified) run Opt since we rely on it to
+        -- fix up some pretty big deficiencies in the code we generate
+        llvmOpts = ["-mem2reg", "-O1", "-O2"]
+
+-----------------------------------------------------------------------------
+-- LlvmLlc phase
+
+runPhase LlvmLlc input_fn dflags
+  = do
+    let lc_opts = getOpts dflags opt_lc
+        opt_lvl = max 0 (min 2 $ optLevel dflags)
+        rmodel | opt_PIC        = "pic"
+               | not opt_Static = "dynamic-no-pic"
+               | otherwise      = "static"
+
+    output_fn <- phaseOutputFilename LlvmMangle
+
+    io $ SysTools.runLlvmLlc dflags
+                ([ SysTools.Option (llvmOpts !! opt_lvl),
+                    SysTools.Option $ "-relocation-model=" ++ rmodel,
+                    SysTools.FileOption "" input_fn,
+                    SysTools.Option "-o", SysTools.FileOption "" output_fn]
+                ++ map SysTools.Option lc_opts)
+
+    return (LlvmMangle, output_fn)
+  where
+        -- Bug in LLVM at O3 on OSX.
+        llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin
+                   then ["-O1", "-O2", "-O2"]
+                   else ["-O1", "-O2", "-O3"]
+
+-----------------------------------------------------------------------------
+-- LlvmMangle phase
+
+runPhase LlvmMangle input_fn _dflags
+  = do
+      output_fn <- phaseOutputFilename As
+      io $ llvmFixupAsm input_fn output_fn
+      return (As, output_fn)
+
+-----------------------------------------------------------------------------
+-- merge in stub objects
+
+runPhase MergeStub input_fn dflags
+ = do
+     PipeState{maybe_stub_o} <- getPipeState
+     output_fn <- phaseOutputFilename StopLn
+     case maybe_stub_o of
+       Nothing ->
+         panic "runPhase(MergeStub): no stub"
+       Just stub_o -> do
+         io $ joinObjectFiles dflags [input_fn, stub_o] output_fn
+         return (StopLn, output_fn)
+
+-- warning suppression
+runPhase other _input_fn _dflags =
+   panic ("runPhase: don't know how to run phase " ++ show other)
+
+maybeMergeStub :: CompPipeline Phase
+maybeMergeStub
+ = do
+     PipeState{maybe_stub_o} <- getPipeState
+     if isJust maybe_stub_o then return MergeStub else return StopLn
 
 -----------------------------------------------------------------------------
 -- MoveBinary sort-of-phase
 -- After having produced a binary, move it somewhere else and generate a
--- wrapper script calling the binary. Currently, we need this only in 
+-- wrapper script calling the binary. Currently, we need this only in
 -- a parallel way (i.e. in GUM), because PVM expects the binary in a
 -- central directory.
--- This is called from staticLink below, after linking. I haven't made it
+-- This is called from linkBinary below, after linking. I haven't made it
 -- a separate phase to minimise interfering with other modules, and
 -- we don't need the generality of a phase (MoveBinary is always
 -- done after linking and makes only sense in a parallel setup)   -- HWL
 
+runPhase_MoveBinary :: DynFlags -> FilePath -> IO Bool
 runPhase_MoveBinary dflags input_fn
-  = do 
+    | WayPar `elem` (wayNames dflags) && not opt_Static =
+        panic ("Don't know how to combine PVM wrapper and dynamic wrapper")
+    | WayPar `elem` (wayNames dflags) = do
         let sysMan = pgm_sysman dflags
         pvm_root <- getEnv "PVM_ROOT"
         pvm_arch <- getEnv "PVM_ARCH"
-        let 
+        let
            pvm_executable_base = "=" ++ input_fn
            pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
         -- nuke old binary; maybe use configur'ed names for cp and rm?
-        Panic.try (removeFile pvm_executable)
+        _ <- tryIO (removeFile pvm_executable)
         -- move the newly created binary into PVM land
         copy dflags "copying PVM executable" input_fn pvm_executable
         -- generate a wrapper script for running a parallel prg under PVM
         writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
-       return True
+        return True
+    | otherwise = return True
+
+mkExtraCObj :: DynFlags -> String -> IO FilePath
+mkExtraCObj dflags xs
+ = do cFile <- newTempName dflags "c"
+      oFile <- newTempName dflags "o"
+      writeFile cFile xs
+      let rtsDetails = getPackageDetails (pkgState dflags) rtsPackageId
+      SysTools.runCc dflags
+                     ([Option        "-c",
+                       FileOption "" cFile,
+                       Option        "-o",
+                       FileOption "" oFile] ++
+                      map (FileOption "-I") (includeDirs rtsDetails))
+      return oFile
+
+mkExtraObjToLinkIntoBinary :: DynFlags -> [PackageId] -> IO FilePath
+mkExtraObjToLinkIntoBinary dflags dep_packages = do
+   link_info <- getLinkInfo dflags dep_packages
+   mkExtraCObj dflags (showSDoc (vcat [rts_opts_enabled,
+                                       extra_rts_opts,
+                                       link_opts link_info]
+                                   <> char '\n')) -- final newline, to
+                                                  -- keep gcc happy
+
+  where
+    mk_rts_opts_enabled val
+         = vcat [text "#include \"Rts.h\"",
+                 text "#include \"RtsOpts.h\"",
+                 text "const RtsOptsEnabledEnum rtsOptsEnabled = " <>
+                       text val <> semi ]
+
+    rts_opts_enabled = case rtsOptsEnabled dflags of
+          RtsOptsNone     -> mk_rts_opts_enabled "RtsOptsNone"
+          RtsOptsSafeOnly -> empty -- The default
+          RtsOptsAll      -> mk_rts_opts_enabled "RtsOptsAll"
+
+    extra_rts_opts = case rtsOpts dflags of
+          Nothing   -> empty
+          Just opts -> text "char *ghc_rts_opts = " <> text (show opts) <> semi
+
+    link_opts info
+      | isDarwinTarget  = empty
+      | isWindowsTarget = empty
+      | otherwise = hcat [
+          text "__asm__(\"\\t.section ", text ghcLinkInfoSectionName,
+                                    text ",\\\"\\\",@note\\n",
+                    text "\\t.ascii \\\"", info', text "\\\"\\n\");" ]
+          where
+            -- we need to escape twice: once because we're inside a C string,
+            -- and again because we're inside an asm string.
+            info' = text $ (escape.escape) info
+
+            escape :: String -> String
+            escape = concatMap (charToC.fromIntegral.ord)
+
+-- The "link info" is a string representing the parameters of the
+-- link.  We save this information in the binary, and the next time we
+-- link, if nothing else has changed, we use the link info stored in
+-- the existing binary to decide whether to re-link or not.
+getLinkInfo :: DynFlags -> [PackageId] -> IO String
+getLinkInfo dflags dep_packages = do
+   package_link_opts <- getPackageLinkOpts dflags dep_packages
+#ifdef darwin_TARGET_OS
+   pkg_frameworks <- getPackageFrameworks dflags dep_packages
+#endif
+   extra_ld_inputs <- readIORef v_Ld_inputs
+   let
+      link_info = (package_link_opts,
+#ifdef darwin_TARGET_OS
+                   pkg_frameworks,
+#endif
+                   rtsOpts dflags,
+                   rtsOptsEnabled dflags,
+                   dopt Opt_NoHsMain dflags,
+                   extra_ld_inputs,
+                   getOpts dflags opt_l)
+   --
+   return (show link_info)
 
 -- generates a Perl skript starting a parallel prg under PVM
 mk_pvm_wrapper_script :: String -> String -> String -> String
 mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
  [
-  "eval 'exec perl -S $0 ${1+\"$@\"}'", 
+  "eval 'exec perl -S $0 ${1+\"$@\"}'",
   "  if $running_under_some_shell;",
   "# =!=!=!=!=!=!=!=!=!=!=!",
   "# This script is automatically generated: DO NOT EDIT!!!",
@@ -1106,18 +1507,18 @@ mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
   "",
   "args: while ($a = shift(@ARGV)) {",
   "    if ( $a eq '+RTS' ) {",
-  "    $in_RTS_args = 1;",
+  "        $in_RTS_args = 1;",
   "    } elsif ( $a eq '-RTS' ) {",
-  "    $in_RTS_args = 0;",
+  "        $in_RTS_args = 0;",
   "    }",
   "    if ( $a eq '-d' && $in_RTS_args ) {",
-  "    $debug = '-';",
+  "        $debug = '-';",
   "    } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
-  "    $nprocessors = $1;",
+  "        $nprocessors = $1;",
   "    } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
-  "    $nprocessors = $1;",
+  "        $nprocessors = $1;",
   "    } else {",
-  "    push(@nonPVM_args, $a);",
+  "        push(@nonPVM_args, $a);",
   "    }",
   "}",
   "",
@@ -1131,16 +1532,6 @@ mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
  ]
 
 -----------------------------------------------------------------------------
--- Complain about non-dynamic flags in OPTIONS pragmas
-
-checkProcessArgsResult flags filename
-  = do when (notNull flags) (throwDyn (ProgramError (
-         showSDoc (hang (text filename <> char ':')
-                     4 (text "unknown flags in  {-# OPTIONS #-} pragma:" <+>
-                         hsep (map text flags)))
-       )))
-
------------------------------------------------------------------------------
 -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
 
 getHCFilePackages :: FilePath -> IO [PackageId]
@@ -1149,9 +1540,9 @@ getHCFilePackages filename =
     l <- hGetLine h
     case l of
       '/':'*':' ':'G':'H':'C':'_':'P':'A':'C':'K':'A':'G':'E':'S':rest ->
-         return (map stringToPackageId (words rest))
+          return (map stringToPackageId (words rest))
       _other ->
-         return []
+          return []
 
 -----------------------------------------------------------------------------
 -- Static linking, of .o files
@@ -1159,16 +1550,16 @@ getHCFilePackages filename =
 -- The list of packages passed to link is the list of packages on
 -- which this program depends, as discovered by the compilation
 -- manager.  It is combined with the list of packages that the user
--- specifies on the command line with -package flags.  
+-- specifies on the command line with -package flags.
 --
 -- In one-shot linking mode, we can't discover the package
 -- dependencies (because we haven't actually done any compilation or
 -- read any interface files), so the user must explicitly specify all
 -- the packages.
 
-staticLink :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
-staticLink dflags o_files dep_packages = do
-    let verb = getVerbFlag dflags
+linkBinary :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
+linkBinary dflags o_files dep_packages = do
+    let verbFlags = getVerbFlags dflags
         output_fn = exeFileName dflags
 
     -- get the full list of packages to link with, by combining the
@@ -1176,11 +1567,26 @@ staticLink dflags o_files dep_packages = do
     -- dependencies, and eliminating duplicates.
 
     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
-    let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
+    let pkg_lib_path_opts = concat (map get_pkg_lib_path_opts pkg_lib_paths)
+#ifdef elf_OBJ_FORMAT
+        get_pkg_lib_path_opts l | (dynLibLoader dflags)==SystemDependent && not opt_Static = ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l]
+                                | otherwise = ["-L" ++ l]
+#else
+        get_pkg_lib_path_opts l = ["-L" ++ l]
+#endif
 
     let lib_paths = libraryPaths dflags
     let lib_path_opts = map ("-L"++) lib_paths
 
+    -- The C "main" function is not in the rts but in a separate static
+    -- library libHSrtsmain.a that sits next to the rts lib files. Assuming
+    -- we're using a Haskell main function then we need to link it in.
+    let no_hs_main = dopt Opt_NoHsMain dflags
+    let main_lib | no_hs_main = []
+                 | otherwise  = [ "-lHSrtsmain" ]
+
+    extraLinkObj <- mkExtraObjToLinkIntoBinary dflags dep_packages
+
     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
 
 #ifdef darwin_TARGET_OS
@@ -1192,16 +1598,15 @@ staticLink dflags o_files dep_packages = do
 
     pkg_frameworks <- getPackageFrameworks dflags dep_packages
     let pkg_framework_opts = concat [ ["-framework", fw] | fw <- pkg_frameworks ]
-    
+
     let frameworks = cmdlineFrameworks dflags
         framework_opts = concat [ ["-framework", fw] | fw <- reverse frameworks ]
-        -- reverse because they're added in reverse order from the cmd line
+         -- reverse because they're added in reverse order from the cmd line
 #endif
-
-       -- probably _stub.o files
+        -- probably _stub.o files
     extra_ld_inputs <- readIORef v_Ld_inputs
 
-       -- opts from -optl-<blah> (including -l<blah> options)
+        -- opts from -optl-<blah> (including -l<blah> options)
     let extra_ld_opts = getOpts dflags opt_l
 
     let ways = wayNames dflags
@@ -1210,129 +1615,298 @@ staticLink dflags o_files dep_packages = do
     -- the command line, because they contain symbols that are referred to
     -- by the RTS.  We can't therefore use the ordinary way opts for these.
     let
-       debug_opts | WayDebug `elem` ways = [ 
+        debug_opts | WayDebug `elem` ways = [
 #if defined(HAVE_LIBBFD)
-                       "-lbfd", "-liberty"
+                        "-lbfd", "-liberty"
 #endif
-                        ]
-                  | otherwise            = []
+                         ]
+                   | otherwise            = []
 
     let
-       thread_opts | WayThreaded `elem` ways = [ 
-#if !defined(mingw32_TARGET_OS) && !defined(freebsd_TARGET_OS)
-                       "-lpthread"
+        thread_opts | WayThreaded `elem` ways = [
+#if !defined(mingw32_TARGET_OS) && !defined(freebsd_TARGET_OS) && !defined(openbsd_TARGET_OS) && !defined(haiku_TARGET_OS)
+                        "-lpthread"
 #endif
 #if defined(osf3_TARGET_OS)
-                       , "-lexc"
+                        , "-lexc"
 #endif
-                       ]
-                   | otherwise               = []
-
-    let (md_c_flags, _) = machdepCCOpts dflags
-    SysTools.runLink dflags ( 
-                      [ SysTools.Option verb
-                      , SysTools.Option "-o"
-                      , SysTools.FileOption "" output_fn
-                      ]
-                     ++ map SysTools.Option (
-                        md_c_flags
-                     ++ o_files
-                     ++ extra_ld_inputs
-                     ++ lib_path_opts
-                     ++ extra_ld_opts
+                        ]
+                    | otherwise               = []
+
+    rc_objs <- maybeCreateManifest dflags output_fn
+
+    SysTools.runLink dflags (
+                       map SysTools.Option verbFlags
+                      ++ [ SysTools.Option "-o"
+                         , SysTools.FileOption "" output_fn
+                         ]
+                      ++ map SysTools.Option (
+                         []
+
+                      -- Permit the linker to auto link _symbol to _imp_symbol.
+                      -- This lets us link against DLLs without needing an "import library".
+                      ++ (if platformOS (targetPlatform dflags) == OSMinGW32
+                          then ["-Wl,--enable-auto-import"]
+                          else [])
+
+                      ++ o_files
+                      ++ extra_ld_inputs
+                      ++ lib_path_opts
+                      ++ extra_ld_opts
+                      ++ rc_objs
 #ifdef darwin_TARGET_OS
-                     ++ framework_path_opts
-                     ++ framework_opts
+                      ++ framework_path_opts
+                      ++ framework_opts
 #endif
-                     ++ pkg_lib_path_opts
-                     ++ pkg_link_opts
+                      ++ pkg_lib_path_opts
+                      ++ main_lib
+                      ++ [extraLinkObj]
+                      ++ pkg_link_opts
 #ifdef darwin_TARGET_OS
-                     ++ pkg_framework_path_opts
-                     ++ pkg_framework_opts
+                      ++ pkg_framework_path_opts
+                      ++ pkg_framework_opts
 #endif
-                     ++ debug_opts
-                     ++ thread_opts
-                   ))
+                      ++ debug_opts
+                      ++ thread_opts
+                    ))
 
     -- parallel only: move binary to another dir -- HWL
-    when (WayPar `elem` ways)
-        (do success <- runPhase_MoveBinary dflags output_fn
-             if success then return ()
-                        else throwDyn (InstallationError ("cannot move binary to PVM dir")))
+    success <- runPhase_MoveBinary dflags output_fn
+    if success then return ()
+               else ghcError (InstallationError ("cannot move binary"))
 
 
 exeFileName :: DynFlags -> FilePath
 exeFileName dflags
-  | Just s <- outputFile dflags = 
-#if defined(mingw32_HOST_OS)
-      if null (suffixOf s)
-        then s `joinFileExt` "exe"
-        else s
+  | Just s <- outputFile dflags =
+      if platformOS (targetPlatform dflags) == OSMinGW32
+      then if null (takeExtension s)
+           then s <.> "exe"
+           else s
+      else s
+  | otherwise =
+      if platformOS (targetPlatform dflags) == OSMinGW32
+      then "main.exe"
+      else "a.out"
+
+maybeCreateManifest
+   :: DynFlags
+   -> FilePath                          -- filename of executable
+   -> IO [FilePath]                     -- extra objects to embed, maybe
+#ifndef mingw32_TARGET_OS
+maybeCreateManifest _ _ = do
+  return []
 #else
-      s
-#endif
-  | otherwise = 
-#if defined(mingw32_HOST_OS)
-       "main.exe"
-#else
-       "a.out"
+maybeCreateManifest dflags exe_filename = do
+  if not (dopt Opt_GenManifest dflags) then return [] else do
+
+  let manifest_filename = exe_filename <.> "manifest"
+
+  writeFile manifest_filename $
+      "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\n"++
+      "  <assembly xmlns=\"urn:schemas-microsoft-com:asm.v1\" manifestVersion=\"1.0\">\n"++
+      "  <assemblyIdentity version=\"1.0.0.0\"\n"++
+      "     processorArchitecture=\"X86\"\n"++
+      "     name=\"" ++ dropExtension exe_filename ++ "\"\n"++
+      "     type=\"win32\"/>\n\n"++
+      "  <trustInfo xmlns=\"urn:schemas-microsoft-com:asm.v3\">\n"++
+      "    <security>\n"++
+      "      <requestedPrivileges>\n"++
+      "        <requestedExecutionLevel level=\"asInvoker\" uiAccess=\"false\"/>\n"++
+      "        </requestedPrivileges>\n"++
+      "       </security>\n"++
+      "  </trustInfo>\n"++
+      "</assembly>\n"
+
+  -- Windows will find the manifest file if it is named foo.exe.manifest.
+  -- However, for extra robustness, and so that we can move the binary around,
+  -- we can embed the manifest in the binary itself using windres:
+  if not (dopt Opt_EmbedManifest dflags) then return [] else do
+
+  rc_filename <- newTempName dflags "rc"
+  rc_obj_filename <- newTempName dflags (objectSuf dflags)
+
+  writeFile rc_filename $
+      "1 24 MOVEABLE PURE " ++ show manifest_filename ++ "\n"
+        -- magic numbers :-)
+        -- show is a bit hackish above, but we need to escape the
+        -- backslashes in the path.
+
+  let wr_opts = getOpts dflags opt_windres
+  runWindres dflags $ map SysTools.Option $
+        ["--input="++rc_filename,
+         "--output="++rc_obj_filename,
+         "--output-format=coff"]
+        ++ wr_opts
+        -- no FileOptions here: windres doesn't like seeing
+        -- backslashes, apparently
+
+  removeFile manifest_filename
+
+  return [rc_obj_filename]
 #endif
 
------------------------------------------------------------------------------
--- Making a DLL (only for Win32)
 
-doMkDLL :: DynFlags -> [String] -> [PackageId] -> IO ()
-doMkDLL dflags o_files dep_packages = do
-    let verb = getVerbFlag dflags
-    let static = opt_Static
-    let no_hs_main = dopt Opt_NoHsMain dflags
+linkDynLib :: DynFlags -> [String] -> [PackageId] -> IO ()
+linkDynLib dflags o_files dep_packages = do
+    let verbFlags = getVerbFlags dflags
     let o_file = outputFile dflags
-    let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
 
-    pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
-    let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
+    pkgs <- getPreloadPackagesAnd dflags dep_packages
+
+    let pkg_lib_paths = collectLibraryPaths pkgs
+    let pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
+#ifdef elf_OBJ_FORMAT
+        get_pkg_lib_path_opts l | (dynLibLoader dflags)==SystemDependent && not opt_Static = ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l]
+                                | otherwise = ["-L" ++ l]
+#else
+        get_pkg_lib_path_opts l = ["-L" ++ l]
+#endif
 
     let lib_paths = libraryPaths dflags
     let lib_path_opts = map ("-L"++) lib_paths
 
-    pkg_link_opts <- getPackageLinkOpts dflags dep_packages
+    -- We don't want to link our dynamic libs against the RTS package,
+    -- because the RTS lib comes in several flavours and we want to be
+    -- able to pick the flavour when a binary is linked.
+    -- On Windows we need to link the RTS import lib as Windows does
+    -- not allow undefined symbols.
+    -- The RTS library path is still added to the library search path
+    -- above in case the RTS is being explicitly linked in (see #3807).
+#if !defined(mingw32_HOST_OS)
+    let pkgs_no_rts = filter ((/= rtsPackageId) . packageConfigId) pkgs
+#else
+    let pkgs_no_rts = pkgs
+#endif
+    let pkg_link_opts = collectLinkOpts dflags pkgs_no_rts
 
-       -- probably _stub.o files
+        -- probably _stub.o files
     extra_ld_inputs <- readIORef v_Ld_inputs
 
-       -- opts from -optdll-<blah>
-    let extra_ld_opts = getOpts dflags opt_dll 
-
-    let pstate = pkgState dflags
-       rts_pkg  = getPackageDetails pstate rtsPackageId
-        base_pkg = getPackageDetails pstate basePackageId
-
-    let extra_os = if static || no_hs_main
-                   then []
-                   else [ head (libraryDirs rts_pkg) ++ "/Main.dll_o",
-                          head (libraryDirs base_pkg) ++ "/PrelMain.dll_o" ]
-
-    let (md_c_flags, _) = machdepCCOpts dflags
-    SysTools.runMkDLL dflags
-        ([ SysTools.Option verb
-         , SysTools.Option "-o"
-         , SysTools.FileOption "" output_fn
-         ]
-        ++ map SysTools.Option (
-           md_c_flags
-        ++ o_files
-        ++ extra_os
-        ++ [ "--target=i386-mingw32" ]
-        ++ extra_ld_inputs
-        ++ lib_path_opts
-        ++ extra_ld_opts
-        ++ pkg_lib_path_opts
-        ++ pkg_link_opts
-         ++ (if "--def" `elem` (concatMap words extra_ld_opts)
-              then [ "" ]
-               else [ "--export-all" ])
-       ))
+    let extra_ld_opts = getOpts dflags opt_l
+
+    extraLinkObj <- mkExtraObjToLinkIntoBinary dflags dep_packages
 
+#if defined(mingw32_HOST_OS)
+    -----------------------------------------------------------------------------
+    -- Making a DLL
+    -----------------------------------------------------------------------------
+    let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
+
+    SysTools.runLink dflags (
+            map SysTools.Option verbFlags
+         ++ [ SysTools.Option "-o"
+            , SysTools.FileOption "" output_fn
+            , SysTools.Option "-shared"
+            ] ++
+            [ SysTools.FileOption "-Wl,--out-implib=" (output_fn ++ ".a")
+            | dopt Opt_SharedImplib dflags
+            ]
+         ++ map (SysTools.FileOption "") o_files
+         ++ map SysTools.Option (
+
+         -- Permit the linker to auto link _symbol to _imp_symbol
+         -- This lets us link against DLLs without needing an "import library"
+            ["-Wl,--enable-auto-import"]
+
+         ++ extra_ld_inputs
+         ++ lib_path_opts
+         ++ extra_ld_opts
+         ++ pkg_lib_path_opts
+         ++ [extraLinkObj]
+         ++ pkg_link_opts
+        ))
+#elif defined(darwin_TARGET_OS)
+    -----------------------------------------------------------------------------
+    -- Making a darwin dylib
+    -----------------------------------------------------------------------------
+    -- About the options used for Darwin:
+    -- -dynamiclib
+    --   Apple's way of saying -shared
+    -- -undefined dynamic_lookup:
+    --   Without these options, we'd have to specify the correct dependencies
+    --   for each of the dylibs. Note that we could (and should) do without this
+    --   for all libraries except the RTS; all we need to do is to pass the
+    --   correct HSfoo_dyn.dylib files to the link command.
+    --   This feature requires Mac OS X 10.3 or later; there is a similar feature,
+    --   -flat_namespace -undefined suppress, which works on earlier versions,
+    --   but it has other disadvantages.
+    -- -single_module
+    --   Build the dynamic library as a single "module", i.e. no dynamic binding
+    --   nonsense when referring to symbols from within the library. The NCG
+    --   assumes that this option is specified (on i386, at least).
+    -- -install_name
+    --   Mac OS/X stores the path where a dynamic library is (to be) installed
+    --   in the library itself.  It's called the "install name" of the library.
+    --   Then any library or executable that links against it before it's
+    --   installed will search for it in its ultimate install location.  By
+    --   default we set the install name to the absolute path at build time, but
+    --   it can be overridden by the -dylib-install-name option passed to ghc.
+    --   Cabal does this.
+    -----------------------------------------------------------------------------
+
+    let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
+
+    instName <- case dylibInstallName dflags of
+        Just n -> return n
+        Nothing -> do
+            pwd <- getCurrentDirectory
+            return $ pwd `combine` output_fn
+    SysTools.runLink dflags (
+            map SysTools.Option verbFlags
+         ++ [ SysTools.Option "-dynamiclib"
+            , SysTools.Option "-o"
+            , SysTools.FileOption "" output_fn
+            ]
+         ++ map SysTools.Option (
+            o_files
+         ++ [ "-undefined", "dynamic_lookup", "-single_module",
+#if !defined(x86_64_TARGET_ARCH)
+              "-Wl,-read_only_relocs,suppress",
+#endif
+              "-install_name", instName ]
+         ++ extra_ld_inputs
+         ++ lib_path_opts
+         ++ extra_ld_opts
+         ++ pkg_lib_path_opts
+         ++ [extraLinkObj]
+         ++ pkg_link_opts
+        ))
+#else
+    -----------------------------------------------------------------------------
+    -- Making a DSO
+    -----------------------------------------------------------------------------
+
+    let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
+    let buildingRts = thisPackage dflags == rtsPackageId
+    let bsymbolicFlag = if buildingRts
+                        then -- -Bsymbolic breaks the way we implement
+                             -- hooks in the RTS
+                             []
+                        else -- we need symbolic linking to resolve
+                             -- non-PIC intra-package-relocations
+                             ["-Wl,-Bsymbolic"]
+
+    SysTools.runLink dflags (
+            map SysTools.Option verbFlags
+         ++ [ SysTools.Option "-o"
+            , SysTools.FileOption "" output_fn
+            ]
+         ++ map SysTools.Option (
+            o_files
+         ++ [ "-shared" ]
+         ++ bsymbolicFlag
+            -- Set the library soname. We use -h rather than -soname as
+            -- Solaris 10 doesn't support the latter:
+         ++ [ "-Wl,-h," ++ takeFileName output_fn ]
+         ++ extra_ld_inputs
+         ++ lib_path_opts
+         ++ extra_ld_opts
+         ++ pkg_lib_path_opts
+         ++ [extraLinkObj]
+         ++ pkg_link_opts
+        ))
+#endif
 -- -----------------------------------------------------------------------------
 -- Running CPP
 
@@ -1343,91 +1917,94 @@ doCpp dflags raw include_cc_opts input_fn output_fn = do
 
     pkg_include_dirs <- getPackageIncludePath dflags []
     let include_paths = foldr (\ x xs -> "-I" : x : xs) []
-                         (cmdline_include_paths ++ pkg_include_dirs)
+                          (cmdline_include_paths ++ pkg_include_dirs)
 
-    let verb = getVerbFlag dflags
+    let verbFlags = getVerbFlags dflags
 
     let cc_opts
-         | not include_cc_opts = []
-         | otherwise           = (optc ++ md_c_flags)
-               where 
-                     optc = getOpts dflags opt_c
-                     (md_c_flags, _) = machdepCCOpts dflags
+          | include_cc_opts = getOpts dflags opt_c
+          | otherwise       = []
 
     let cpp_prog args | raw       = SysTools.runCpp dflags args
-                     | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args)
-
-    let target_defs = 
-         [ "-D" ++ HOST_OS     ++ "_BUILD_OS=1",
-           "-D" ++ HOST_ARCH   ++ "_BUILD_ARCH=1",
-           "-D" ++ TARGET_OS   ++ "_HOST_OS=1",
-           "-D" ++ TARGET_ARCH ++ "_HOST_ARCH=1" ]
-       -- remember, in code we *compile*, the HOST is the same our TARGET,
-       -- and BUILD is the same as our HOST.
-
-    cpp_prog       ([SysTools.Option verb]
-                   ++ map SysTools.Option include_paths
-                   ++ map SysTools.Option hsSourceCppOpts
-                   ++ map SysTools.Option hscpp_opts
-                   ++ map SysTools.Option cc_opts
-                   ++ map SysTools.Option target_defs
-                   ++ [ SysTools.Option     "-x"
-                      , SysTools.Option     "c"
-                      , SysTools.Option     input_fn
-       -- We hackily use Option instead of FileOption here, so that the file
-       -- name is not back-slashed on Windows.  cpp is capable of
-       -- dealing with / in filenames, so it works fine.  Furthermore
-       -- if we put in backslashes, cpp outputs #line directives
-       -- with *double* backslashes.   And that in turn means that
-       -- our error messages get double backslashes in them.
-       -- In due course we should arrange that the lexer deals
-       -- with these \\ escapes properly.
-                      , SysTools.Option     "-o"
-                      , SysTools.FileOption "" output_fn
-                      ])
-
-cHaskell1Version = "5" -- i.e., Haskell 98
-
+                      | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args)
+
+    let target_defs =
+          [ "-D" ++ HOST_OS     ++ "_BUILD_OS=1",
+            "-D" ++ HOST_ARCH   ++ "_BUILD_ARCH=1",
+            "-D" ++ TARGET_OS   ++ "_HOST_OS=1",
+            "-D" ++ TARGET_ARCH ++ "_HOST_ARCH=1" ]
+        -- remember, in code we *compile*, the HOST is the same our TARGET,
+        -- and BUILD is the same as our HOST.
+
+    cpp_prog       (   map SysTools.Option verbFlags
+                    ++ map SysTools.Option include_paths
+                    ++ map SysTools.Option hsSourceCppOpts
+                    ++ map SysTools.Option target_defs
+                    ++ map SysTools.Option hscpp_opts
+                    ++ map SysTools.Option cc_opts
+                    ++ [ SysTools.Option     "-x"
+                       , SysTools.Option     "c"
+                       , SysTools.Option     input_fn
+        -- We hackily use Option instead of FileOption here, so that the file
+        -- name is not back-slashed on Windows.  cpp is capable of
+        -- dealing with / in filenames, so it works fine.  Furthermore
+        -- if we put in backslashes, cpp outputs #line directives
+        -- with *double* backslashes.   And that in turn means that
+        -- our error messages get double backslashes in them.
+        -- In due course we should arrange that the lexer deals
+        -- with these \\ escapes properly.
+                       , SysTools.Option     "-o"
+                       , SysTools.FileOption "" output_fn
+                       ])
+
+hsSourceCppOpts :: [String]
 -- Default CPP defines in Haskell source
 hsSourceCppOpts =
-       [ "-D__HASKELL1__="++cHaskell1Version
-       , "-D__GLASGOW_HASKELL__="++cProjectVersionInt                          
-       , "-D__HASKELL98__"
-       , "-D__CONCURRENT_HASKELL__"
-       ]
+        [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
 
+-- ---------------------------------------------------------------------------
+-- join object files into a single relocatable object file, using ld -r
+
+joinObjectFiles :: DynFlags -> [FilePath] -> FilePath -> IO ()
+joinObjectFiles dflags o_files output_fn = do
+  let ld_r args = SysTools.runLink dflags ([
+                            SysTools.Option "-nostdlib",
+                            SysTools.Option "-nodefaultlibs",
+                            SysTools.Option "-Wl,-r",
+                            SysTools.Option ld_build_id,
+                            SysTools.Option ld_x_flag,
+                            SysTools.Option "-o",
+                            SysTools.FileOption "" output_fn ]
+                         ++ args)
+
+      ld_x_flag | null cLD_X = ""
+                | otherwise  = "-Wl,-x"
+
+      -- suppress the generation of the .note.gnu.build-id section,
+      -- which we don't need and sometimes causes ld to emit a
+      -- warning:
+      ld_build_id | cLdHasBuildId == "YES"  = "-Wl,--build-id=none"
+                  | otherwise               = ""
+
+  if cLdIsGNULd == "YES"
+     then do
+          script <- newTempName dflags "ldscript"
+          writeFile script $ "INPUT(" ++ unwords o_files ++ ")"
+          ld_r [SysTools.FileOption "" script]
+     else do
+          ld_r (map (SysTools.FileOption "") o_files)
 
 -- -----------------------------------------------------------------------------
 -- Misc.
 
 hscNextPhase :: DynFlags -> HscSource -> HscTarget -> Phase
-hscNextPhase dflags HsBootFile hsc_lang  =  StopLn
-hscNextPhase dflags other hsc_lang = 
+hscNextPhase _ HsBootFile _        =  StopLn
+hscNextPhase dflags _ hsc_lang =
   case hsc_lang of
-       HscC -> HCc
-       HscAsm | dopt Opt_SplitObjs dflags -> SplitMangle
-              | otherwise -> As
-       HscNothing     -> StopLn
-       HscInterpreted -> StopLn
-       _other         -> StopLn
-
-
-hscMaybeAdjustTarget :: DynFlags -> Phase -> HscSource -> HscTarget -> HscTarget
-hscMaybeAdjustTarget dflags stop HsBootFile current_hsc_lang 
-  = HscNothing         -- No output (other than Foo.hi-boot) for hs-boot files
-hscMaybeAdjustTarget dflags stop other current_hsc_lang 
-  = hsc_lang 
-  where
-       keep_hc = dopt Opt_KeepHcFiles dflags
-       hsc_lang
-               -- don't change the lang if we're interpreting
-                | current_hsc_lang == HscInterpreted = current_hsc_lang
-
-               -- force -fvia-C if we are being asked for a .hc file
-                | HCc <- stop = HscC
-                | keep_hc     = HscC
-               -- otherwise, stick to the plan
-                | otherwise = current_hsc_lang
-
-GLOBAL_VAR(v_Split_info, ("",0), (String,Int))
-       -- The split prefix and number of files
+        HscC -> HCc
+        HscAsm | dopt Opt_SplitObjs dflags -> SplitMangle
+               | otherwise -> As
+        HscLlvm        -> LlvmOpt
+        HscNothing     -> StopLn
+        HscInterpreted -> StopLn
+