5cc7cbb
diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs
5cc7cbb
--- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs	2011-01-22 14:49:22.000000000 +1000
5cc7cbb
+++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs	2011-01-22 14:49:22.000000000 +1000
5cc7cbb
@@ -488,6 +488,7 @@
5cc7cbb
                     withVanillaLib      = fromFlag $ configVanillaLib cfg,
5cc7cbb
                     withProfLib         = fromFlag $ configProfLib cfg,
5cc7cbb
                     withSharedLib       = fromFlag $ configSharedLib cfg,
5cc7cbb
+                    withDynExe          = fromFlag $ configDynExe cfg,
5cc7cbb
                     withProfExe         = fromFlag $ configProfExe cfg,
5cc7cbb
                     withOptimization    = fromFlag $ configOptimization cfg,
5cc7cbb
                     withGHCiLib         = fromFlag $ configGHCiLib cfg,
5cc7cbb
diff -u ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs.orig ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs
5cc7cbb
--- ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs.orig	2010-11-13 04:10:09.000000000 +1000
5cc7cbb
+++ ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs	2011-01-22 14:52:52.000000000 +1000
5cc7cbb
@@ -537,6 +537,7 @@
5cc7cbb
      info verbosity "Building C Sources..."
5cc7cbb
      sequence_ [do let (odir,args) = constructCcCmdLine lbi libBi clbi pref
5cc7cbb
                                                         filename verbosity
5cc7cbb
+                                                        False
5cc7cbb
                                                         (withProfLib lbi)
5cc7cbb
                    createDirectoryIfMissingVerbose verbosity True odir
5cc7cbb
                    runGhcProg args
5cc7cbb
@@ -671,7 +672,7 @@
5cc7cbb
    info verbosity "Building C Sources."
5cc7cbb
    sequence_ [do let (odir,args) = constructCcCmdLine lbi exeBi clbi
5cc7cbb
                                           exeDir filename verbosity
5cc7cbb
-                                          (withProfExe lbi)
5cc7cbb
+                                          (withDynExe lbi) (withProfExe lbi)
5cc7cbb
                  createDirectoryIfMissingVerbose verbosity True odir
5cc7cbb
                  runGhcProg args
5cc7cbb
              | filename <- cSources exeBi]
5cc7cbb
@@ -679,7 +680,7 @@
5cc7cbb
   srcMainFile <- findFile (exeDir : hsSourceDirs exeBi) modPath
5cc7cbb
 
5cc7cbb
   let cObjs = map (`replaceExtension` objExtension) (cSources exeBi)
5cc7cbb
-  let binArgs linkExe profExe =
5cc7cbb
+  let binArgs linkExe dynExe profExe =
5cc7cbb
              "--make"
5cc7cbb
           :  (if linkExe
5cc7cbb
                  then ["-o", targetDir  exeNameReal]
5cc7cbb
@@ -691,6 +692,9 @@
5cc7cbb
           ++ ["-l"++lib | lib <- extraLibs exeBi]
5cc7cbb
           ++ ["-L"++libDir | libDir <- extraLibDirs exeBi]
5cc7cbb
           ++ concat [["-framework", f] | f <- PD.frameworks exeBi]
5cc7cbb
+          ++ if dynExe
5cc7cbb
+                then ["-dynamic"]
5cc7cbb
+                else []
5cc7cbb
           ++ if profExe
5cc7cbb
                 then ["-prof",
5cc7cbb
                       "-hisuf", "p_hi",
5cc7cbb
@@ -704,9 +708,9 @@
5cc7cbb
   -- run at compile time needs to be the vanilla ABI so it can
5cc7cbb
   -- be loaded up and run by the compiler.
5cc7cbb
   when (withProfExe lbi && TemplateHaskell `elem` allExtensions exeBi)
5cc7cbb
-     (runGhcProg (binArgs False False))
5cc7cbb
+     (runGhcProg (binArgs (withDynExe lbi) False False))
5cc7cbb
 
5cc7cbb
-  runGhcProg (binArgs True (withProfExe lbi))
5cc7cbb
+  runGhcProg (binArgs True (withDynExe lbi) (withProfExe lbi))
5cc7cbb
 
5cc7cbb
 -- | Filter the "-threaded" flag when profiling as it does not
5cc7cbb
 --   work with ghc-6.8 and older.
5cc7cbb
@@ -836,9 +840,9 @@
5cc7cbb
     ierror     = error ("internal error: unexpected package db stack: " ++ show dbstack)
5cc7cbb
 
5cc7cbb
 constructCcCmdLine :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo
5cc7cbb
-                   -> FilePath -> FilePath -> Verbosity -> Bool
5cc7cbb
+                   -> FilePath -> FilePath -> Verbosity -> Bool -> Bool
5cc7cbb
                    ->(FilePath,[String])
5cc7cbb
-constructCcCmdLine lbi bi clbi pref filename verbosity profiling
5cc7cbb
+constructCcCmdLine lbi bi clbi pref filename verbosity dynamic profiling
5cc7cbb
   =  let odir | compilerVersion (compiler lbi) >= Version [6,4,1] []  = pref
5cc7cbb
               | otherwise = pref  takeDirectory filename
5cc7cbb
                         -- ghc 6.4.1 fixed a bug in -odir handling
5cc7cbb
@@ -852,6 +856,7 @@
5cc7cbb
          -- option to ghc here when compiling C code, so that the PROFILING
5cc7cbb
          -- macro gets defined. The macro is used in ghc's Rts.h in the
5cc7cbb
          -- definitions of closure layouts (Closures.h).
5cc7cbb
+         ++ ["-dynamic" | dynamic]
5cc7cbb
          ++ ["-prof" | profiling])
5cc7cbb
 
5cc7cbb
 ghcCcOptions :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo
5cc7cbb
diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs
5cc7cbb
--- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs	2011-01-22 14:49:22.000000000 +1000
5cc7cbb
+++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs	2011-01-22 14:49:22.000000000 +1000
5cc7cbb
@@ -118,6 +118,7 @@
5cc7cbb
         withVanillaLib:: Bool,  -- ^Whether to build normal libs.
5cc7cbb
         withProfLib   :: Bool,  -- ^Whether to build profiling versions of libs.
5cc7cbb
         withSharedLib :: Bool,  -- ^Whether to build shared versions of libs.
5cc7cbb
+        withDynExe    :: Bool,  -- ^Whether to link executables dynamically
5cc7cbb
         withProfExe   :: Bool,  -- ^Whether to build executables for profiling.
5cc7cbb
         withOptimization :: OptimisationLevel, -- ^Whether to build with optimization (if available).
5cc7cbb
         withGHCiLib   :: Bool,  -- ^Whether to build libs suitable for use with GHCi.
5cc7cbb
diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs
5cc7cbb
--- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs	2011-01-22 14:49:22.000000000 +1000
5cc7cbb
+++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs	2011-01-22 14:49:22.000000000 +1000
5cc7cbb
@@ -270,6 +270,7 @@
5cc7cbb
     configVanillaLib    :: Flag Bool,     -- ^Enable vanilla library
5cc7cbb
     configProfLib       :: Flag Bool,     -- ^Enable profiling in the library
5cc7cbb
     configSharedLib     :: Flag Bool,     -- ^Build shared library
5cc7cbb
+    configDynExe        :: Flag Bool,     -- ^Enable dynamic linking of the executables.
5cc7cbb
     configProfExe       :: Flag Bool,     -- ^Enable profiling in the executables.
5cc7cbb
     configConfigureArgs :: [String],      -- ^Extra arguments to @configure@
5cc7cbb
     configOptimization  :: Flag OptimisationLevel,  -- ^Enable optimization.
5cc7cbb
@@ -301,6 +302,7 @@
5cc7cbb
     configVanillaLib   = Flag True,
5cc7cbb
     configProfLib      = Flag False,
5cc7cbb
     configSharedLib    = Flag False,
5cc7cbb
+    configDynExe       = Flag False,
5cc7cbb
     configProfExe      = Flag False,
5cc7cbb
     configOptimization = Flag NormalOptimisation,
5cc7cbb
     configProgPrefix   = Flag (toPathTemplate ""),
5cc7cbb
@@ -388,10 +390,16 @@
5cc7cbb
          configSharedLib (\v flags -> flags { configSharedLib = v })
5cc7cbb
          (boolOpt [] [])
5cc7cbb
 
5cc7cbb
+      ,option "" ["executable-dynamic"]
5cc7cbb
+         "Executable dynamic linking (fedora patch)"
5cc7cbb
+         configDynExe (\v flags -> flags { configDynExe = v })
5cc7cbb
+         (boolOpt [] [])
5cc7cbb
+
5cc7cbb
       ,option "" ["executable-profiling"]
5cc7cbb
          "Executable profiling"
5cc7cbb
          configProfExe (\v flags -> flags { configProfExe = v })
5cc7cbb
          (boolOpt [] [])
5cc7cbb
+
5cc7cbb
       ,multiOption "optimization"
5cc7cbb
          configOptimization (\v flags -> flags { configOptimization = v })
5cc7cbb
          [optArg' "n" (Flag . flagToOptimisationLevel)
5cc7cbb
@@ -553,6 +561,7 @@
5cc7cbb
     configVanillaLib    = mempty,
5cc7cbb
     configProfLib       = mempty,
5cc7cbb
     configSharedLib     = mempty,
5cc7cbb
+    configDynExe        = mempty,
5cc7cbb
     configProfExe       = mempty,
5cc7cbb
     configConfigureArgs = mempty,
5cc7cbb
     configOptimization  = mempty,
5cc7cbb
@@ -583,6 +592,7 @@
5cc7cbb
     configVanillaLib    = combine configVanillaLib,
5cc7cbb
     configProfLib       = combine configProfLib,
5cc7cbb
     configSharedLib     = combine configSharedLib,
5cc7cbb
+    configDynExe        = combine configDynExe,
5cc7cbb
     configProfExe       = combine configProfExe,
5cc7cbb
     configConfigureArgs = combine configConfigureArgs,
5cc7cbb
     configOptimization  = combine configOptimization,