ghc/Cabal-option-executable-dynamic.patch

146 lines
7.7 KiB
Diff
Raw Normal View History

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