Fix some validation errors
[ghc-hetmet.git] / compiler / main / DriverPipeline.hs
index e1a2f46..afbd03e 100644 (file)
@@ -51,11 +51,10 @@ import SrcLoc
 import FastString
 import LlvmCodeGen      ( llvmFixupAsm )
 import MonadUtils
+import Platform
 
--- import Data.Either
 import Exception
 import Data.IORef       ( readIORef )
--- import GHC.Exts              ( Int(..) )
 import System.Directory
 import System.FilePath
 import System.IO
@@ -63,6 +62,7 @@ import Control.Monad
 import Data.List        ( isSuffixOf )
 import Data.Maybe
 import System.Environment
+import Data.Char
 
 -- ---------------------------------------------------------------------------
 -- Pre-process
@@ -268,11 +268,11 @@ link :: GhcLink                 -- interactive or batch
 -- exports main, i.e., we have good reason to believe that linking
 -- will succeed.
 
-#ifdef GHCI
 link LinkInMemory _ _ _
-    = do -- Not Linking...(demand linker will do the job)
-         return Succeeded
-#endif
+    = if cGhcWithInterpreter == "YES"
+      then -- Not Linking...(demand linker will do the job)
+           return Succeeded
+      else panicBadLink LinkInMemory
 
 link NoLink _ _ _
    = return Succeeded
@@ -283,11 +283,6 @@ link LinkBinary dflags batch_attempt_linking hpt
 link LinkDynLib dflags batch_attempt_linking hpt
    = link' dflags batch_attempt_linking hpt
 
-#ifndef GHCI
--- warning suppression
-link other _ _ _ = panicBadLink other
-#endif
-
 panicBadLink :: GhcLink -> a
 panicBadLink other = panic ("link: GHC not built to link this way: " ++
                             show other)
@@ -383,7 +378,30 @@ linkingNeeded dflags linkables pkg_deps = do
         let (lib_errs,lib_times) = splitEithers e_lib_times
         if not (null lib_errs) || any (t <) lib_times
            then return True
-           else return False
+           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
@@ -755,9 +773,9 @@ runPhase (Cpp sf) input_fn dflags0
             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
-            io $ checkProcessArgsResult unhandled_flags
 
             setDynFlags dflags2
 
@@ -790,8 +808,8 @@ runPhase (HsPp sf) input_fn dflags
             (dflags1, unhandled_flags, warns)
                 <- io $ parseDynamicNoPackageFlags dflags src_opts
             setDynFlags dflags1
-            io $ handleFlagWarnings dflags1 warns
             io $ checkProcessArgsResult unhandled_flags
+            io $ handleFlagWarnings dflags1 warns
 
             return (Hsc sf, output_fn)
 
@@ -956,7 +974,7 @@ runPhase CmmCpp input_fn dflags
 
 runPhase Cmm input_fn dflags
   = do
-        PipeEnv{stop_phase,src_basename} <- getPipeEnv
+        PipeEnv{src_basename} <- getPipeEnv
         let hsc_lang = hscTarget dflags
 
         let next_phase = hscNextPhase dflags HsSrcFile hsc_lang
@@ -986,7 +1004,7 @@ runPhase Cmm input_fn dflags
 -- way too many hacks, and I can't say I've ever used it anyway.
 
 runPhase cc_phase input_fn dflags
-   | cc_phase `eqPhase` Cc || cc_phase `eqPhase` Ccpp || cc_phase `eqPhase` HCc
+   | 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
@@ -1003,11 +1021,10 @@ runPhase cc_phase input_fn dflags
         let include_paths = foldr (\ x xs -> "-I" : x : xs) []
                               (cmdline_include_paths ++ pkg_include_dirs)
 
-        let md_c_flags = machdepCCOpts dflags
-        gcc_extra_viac_flags <- io $ getExtraViaCOpts dflags
+        let gcc_extra_viac_flags = extraGccViaCFlags dflags
         let pic_c_flags = picCCOpts dflags
 
