Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/2324b40f65b5cb7e427c5ec0185d635422b4a265

>---------------------------------------------------------------

commit 2324b40f65b5cb7e427c5ec0185d635422b4a265
Author: Simon Marlow <marlo...@gmail.com>
Date:   Tue Oct 23 12:22:59 2012 +0100

    removeWay should also unset the wayGeneralFlags
    
    This means that -static now disables the -fPIC that we're currently
    getting by default.

>---------------------------------------------------------------

 compiler/main/DynFlags.hs |   27 +++++++++++++++++++--------
 1 files changed, 19 insertions(+), 8 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index e1e8c5a..121c85f 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -1026,7 +1026,10 @@ wayGeneralFlags platform WayDyn =
             -- different from the current one.
             OSMinGW32 -> [Opt_PIC]
             OSDarwin  -> [Opt_PIC]
-            OSLinux   -> [Opt_PIC]
+            OSLinux   -> [Opt_PIC] -- This needs to be here for GHCi to work:
+                                   -- GHCi links objects into a .so before
+                                   -- loading the .so using the system linker.
+                                   -- Only PIC objects can be linked into a 
.so.
             _         -> []
 wayGeneralFlags _ WayProf     = [Opt_SccProfilingOn]
 wayGeneralFlags _ WayEventLog = []
@@ -2550,12 +2553,7 @@ defaultFlags settings
     ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
              -- The default -O0 options
 
-    ++ (case platformOS platform of
-        OSDarwin ->
-            case platformArch platform of
-            ArchX86_64         -> [Opt_PIC]
-            _                  -> []
-        _ -> [])
+    ++ default_PIC platform
 
     ++ (if pc_dYNAMIC_BY_DEFAULT (sPlatformConstants settings)
         then wayGeneralFlags platform WayDyn
@@ -2563,6 +2561,12 @@ defaultFlags settings
 
     where platform = sTargetPlatform settings
 
+default_PIC :: Platform -> [GeneralFlag]
+default_PIC platform =
+  case (platformOS platform, platformArch platform) of
+    (OSDarwin, ArchX86_64) -> [Opt_PIC]
+    _                      -> []
+
 impliedFlags :: [(ExtensionFlag, TurnOnFlag, ExtensionFlag)]
 impliedFlags
   = [ (Opt_RankNTypes,                turnOn, Opt_ExplicitForAll)
@@ -2834,7 +2838,14 @@ addWay w = do upd (\dfs -> dfs { ways = w : ways dfs })
               mapM_ setGeneralFlag $ wayGeneralFlags platform w
 
 removeWay :: Way -> DynP ()
-removeWay w = upd (\dfs -> dfs { ways = filter (w /=) (ways dfs) })
+removeWay w = do
+  upd (\dfs -> dfs { ways = filter (w /=) (ways dfs) })
+  dfs <- liftEwM getCmdLineState
+  let platform = targetPlatform dfs
+  -- XXX: wayExtras?
+  mapM_ unSetGeneralFlag $ wayGeneralFlags platform w
+  -- turn Opt_PIC back on if necessary for this platform:
+  mapM_ setGeneralFlag $ default_PIC platform
 
 --------------------------
 setGeneralFlag, unSetGeneralFlag :: GeneralFlag -> DynP ()



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to