Remove LazyUniqFM; fixes trac #3880
[ghc-hetmet.git] / compiler / main / DriverPipeline.hs
index 5355d8f..c0aed96 100644 (file)
@@ -19,7 +19,7 @@ module DriverPipeline (
 
        -- Interfaces for the compilation manager (interpreted/batch-mode)
    preprocess, 
-   compile,
+   compile, compile',
    link, 
 
   ) where
@@ -35,7 +35,7 @@ import Finder
 import HscTypes
 import Outputable
 import Module
-import LazyUniqFM              ( eltsUFM )
+import UniqFM          ( eltsUFM )
 import ErrUtils
 import DynFlags
 import StaticFlags     ( v_Ld_inputs, opt_Static, WayName(..) )
@@ -48,12 +48,12 @@ import Maybes               ( expectJust )
 import ParserCoreUtils ( getCoreModuleName )
 import SrcLoc
 import FastString
-import MonadUtils
+-- import MonadUtils
 
-import Data.Either
+-- import Data.Either
 import Exception
-import Data.IORef      ( readIORef, writeIORef, IORef )
-import GHC.Exts                ( Int(..) )
+import Data.IORef      ( readIORef )
+-- import GHC.Exts             ( Int(..) )
 import System.Directory
 import System.FilePath
 import System.IO
@@ -103,7 +103,26 @@ compile :: GhcMonad m =>
         -> Maybe Linkable  -- ^ old linkable, if we have one
         -> m HomeModInfo   -- ^ the complete HomeModInfo, if successful
 
-compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
+compile = compile' (hscCompileNothing, hscCompileInteractive, hscCompileBatch)
+
+type Compiler m a = HscEnv -> ModSummary -> Bool
+                  -> Maybe ModIface -> Maybe (Int, Int)
+                  -> m a
+
+compile' :: GhcMonad m =>
+           (Compiler m (HscStatus, ModIface, ModDetails),
+            Compiler m (InteractiveStatus, ModIface, ModDetails),
+            Compiler m (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
+        -> m 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
@@ -153,7 +172,7 @@ compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
            = ASSERT (isJust maybe_old_linkable)
              return maybe_old_linkable
 
-       handleBatch (HscRecomp hasStub)
+       handleBatch (HscRecomp hasStub _)
            | isHsBoot src_flavour
                = do when (isObjectTarget hsc_lang) $ -- interpreted reaches here too
                        liftIO $ SysTools.touch dflags' "Touching object file"
@@ -168,7 +187,7 @@ compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
                             -> return ([], ms_hs_date summary)
                           -- We're in --make mode: finish the compilation pipeline.
                           _other
-                            -> do runPipeline StopLn hsc_env' (output_fn,Nothing)
+                            -> do _ <- runPipeline StopLn hsc_env' (output_fn,Nothing)
                                               (Just basename)
                                               Persistent
                                               (Just location)
@@ -179,10 +198,13 @@ compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
                                   (hs_unlinked ++ stub_unlinked)
                     return (Just linkable)
 
-       handleInterpreted InteractiveNoRecomp
+       handleInterpreted HscNoRecomp
            = ASSERT (isJust maybe_old_linkable)
              return maybe_old_linkable
-       handleInterpreted (InteractiveRecomp hasStub comp_bc modBreaks)
+       handleInterpreted (HscRecomp _hasStub Nothing)
+           = ASSERT (isHsBoot src_flavour)
+             return maybe_old_linkable
+       handleInterpreted (HscRecomp hasStub (Just (comp_bc, modBreaks)))
            = do stub_unlinked <- getStubLinkable hasStub
                 let hs_unlinked = [BCOs comp_bc modBreaks]
                     unlinked_time = ms_hs_date summary
@@ -208,15 +230,13 @@ compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
                                      hm_linkable = linkable })
    -- run the compiler
    case hsc_lang of
-      HscInterpreted
-        | isHsBoot src_flavour -> 
-                runCompiler hscCompileNothing handleBatch
-        | otherwise -> 
-                runCompiler hscCompileInteractive handleInterpreted
+      HscInterpreted ->
+                runCompiler interactiveCompiler handleInterpreted
       HscNothing -> 
-                runCompiler hscCompileNothing handleBatch
+                runCompiler nothingCompiler handleBatch
       _other -> 
