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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/22423fc93a008732e426f10f1b545b5d571173f3

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

commit 22423fc93a008732e426f10f1b545b5d571173f3
Author: David Terei <[email protected]>
Date:   Mon May 2 05:58:56 2011 +1000

    LLVM: Add support for 64bit OSX. (partial #4210)

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

 compiler/llvmGen/LlvmMangler.hs |   16 ++++++++++++----
 compiler/main/DynFlags.hs       |    9 +++++----
 2 files changed, 17 insertions(+), 8 deletions(-)

diff --git a/compiler/llvmGen/LlvmMangler.hs b/compiler/llvmGen/LlvmMangler.hs
index ac187e0..890f710 100644
--- a/compiler/llvmGen/LlvmMangler.hs
+++ b/compiler/llvmGen/LlvmMangler.hs
@@ -12,6 +12,8 @@
 
 module LlvmMangler ( llvmFixupAsm ) where
 
+#include "HsVersions.h"
+
 import Control.Exception
 import qualified Data.ByteString.Char8 as B
 import Data.Char
@@ -23,14 +25,20 @@ infoSec, newInfoSec, newLine, spInst, jmpInst :: 
B.ByteString
 infoSec    = B.pack "\t.section\t__STRIP,__me"
 newInfoSec = B.pack "\n\t.text"
 newLine    = B.pack "\n"
-spInst     = B.pack ", %esp\n"
 jmpInst    = B.pack "\n\tjmp"
 
-infoLen, spFix, labelStart :: Int
-infoLen = B.length infoSec
-spFix   = 4
+infoLen, labelStart, spFix :: Int
+infoLen    = B.length infoSec
 labelStart = B.length jmpInst
 
+#if x86_64_TARGET_ARCH
+spInst     = B.pack ", %rsp\n"
+spFix      = 8
+#else
+spInst     = B.pack ", %esp\n"
+spFix      = 4
+#endif
+
 -- Search Predicates
 eolPred, dollarPred, commaPred :: Char -> Bool
 eolPred    = ((==) '\n')
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 1d2d1f5..4131a34 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -1103,12 +1103,13 @@ parseDynamicFlags_ dflags0 args pkg_flags = do
   when (not (null errs)) $ ghcError $ errorsToGhcException errs
 
   let (pic_warns, dflags2)
-        | not (cTargetArch == X86_64 && cTargetOS == Linux) &&
+        | not (cTargetArch == X86_64 && (cTargetOS == Linux || cTargetOS == 
OSX)) &&
           (not opt_Static || opt_PIC) &&
           hscTarget dflags1 == HscLlvm
-        = ([L noSrcSpan $ "Warning: -fllvm is incompatible with -fPIC and -"
-                       ++ "dynamic on this platform;\n"
-                       ++ "         using " ++ showHscTargetFlag 
defaultObjectTarget ++ " instead"],
+        = ([L noSrcSpan $ "Warning: -fllvm is incompatible with -fPIC and "
+                       ++ "-dynamic on this platform;\n"
+                       ++ "         using "
+                       ++ showHscTargetFlag defaultObjectTarget ++ " instead"],
                 dflags1{ hscTarget = defaultObjectTarget })
         | otherwise = ([], dflags1)
 



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to