-        let verb = getVerbFlag dflags
+        let verbFlags = getVerbFlags dflags
 
         -- cc-options are not passed when compiling .hc files.  Our
         -- hc code doesn't not #include any header files anyway, so these
@@ -1038,15 +1055,14 @@ runPhase cc_phase input_fn dflags
 
         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 dopt Opt_ExcessPrecision dflags
-                        then []
-                        else [ "-ffloat-store" ]) ++
-#endif
+                (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.
@@ -1054,46 +1070,47 @@ runPhase cc_phase input_fn dflags
                 -- 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", if cc_phase `eqPhase` Ccpp
-                                                then SysTools.Option "c++"
-                                                else SysTools.Option "c"] ++
-                        [ SysTools.FileOption "" input_fn
+                        [ SysTools.Option "-x", SysTools.Option gcc_lang_opt
+                        , SysTools.FileOption "" input_fn
                         , SysTools.Option "-o"
                         , SysTools.FileOption "" output_fn
                         ]
                        ++ map SysTools.Option (
-                          md_c_flags
-                       ++ pic_c_flags
+                          pic_c_flags
 
-#if    defined(mingw32_TARGET_OS)
                 -- 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 thisPackage dflags == basePackageId
+                       ++ (if platformOS (targetPlatform dflags) == OSMinGW32 &&
+                              thisPackage dflags == basePackageId
                                 then [ "-DCOMPILING_BASE_PACKAGE" ]
                                 else [])
-#endif
 
-#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.
         --
         -- This is a temporary hack.
-                       ++ ["-mcpu=v9"]
-#endif
+                       ++ (if platformArch (targetPlatform dflags) == ArchSPARC
+                           then ["-mcpu=v9"]
+                           else [])
+
                        ++ (if hcc
                              then gcc_extra_viac_flags ++ more_hcc_opts
                              else [])
-                       ++ [ verb, "-S", "-Wimplicit", cc_opt ]
+                       ++ verbFlags
+                       ++ [ "-S", "-Wimplicit", cc_opt ]
                        ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
 #ifdef darwin_TARGET_OS
                        ++ framework_paths
@@ -1152,11 +1169,10 @@ runPhase As input_fn dflags
         -- might be a hierarchical module.
         io $ createDirectoryHierarchy (takeDirectory output_fn)
 
-        let md_c_flags = machdepCCOpts dflags
         io $ 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 set. Note that the user can still override this
@@ -1164,21 +1180,24 @@ runPhase As input_fn dflags
         -- regardless of the ordering.
         --
         -- This is a temporary hack.
-                       ++ [ SysTools.Option "-mcpu=v9" ]
-#endif
+                       ++ (if platformArch (targetPlatform dflags) == ArchSPARC
+                           then [SysTools.Option "-mcpu=v9"]
+                           else [])
+
                        ++ [ SysTools.Option "-c"
                           , SysTools.FileOption "" input_fn
                           , SysTools.Option "-o"
                           , SysTools.FileOption "" output_fn
-                          ]
-                       ++ map SysTools.Option md_c_flags)
+                          ])
 
         return (next_phase, output_fn)
 
 
 runPhase SplitAs _input_fn dflags
   = do
-        next_phase <- maybeMergeStub
+        -- 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
@@ -1200,14 +1219,15 @@ runPhase SplitAs _input_fn dflags
                                   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 md_c_flags = machdepCCOpts dflags
         let assemble_file n
               = SysTools.runAs dflags
                          (map SysTools.Option as_opts ++
-#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 set. Note that the user can still override this
@@ -1215,17 +1235,41 @@ runPhase SplitAs _input_fn dflags
         -- regardless of the ordering.
         --
         -- This is a temporary hack.
-                          [ SysTools.Option "-mcpu=v9" ] ++
-#endif
+                          (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)
-                          ]
-                       ++ map SysTools.Option md_c_flags)
+                          ])
 
         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
 
@@ -1261,24 +1305,18 @@ runPhase LlvmOpt input_fn dflags
         -- 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