-                runCompiler hscCompileBatch handleBatch
+                runCompiler batchCompiler handleBatch
+
 
 -----------------------------------------------------------------------------
 -- stub .h and .c files (for foreign export support)
@@ -240,12 +260,11 @@ compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
 compileStub :: GhcMonad m => HscEnv -> Module -> ModLocation
             -> m FilePath
 compileStub hsc_env mod location = do
-       let (o_base, o_ext) = splitExtension (ml_obj_file location)
-           stub_o = (o_base ++ "_stub") <.> o_ext
-
        -- compile the _stub.c file w/ gcc
-       let (stub_c,_,_) = mkStubPaths (hsc_dflags hsc_env) (moduleName mod) location
-       runPipeline StopLn hsc_env (stub_c,Nothing)  Nothing
+       let (stub_c,_,stub_o) = mkStubPaths (hsc_dflags hsc_env) 
+                                   (moduleName mod) location
+
+       _ <- runPipeline StopLn hsc_env (stub_c,Nothing)  Nothing
                (SpecificFile stub_o) Nothing{-no ModLocation-}
 
        return stub_o
@@ -277,6 +296,26 @@ 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
+
+#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)
+
+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
@@ -328,13 +367,6 @@ link LinkBinary dflags batch_attempt_linking hpt
                                 text "   Main.main not exported; not linking.")
         return Succeeded
 
--- warning suppression
-link other _ _ _ = panicBadLink other
-
-panicBadLink :: GhcLink -> a
-panicBadLink other = panic ("link: GHC not built to link this way: " ++
-                            show other)
-
 
 linkingNeeded :: DynFlags -> [Linkable] -> [PackageId] -> IO Bool
 linkingNeeded dflags linkables pkg_deps = do
@@ -459,7 +491,7 @@ data PipelineOutput
 -- 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.
 runPipeline
   :: GhcMonad m =>
@@ -664,19 +696,30 @@ runPhase (Unlit sf) _stop hsc_env _basename _suff input_fn get_output_fn maybe_l
 runPhase (Cpp sf) _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc
   = do let dflags0 = hsc_dflags hsc_env
        src_opts <- liftIO $ getOptionsFromFile dflags0 input_fn
-       (dflags, unhandled_flags, warns)
-           <- liftIO $ parseDynamicFlags dflags0 src_opts
-       liftIO $ handleFlagWarnings dflags warns  -- XXX: may exit the program
-       liftIO $ checkProcessArgsResult unhandled_flags -- XXX: may throw program error
+       (dflags1, unhandled_flags, warns)
+           <- liftIO $ parseDynamicNoPackageFlags dflags0 src_opts
+       checkProcessArgsResult unhandled_flags
+
+       if not (dopt Opt_Cpp dflags1) then do
+           -- we have to be careful to emit warnings only once.
+           unless (dopt Opt_Pp dflags1) $ 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)
+           return (HsPp sf, dflags1, maybe_loc, input_fn)
        else do
-           output_fn <- liftIO $ get_output_fn dflags (HsPp sf) maybe_loc
-           liftIO $ doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn
-           return (HsPp sf, dflags, maybe_loc, output_fn)
+           output_fn <- liftIO $ get_output_fn dflags1 (HsPp sf) maybe_loc
+           liftIO $ 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 <- liftIO $ getOptionsFromFile dflags0 output_fn
+            (dflags2, unhandled_flags, warns)
+                <- liftIO $ parseDynamicNoPackageFlags dflags0 src_opts
+            unless (dopt Opt_Pp dflags2) $ handleFlagWarnings dflags2 warns
+            -- the HsPp pass below will emit warnings
+            checkProcessArgsResult unhandled_flags
+
+           return (HsPp sf, dflags2, maybe_loc, output_fn)
 
 -------------------------------------------------------------------------------
 -- HsPp phase 
@@ -698,7 +741,15 @@ runPhase (HsPp sf) _stop hsc_env basename suff input_fn get_output_fn maybe_loc
                             ] ++
                             map SysTools.Option hspp_opts
                           )
-           return (Hsc sf, dflags, maybe_loc, output_fn)
+
+            -- re-read pragmas now that we've parsed the file (see #3674)
+            src_opts <- liftIO $ getOptionsFromFile dflags output_fn
+            (dflags1, unhandled_flags, warns)
+                <- liftIO $ parseDynamicNoPackageFlags dflags src_opts
+            handleFlagWarnings dflags1 warns
+            checkProcessArgsResult unhandled_flags
+
+           return (Hsc sf, dflags1, maybe_loc, output_fn)
 
 -----------------------------------------------------------------------------
 -- Hsc phase
@@ -726,8 +777,8 @@ runPhase (Hsc src_flavour) stop hsc_env basename suff input_fn get_output_fn _ma
                     m <- liftIO $ getCoreModuleName input_fn
                     return (Nothing, mkModuleName m, [], [])
 
-                _           -> liftIO $ do
-                    buf <- hGetStringBuffer input_fn
+                _           -> do
+                    buf <- liftIO $ hGetStringBuffer input_fn
                     (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename <.> suff)
                     return (Just buf, mod_name, imps, src_imps)
 
@@ -830,7 +881,7 @@ runPhase (Hsc src_flavour) stop hsc_env basename suff input_fn get_output_fn _ma
                     -- 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)
-          (HscRecomp hasStub)
+          (HscRecomp hasStub _)
               -> do when hasStub $
                          do stub_o <- compileStub hsc_env' mod location4
                             liftIO $ consIORef v_Ld_inputs stub_o
@@ -942,21 +993,21 @@ runPhase cc_phase _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc
                         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"]
 
-
-
        liftIO $ 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"] ++
+                                                then SysTools.Option "c++" 
+                                                else SysTools.Option "c"] ++
                        [ SysTools.FileOption "" input_fn
                        , SysTools.Option "-o"
                        , SysTools.FileOption "" output_fn
@@ -964,6 +1015,18 @@ runPhase cc_phase _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc
                       ++ map SysTools.Option (
                          md_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
+                               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
@@ -1048,13 +1111,13 @@ runPhase SplitMangle _stop hsc_env _basename _suff input_fn _get_output_fn maybe
        -- 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)
+           dflags' = dflags { splitInfo = Just (split_s_prefix, n_files) }
 
        -- Remember to delete all these files
-       addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s"
-                       | n <- [1..n_files]]
+       addFilesToClean dflags' [ split_s_prefix ++ "__" ++ show n ++ ".s"
+                               | n <- [1..n_files]]
 
-       return (SplitAs, dflags, maybe_loc, "**splitmangle**")
+       return (SplitAs, dflags', maybe_loc, "**splitmangle**")
          -- we don't use the filename
 
 -----------------------------------------------------------------------------
@@ -1072,6 +1135,7 @@ runPhase As _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc
        -- might be a hierarchical module.
        createDirectoryHierarchy (takeDirectory output_fn)
 
+       let (md_c_flags, _) = machdepCCOpts dflags
        SysTools.runAs dflags   
                       (map SysTools.Option as_opts
                       ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
@@ -1089,7 +1153,8 @@ runPhase As _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc
                          , SysTools.FileOption "" input_fn
                          , SysTools.Option "-o"
                          , SysTools.FileOption "" output_fn
-                         ])
+                         ]
+                      ++ map SysTools.Option md_c_flags)
 
        return (StopLn, dflags, maybe_loc, output_fn)
 
@@ -1100,8 +1165,8 @@ runPhase SplitAs _stop hsc_env _basename _suff _input_fn get_output_fn maybe_loc
         output_fn <- get_output_fn dflags StopLn maybe_loc
 
         let base_o = dropExtension output_fn
-            split_odir  = base_o ++ "_split"
             osuf = objectSuf dflags
+            split_odir  = base_o ++ "_" ++ osuf ++ "_split"
 
         createDirectoryHierarchy split_odir
 
@@ -1112,20 +1177,34 @@ runPhase SplitAs _stop hsc_env _basename _suff _input_fn get_output_fn maybe_loc
 
         let as_opts = getOpts dflags opt_a
 
-        (split_s_prefix, n) <- readIORef v_Split_info
+        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 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
+        -- (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.Option "-o"
                           , SysTools.FileOption "" (split_obj n)
                           , SysTools.FileOption "" (split_s n)
-                          ])
+                          ]
+                       ++ map SysTools.Option md_c_flags)
 
         mapM_ assemble_file [1..n]
 
@@ -1136,7 +1215,9 @@ runPhase SplitAs _stop hsc_env _basename _suff _input_fn get_output_fn maybe_loc
                             SysTools.Option "-Wl,-r",
                             SysTools.Option ld_x_flag,
                             SysTools.Option "-o",