-    let opt_lvl = max 0 (min 2 $ optLevel dflags)
-#if darwin_TARGET_OS
-    let nphase = LlvmMangle
-#else
-    let nphase = As
-#endif
-    let rmodel | opt_PIC        = "pic"
+        opt_lvl = max 0 (min 2 $ optLevel dflags)
+        rmodel | opt_PIC        = "pic"
                | not opt_Static = "dynamic-no-pic"
                | otherwise      = "static"
 
-    output_fn <- phaseOutputFilename nphase
+    output_fn <- phaseOutputFilename LlvmMangle
 
     io $ SysTools.runLlvmLlc dflags
                 ([ SysTools.Option (llvmOpts !! opt_lvl),
@@ -1287,14 +1325,12 @@ runPhase LlvmLlc input_fn dflags
                     SysTools.Option "-o", SysTools.FileOption "" output_fn]
                 ++ map SysTools.Option lc_opts)
 
-    return (nphase, output_fn)
+    return (LlvmMangle, output_fn)
   where
-#if darwin_TARGET_OS
-        llvmOpts = ["-O1", "-O2", "-O2"]
-#else
-        llvmOpts = ["-O1", "-O2", "-O3"]
-#endif
-
+        -- Bug in LLVM at O3 on OSX.
+        llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin
+                   then ["-O1", "-O2", "-O2"]
+                   else ["-O1", "-O2", "-O3"]
 
 -----------------------------------------------------------------------------
 -- LlvmMangle phase
@@ -1360,35 +1396,83 @@ runPhase_MoveBinary dflags input_fn
         return True
     | otherwise = return True
 
-mkExtraCObj :: DynFlags -> [String] -> IO FilePath
+mkExtraCObj :: DynFlags -> String -> IO FilePath
 mkExtraCObj dflags xs
  = do cFile <- newTempName dflags "c"
       oFile <- newTempName dflags "o"
-      writeFile cFile $ unlines xs
+      writeFile cFile xs
       let rtsDetails = getPackageDetails (pkgState dflags) rtsPackageId
-          md_c_flags = machdepCCOpts dflags
       SysTools.runCc dflags
                      ([Option        "-c",
                        FileOption "" cFile,
                        Option        "-o",
                        FileOption "" oFile] ++
-                      map (FileOption "-I") (includeDirs rtsDetails) ++
-                      map Option md_c_flags)
+                      map (FileOption "-I") (includeDirs rtsDetails))
       return oFile
 
-mkRtsOptionsLevelObj :: DynFlags -> IO [FilePath]
-mkRtsOptionsLevelObj dflags
- = do let mkRtsEnabledObj val
-              = do fn <- mkExtraCObj dflags
-                             ["#include \"Rts.h\"",
-                              "#include \"RtsOpts.h\"",
-                              "const rtsOptsEnabledEnum rtsOptsEnabled = "
-                                  ++ val ++ ";"]
-                   return [fn]
-      case rtsOptsEnabled dflags of
-          RtsOptsNone     -> mkRtsEnabledObj "rtsOptsNone"
-          RtsOptsSafeOnly -> return [] -- The default
-          RtsOptsAll      -> mkRtsEnabledObj "rtsOptsAll"
+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
@@ -1475,7 +1559,7 @@ getHCFilePackages filename =
 
 linkBinary :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
 linkBinary dflags o_files dep_packages = do
-    let verb = getVerbFlag dflags
+    let verbFlags = getVerbFlags dflags
         output_fn = exeFileName dflags
 
     -- get the full list of packages to link with, by combining the
@@ -1500,15 +1584,8 @@ linkBinary dflags o_files dep_packages = do
     let no_hs_main = dopt Opt_NoHsMain dflags
     let main_lib | no_hs_main = []
                  | otherwise  = [ "-lHSrtsmain" ]