-                            SysTools.FileOption "" output_fn ] ++ args)
+                            SysTools.FileOption "" output_fn ]
+                         ++ map SysTools.Option md_c_flags
+                         ++ args)
             ld_x_flag | null cLD_X = ""
                       | otherwise  = "-Wl,-x"
 
@@ -1177,7 +1258,7 @@ runPhase_MoveBinary dflags input_fn dep_packages
            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?
-        tryIO (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
@@ -1188,8 +1269,8 @@ runPhase_MoveBinary dflags input_fn dep_packages
          Wrapped wrapmode ->
              do
                let (o_base, o_ext) = splitExtension input_fn
-               let wrapped_executable | o_ext == "exe" = (o_base ++ "_real") <.> o_ext
-                                      | otherwise = input_fn ++ "_real"
+               let wrapped_executable | o_ext == "exe" = (o_base ++ ".dyn") <.> o_ext
+                                      | otherwise = input_fn ++ ".dyn"
                behaviour <- wrapper_behaviour dflags wrapmode dep_packages
 
                 -- THINKME isn't this possible to do a bit nicer?
@@ -1218,6 +1299,20 @@ wrapper_behaviour dflags mode dep_packages =
        putStrLn (unwords (map (packageIdString . packageConfigId) allpkg))
        return $ 'F':s ++ ';':(seperateBySemiColon (map (packageIdString . packageConfigId) allpkg))
 
+mkExtraCObj :: DynFlags -> [String] -> IO FilePath
+mkExtraCObj dflags xs
+ = do cFile <- newTempName dflags "c"
+      oFile <- newTempName dflags "o"
+      writeFile cFile $ unlines 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
+
 -- 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 $
@@ -1312,7 +1407,7 @@ linkBinary dflags o_files dep_packages = do
 
     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
     let pkg_lib_path_opts = concat (map get_pkg_lib_path_opts pkg_lib_paths)
-#ifdef linux_TARGET_OS
+#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
@@ -1322,6 +1417,27 @@ linkBinary dflags o_files dep_packages = do
     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" ]
+    rtsEnabledObj <- if dopt Opt_RtsOptsEnabled dflags
+                     then do fn <- mkExtraCObj dflags
+                                    ["#include \"Rts.h\"",
+                                     "const rtsBool rtsOptsEnabled = rtsTrue;"]
+                             return [fn]
+                     else return []
+    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 []
+
     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
 
 #ifdef darwin_TARGET_OS
@@ -1338,12 +1454,6 @@ linkBinary dflags o_files dep_packages = do
         framework_opts = concat [ ["-framework", fw] | fw <- reverse frameworks ]
         -- reverse because they're added in reverse order from the cmd line
 #endif
-#ifdef mingw32_TARGET_OS
-    let dynMain = if not opt_Static then
-                     (head (libraryDirs (getPackageDetails (pkgState dflags) rtsPackageId))) ++ "/Main.dyn_o"
-                 else
-                     ""
-#endif
        -- probably _stub.o files
     extra_ld_inputs <- readIORef v_Ld_inputs
 
@@ -1365,7 +1475,7 @@ linkBinary dflags o_files dep_packages = do
 
     let
        thread_opts | WayThreaded `elem` ways = [ 
-#if !defined(mingw32_TARGET_OS) && !defined(freebsd_TARGET_OS)
+#if !defined(mingw32_TARGET_OS) && !defined(freebsd_TARGET_OS) && !defined(haiku_TARGET_OS)
                        "-lpthread"
 #endif
 #if defined(osf3_TARGET_OS)
@@ -1384,10 +1494,13 @@ linkBinary dflags o_files dep_packages = do
                       ]
                      ++ map SysTools.Option (
                         md_c_flags
-                     ++ o_files
+
 #ifdef mingw32_TARGET_OS
-                     ++ [dynMain]
+                      -- 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
+                     ++ o_files
                      ++ extra_ld_inputs
                      ++ lib_path_opts
                      ++ extra_ld_opts
@@ -1397,6 +1510,9 @@ linkBinary dflags o_files dep_packages = do
                      ++ framework_opts
 #endif
                      ++ pkg_lib_path_opts
+                      ++ main_lib
+                      ++ rtsEnabledObj
+                      ++ rtsOptsObj
                      ++ pkg_link_opts
 #ifdef darwin_TARGET_OS
                      ++ pkg_framework_path_opts
@@ -1481,6 +1597,8 @@ maybeCreateManifest dflags exe_filename = do
         -- no FileOptions here: windres doesn't like seeing
         -- backslashes, apparently
 
+  removeFile manifest_filename
+
   return [rc_obj_filename]
 #endif
 
@@ -1494,10 +1612,22 @@ linkDynLib dflags o_files dep_packages = do
     -- because the RTS lib comes in several flavours and we want to be
     -- able to pick the flavour when a binary is linked.
     pkgs <- getPreloadPackagesAnd dflags dep_packages
-    let pkgs_no_rts = filter ((/= rtsPackageId) . packageConfigId) pkgs
 
+    -- On Windows we need to link the RTS import lib as Windows does
+    -- not allow undefined symbols.
+#if !defined(mingw32_HOST_OS)
+    let pkgs_no_rts = filter ((/= rtsPackageId) . packageConfigId) pkgs
+#else
+    let pkgs_no_rts = pkgs
+#endif
     let pkg_lib_paths = collectLibraryPaths pkgs_no_rts
-    let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
+    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
@@ -1520,11 +1650,18 @@ linkDynLib dflags o_files dep_packages = do
          , SysTools.Option "-o"
          , SysTools.FileOption "" output_fn
          , SysTools.Option "-shared"
-         , SysTools.FileOption "-Wl,--out-implib=" (output_fn ++ ".a")
+         ] ++
+         [ 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"]
+
         ++ extra_ld_inputs
         ++ lib_path_opts
         ++ extra_ld_opts
@@ -1555,16 +1692,22 @@ linkDynLib dflags o_files dep_packages = do
     --  later, so that it will not complain about the use of the option
     --  -undefined dynamic_lookup above.
     -- -install_name
-    --   Causes the dynamic linker to ignore the DYLD_LIBRARY_PATH when loading
-    --   this lib and instead look for it at its absolute path.
-    --   When installing the .dylibs (see target.mk), we'll change that path to
-    --   point to the place they are installed. Therefore, we won't have to set
-    --  up DYLD_LIBRARY_PATH specifically for ghc.
+    --   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"; }
 
-    pwd <- getCurrentDirectory
+    instName <- case dylibInstallName dflags of
+        Just n -> return n
+        Nothing -> do
+            pwd <- getCurrentDirectory
+            return $ pwd `combine` output_fn
     SysTools.runLink dflags
         ([ SysTools.Option verb
          , SysTools.Option "-dynamiclib"
@@ -1574,7 +1717,8 @@ linkDynLib dflags o_files dep_packages = do
         ++ map SysTools.Option (
            md_c_flags
         ++ o_files
-        ++ [ "-undefined", "dynamic_lookup", "-single_module", "-Wl,-macosx_version_min","-Wl,10.3", "-install_name " ++ (pwd </> output_fn) ]
+        ++ [ "-undefined", "dynamic_lookup", "-single_module", "-Wl,-macosx_version_min","-Wl,10.5",
+              "-Wl,-read_only_relocs,suppress", "-install_name", instName ]
         ++ extra_ld_inputs
         ++ lib_path_opts
         ++ extra_ld_opts
@@ -1587,6 +1731,14 @@ linkDynLib dflags o_files dep_packages = do
     -----------------------------------------------------------------------------
 
     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
         ([ SysTools.Option verb
@@ -1596,7 +1748,9 @@ linkDynLib dflags o_files dep_packages = do
         ++ map SysTools.Option (
            md_c_flags
         ++ o_files
-        ++ [ "-shared", "-Wl,-Bsymbolic" ] -- we need symbolic linking to resolve non-PIC intra-package-relocations
+        ++ [ "-shared" ]
+        ++ bsymbolicFlag
+         ++ [ "-Wl,-soname," ++ takeFileName output_fn ] -- set the library soname
         ++ extra_ld_inputs
         ++ lib_path_opts
         ++ extra_ld_opts
@@ -1700,5 +1854,3 @@ hscMaybeAdjustTarget dflags stop _ current_hsc_lang
                -- otherwise, stick to the plan
                 | otherwise = current_hsc_lang
 
-GLOBAL_VAR(v_Split_info, ("",0), (String,Int))
-       -- The split prefix and number of files