-    rtsEnabledObj <- mkRtsOptionsLevelObj dflags
-    rtsOptsObj <- case rtsOpts dflags of
-                  Just opts ->
-                      do fn <- mkExtraCObj dflags
-                                 -- We assume that the Haskell "show" does
-                                 -- the right thing here
-                                 ["char *ghc_rts_opts = " ++ show opts ++ ";"]
-                         return [fn]
-                  Nothing -> return []
+
+    extraLinkObj <- mkExtraObjToLinkIntoBinary dflags dep_packages
 
     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
 
@@ -1558,20 +1635,20 @@ linkBinary dflags o_files dep_packages = do
 
     rc_objs <- maybeCreateManifest dflags output_fn
 
-    let md_c_flags = machdepCCOpts dflags
     SysTools.runLink dflags (
-                       [ SysTools.Option verb
-                       , SysTools.Option "-o"
-                       , SysTools.FileOption "" output_fn
-                       ]
+                       map SysTools.Option verbFlags
+                      ++ [ SysTools.Option "-o"
+                         , SysTools.FileOption "" output_fn
+                         ]
                       ++ map SysTools.Option (
-                         md_c_flags
+                         []
 
-#ifdef mingw32_TARGET_OS
                       -- 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"]
-#endif
+                      ++ (if platformOS (targetPlatform dflags) == OSMinGW32
+                          then ["-Wl,--enable-auto-import"]
+                          else [])
+
                       ++ o_files
                       ++ extra_ld_inputs
                       ++ lib_path_opts
@@ -1583,8 +1660,7 @@ linkBinary dflags o_files dep_packages = do
 #endif
                       ++ pkg_lib_path_opts
                       ++ main_lib
-                      ++ rtsEnabledObj
-                      ++ rtsOptsObj
+                      ++ [extraLinkObj]
                       ++ pkg_link_opts
 #ifdef darwin_TARGET_OS
                       ++ pkg_framework_path_opts
@@ -1603,19 +1679,15 @@ linkBinary dflags o_files dep_packages = do
 exeFileName :: DynFlags -> FilePath
 exeFileName dflags
   | Just s <- outputFile dflags =
-#if defined(mingw32_HOST_OS)
-      if null (takeExtension s)
-        then s <.> "exe"
-        else s
-#else
-      s
-#endif
+      if platformOS (targetPlatform dflags) == OSMinGW32
+      then if null (takeExtension s)
+           then s <.> "exe"
+           else s
+      else s
   | otherwise =
-#if defined(mingw32_HOST_OS)
-        "main.exe"
-#else
-        "a.out"
-#endif
+      if platformOS (targetPlatform dflags) == OSMinGW32
+      then "main.exe"
+      else "a.out"
 
 maybeCreateManifest
    :: DynFlags
@@ -1677,7 +1749,7 @@ maybeCreateManifest dflags exe_filename = do
 
 linkDynLib :: DynFlags -> [String] -> [PackageId] -> IO ()
 linkDynLib dflags o_files dep_packages = do
-    let verb = getVerbFlag dflags
+    let verbFlags = getVerbFlags dflags
     let o_file = outputFile dflags
 
     pkgs <- getPreloadPackagesAnd dflags dep_packages
@@ -1711,10 +1783,9 @@ linkDynLib dflags o_files dep_packages = do
         -- probably _stub.o files
     extra_ld_inputs <- readIORef v_Ld_inputs
 
-    let md_c_flags = machdepCCOpts dflags
     let extra_ld_opts = getOpts dflags opt_l
 
-    rtsEnabledObj <- mkRtsOptionsLevelObj dflags
+    extraLinkObj <- mkExtraObjToLinkIntoBinary dflags dep_packages
 
 #if defined(mingw32_HOST_OS)
     -----------------------------------------------------------------------------
@@ -1722,28 +1793,27 @@ linkDynLib dflags o_files dep_packages = do
     -----------------------------------------------------------------------------
     let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
 
-    SysTools.runLink dflags
-         ([ SysTools.Option verb
-          , SysTools.Option "-o"
-          , SysTools.FileOption "" output_fn
-          , SysTools.Option "-shared"
-          ] ++
-          [ SysTools.FileOption "-Wl,--out-implib=" (output_fn ++ ".a")
-          | dopt Opt_SharedImplib dflags
-          ]
+    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 (
-            md_c_flags
 
          -- 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"]
+            ["-Wl,--enable-auto-import"]
 
          ++ extra_ld_inputs
          ++ lib_path_opts
          ++ extra_ld_opts
          ++ pkg_lib_path_opts
-         ++ rtsEnabledObj
+         ++ [extraLinkObj]
          ++ pkg_link_opts
         ))
 #elif defined(darwin_TARGET_OS)
@@ -1782,15 +1852,14 @@ linkDynLib dflags o_files dep_packages = do
         Nothing -> do
             pwd <- getCurrentDirectory
             return $ pwd `combine` output_fn
-    SysTools.runLink dflags
-         ([ SysTools.Option verb
-          , SysTools.Option "-dynamiclib"
-          , SysTools.Option "-o"
-          , SysTools.FileOption "" output_fn
-          ]
+    SysTools.runLink dflags (
+            map SysTools.Option verbFlags
+         ++ [ SysTools.Option "-dynamiclib"
+            , SysTools.Option "-o"
+            , SysTools.FileOption "" output_fn
+            ]
          ++ map SysTools.Option (
-            md_c_flags
-         ++ o_files
+            o_files
          ++ [ "-undefined", "dynamic_lookup", "-single_module",
 #if !defined(x86_64_TARGET_ARCH)
               "-Wl,-read_only_relocs,suppress",
@@ -1800,7 +1869,7 @@ linkDynLib dflags o_files dep_packages = do
          ++ lib_path_opts
          ++ extra_ld_opts
          ++ pkg_lib_path_opts
-         ++ rtsEnabledObj
+         ++ [extraLinkObj]
          ++ pkg_link_opts
         ))
 #else
@@ -1818,14 +1887,13 @@ linkDynLib dflags o_files dep_packages = do
                              -- non-PIC intra-package-relocations
                              ["-Wl,-Bsymbolic"]
 
-    SysTools.runLink dflags
-         ([ SysTools.Option verb
-          , SysTools.Option "-o"
-          , SysTools.FileOption "" output_fn
-          ]
+    SysTools.runLink dflags (
+            map SysTools.Option verbFlags
+         ++ [ SysTools.Option "-o"
+            , SysTools.FileOption "" output_fn
+            ]
          ++ map SysTools.Option (
-            md_c_flags
-         ++ o_files
+            o_files
          ++ [ "-shared" ]
          ++ bsymbolicFlag
             -- Set the library soname. We use -h rather than -soname as
@@ -1835,7 +1903,7 @@ linkDynLib dflags o_files dep_packages = do
          ++ lib_path_opts
          ++ extra_ld_opts
          ++ pkg_lib_path_opts
-         ++ rtsEnabledObj
+         ++ [extraLinkObj]
          ++ pkg_link_opts
         ))
 #endif
@@ -1851,14 +1919,11 @@ doCpp dflags raw include_cc_opts input_fn output_fn = do
     let include_paths = foldr (\ x xs -> "-I" : x : xs) []
                           (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)
@@ -1871,7 +1936,7 @@ doCpp dflags raw include_cc_opts input_fn output_fn = do
         -- 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]
+    cpp_prog       (   map SysTools.Option verbFlags
                     ++ map SysTools.Option include_paths
                     ++ map SysTools.Option hsSourceCppOpts
                     ++ map SysTools.Option target_defs
@@ -1906,16 +1971,21 @@ joinObjectFiles dflags o_files output_fn = do
                             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 ]
-                         ++ map SysTools.Option md_c_flags
                          ++ args)
+
       ld_x_flag | null cLD_X = ""
                 | otherwise  = "-Wl,-x"
 
-      md_c_flags = machdepCCOpts dflags
-  
+      -- 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"
@@ -1937,5 +2007,4 @@ hscNextPhase dflags _ hsc_lang =
         HscLlvm        -> LlvmOpt
         HscNothing     -> StopLn
         HscInterpreted -> StopLn
-        _other         -> StopLn