x86_64: support PIC and therefore, Mac OS X in the NCG
authorwolfgang.thaller@gmx.net <unknown>
Thu, 7 Dec 2006 13:16:07 +0000 (13:16 +0000)
committerwolfgang.thaller@gmx.net <unknown>
Thu, 7 Dec 2006 13:16:07 +0000 (13:16 +0000)
Supporting x86_64-apple-darwin in the NCG basically boils down to supporting
position-independent code in the NCG.
PIC code works almost exactly the same as on x86_64-linux, while position-dependent
code is not supported at all.
This patch implements -fPIC for x86_64-linux, too, but that is untested.

compiler/cmm/CLabel.hs
compiler/cmm/CmmOpt.hs
compiler/main/StaticFlags.hs
compiler/nativeGen/AsmCodeGen.lhs
compiler/nativeGen/MachCodeGen.hs
compiler/nativeGen/PositionIndependentCode.hs
compiler/nativeGen/PprMach.hs
mk/package.mk

index 54abe23..67f7a2e 100644 (file)
@@ -825,7 +825,14 @@ asmTempLabelPrefix =
 
 pprDynamicLinkerAsmLabel :: DynamicLinkerLabelInfo -> CLabel -> SDoc
 
-#if darwin_TARGET_OS
+#if x86_64_TARGET_ARCH && darwin_TARGET_OS
+pprDynamicLinkerAsmLabel GotSymbolPtr lbl
+  = pprCLabel lbl <> text "@GOTPCREL"
+pprDynamicLinkerAsmLabel GotSymbolOffset lbl
+  = pprCLabel lbl
+pprDynamicLinkerAsmLabel _ _
+  = panic "pprDynamicLinkerAsmLabel"
+#elif darwin_TARGET_OS
 pprDynamicLinkerAsmLabel CodeStub lbl
   = char 'L' <> pprCLabel lbl <> text "$stub"
 pprDynamicLinkerAsmLabel SymbolPtr lbl
@@ -839,6 +846,15 @@ pprDynamicLinkerAsmLabel SymbolPtr lbl
   = text ".LC_" <> pprCLabel lbl
 pprDynamicLinkerAsmLabel _ _
   = panic "pprDynamicLinkerAsmLabel"
+#elif x86_64_TARGET_ARCH && linux_TARGET_OS
+pprDynamicLinkerAsmLabel CodeStub lbl
+  = pprCLabel lbl <> text "@plt"
+pprDynamicLinkerAsmLabel GotSymbolPtr lbl
+  = pprCLabel lbl <> text "@gotpcrel"
+pprDynamicLinkerAsmLabel GotSymbolOffset lbl
+  = pprCLabel lbl
+pprDynamicLinkerAsmLabel _ _
+  = panic "pprDynamicLinkerAsmLabel"
 #elif linux_TARGET_OS
 pprDynamicLinkerAsmLabel CodeStub lbl
   = pprCLabel lbl <> text "@plt"
index 7103014..a3de41c 100644 (file)
@@ -312,8 +312,12 @@ cmmMachOpFold op [x@(CmmLit _), y]
 -- put arg1 on the left of the rearranged expression, we'll get into a
 -- loop:  (x1+x2)+x3 => x1+(x2+x3)  => (x2+x3)+x1 => x2+(x3+x1) ...
 --
+-- Also don't do it if arg1 is PicBaseReg, so that we don't separate the
+-- PicBaseReg from the corresponding label (or label difference).
+--
 cmmMachOpFold mop1 [CmmMachOp mop2 [arg1,arg2], arg3]
-   | mop1 == mop2 && isAssociativeMachOp mop1 && not (isLit arg1)
+   | mop1 == mop2 && isAssociativeMachOp mop1
+     && not (isLit arg1) && not (isPicReg arg1)
    = cmmMachOpFold mop1 [arg1, cmmMachOpFold mop2 [arg2,arg3]]
 
 -- Make a RegOff if we can
@@ -527,3 +531,6 @@ maybeInvertConditionalExpr :: CmmExpr -> Maybe CmmExpr
 maybeInvertConditionalExpr (CmmMachOp op args) 
   | Just op' <- maybeInvertComparison op = Just (CmmMachOp op' args)
 maybeInvertConditionalExpr _ = Nothing
+
+isPicReg (CmmReg (CmmGlobal PicBaseReg)) = True
+isPicReg _ = False
\ No newline at end of file
index 68c50c8..1a026bd 100644 (file)
@@ -300,7 +300,11 @@ opt_UF_UpdateInPlace               = lookUp  FSLIT("-funfolding-update-in-place")
 
 opt_UF_DearOp   = ( 4 :: Int)
                        
+#if darwin_TARGET_OS && x86_64_TARGET_ARCH
+opt_PIC                         = True
+#else
 opt_PIC                         = lookUp FSLIT("-fPIC")
+#endif
 opt_Static                     = lookUp  FSLIT("-static")
 opt_Unregisterised             = lookUp  FSLIT("-funregisterised")
 
index 875f790..85fb437 100644 (file)
@@ -444,33 +444,33 @@ cmmBlockConFold (BasicBlock id stmts) = do
 cmmStmtConFold stmt
    = case stmt of
         CmmAssign reg src
-           -> do src' <- cmmExprConFold False src
+           -> do src' <- cmmExprConFold DataReference src
                  return $ case src' of
                   CmmReg reg' | reg == reg' -> CmmNop
                   new_src -> CmmAssign reg new_src
 
         CmmStore addr src
-           -> do addr' <- cmmExprConFold False addr
-                 src'  <- cmmExprConFold False src
+           -> do addr' <- cmmExprConFold DataReference addr
+                 src'  <- cmmExprConFold DataReference src
                  return $ CmmStore addr' src'
 
         CmmJump addr regs
-           -> do addr' <- cmmExprConFold True addr
+           -> do addr' <- cmmExprConFold JumpReference addr
                  return $ CmmJump addr' regs
 
        CmmCall target regs args vols
           -> do target' <- case target of
                              CmmForeignCall e conv -> do
-                               e' <- cmmExprConFold True e
+                               e' <- cmmExprConFold CallReference e
                                return $ CmmForeignCall e' conv
                              other -> return other
                  args' <- mapM (\(arg, hint) -> do
-                                  arg' <- cmmExprConFold False arg
+                                  arg' <- cmmExprConFold DataReference arg
                                   return (arg', hint)) args
                 return $ CmmCall target' regs args' vols
 
         CmmCondBranch test dest
-           -> do test' <- cmmExprConFold False test
+           -> do test' <- cmmExprConFold DataReference test
                 return $ case test' of
                   CmmLit (CmmInt 0 _) -> 
                     CmmComment (mkFastString ("deleted: " ++ 
@@ -480,29 +480,29 @@ cmmStmtConFold stmt
                   other -> CmmCondBranch test' dest
 
        CmmSwitch expr ids
-          -> do expr' <- cmmExprConFold False expr
+          -> do expr' <- cmmExprConFold DataReference expr
                 return $ CmmSwitch expr' ids
 
         other
            -> return other
 
 
-cmmExprConFold isJumpTarget expr
+cmmExprConFold referenceKind expr
    = case expr of
         CmmLoad addr rep
-           -> do addr' <- cmmExprConFold False addr
+           -> do addr' <- cmmExprConFold DataReference addr
                  return $ CmmLoad addr' rep
 
         CmmMachOp mop args
            -- For MachOps, we first optimize the children, and then we try 
            -- our hand at some constant-folding.
-           -> do args' <- mapM (cmmExprConFold False) args
+           -> do args' <- mapM (cmmExprConFold DataReference) args
                  return $ cmmMachOpFold mop args'
 
         CmmLit (CmmLabel lbl)
-           -> cmmMakeDynamicReference addImportCmmOpt isJumpTarget lbl
+           -> cmmMakeDynamicReference addImportCmmOpt referenceKind lbl
         CmmLit (CmmLabelOff lbl off)
-           -> do dynRef <- cmmMakeDynamicReference addImportCmmOpt isJumpTarget lbl
+           -> do dynRef <- cmmMakeDynamicReference addImportCmmOpt referenceKind lbl
                  return $ cmmMachOpFold (MO_Add wordRep) [
                      dynRef,
                      (CmmLit $ CmmInt (fromIntegral off) wordRep)
@@ -514,11 +514,11 @@ cmmExprConFold isJumpTarget expr
            -- with the corresponding labels:
         CmmReg (CmmGlobal GCEnter1)
           | not opt_PIC
-          -> cmmExprConFold isJumpTarget $
+          -> cmmExprConFold referenceKind $
              CmmLit (CmmLabel (mkRtsCodeLabel SLIT( "__stg_gc_enter_1"))) 
         CmmReg (CmmGlobal GCFun)
           | not opt_PIC
-          -> cmmExprConFold isJumpTarget $
+          -> cmmExprConFold referenceKind $
              CmmLit (CmmLabel (mkRtsCodeLabel SLIT( "__stg_gc_fun")))
 #endif
 
@@ -533,12 +533,12 @@ cmmExprConFold isJumpTarget expr
                  Left  realreg -> return expr
                  Right baseRegAddr 
                     -> case mid of 
-                          BaseReg -> cmmExprConFold False baseRegAddr
-                          other   -> cmmExprConFold False (CmmLoad baseRegAddr 
-                                                       (globalRegRep mid))
+                          BaseReg -> cmmExprConFold DataReference baseRegAddr
+                          other   -> cmmExprConFold DataReference
+                                        (CmmLoad baseRegAddr (globalRegRep mid))
           -- eliminate zero offsets
        CmmRegOff reg 0
-          -> cmmExprConFold False (CmmReg reg)
+          -> cmmExprConFold referenceKind (CmmReg reg)
 
         CmmRegOff (CmmGlobal mid) offset
            -- RegOf leaves are just a shorthand form. If the reg maps
@@ -547,7 +547,7 @@ cmmExprConFold isJumpTarget expr
            -> case get_GlobalReg_reg_or_addr mid of
                 Left  realreg -> return expr
                 Right baseRegAddr
-                   -> cmmExprConFold False (CmmMachOp (MO_Add wordRep) [
+                   -> cmmExprConFold DataReference (CmmMachOp (MO_Add wordRep) [
                                         CmmReg (CmmGlobal mid),
                                         CmmLit (CmmInt (fromIntegral offset)
                                                        wordRep)])
index 769d17b..85292d8 100644 (file)
@@ -21,7 +21,7 @@ module MachCodeGen ( cmmTopCodeGen, InstrBlock ) where
 import MachInstrs
 import MachRegs
 import NCGMonad
-import PositionIndependentCode ( cmmMakeDynamicReference, initializePicBase )
+import PositionIndependentCode
 import RegAllocInfo ( mkBranchInstr )
 
 -- Our intermediate code:
@@ -486,10 +486,14 @@ getRegisterReg (CmmGlobal mid)
 
 getRegister :: CmmExpr -> NatM Register
 
+#if !x86_64_TARGET_ARCH
+    -- on x86_64, we have %rip for PicBaseReg, but it's not a full-featured
+    -- register, it can only be used for rip-relative addressing.
 getRegister (CmmReg (CmmGlobal PicBaseReg))
   = do
       reg <- getPicBaseNat wordRep
       return (Fixed wordRep reg nilOL)
+#endif
 
 getRegister (CmmReg reg) 
   = return (Fixed (cmmRegRep reg) (getRegisterReg reg) nilOL)
@@ -761,7 +765,7 @@ getRegister leaf
 
 getRegister (CmmLit (CmmFloat f F32)) = do
     lbl <- getNewLabelNat
-    dynRef <- cmmMakeDynamicReference addImportNat False lbl
+    dynRef <- cmmMakeDynamicReference addImportNat DataReference lbl
     Amode addr addr_code <- getAmode dynRef
     let code dst =
            LDATA ReadOnlyData
@@ -784,7 +788,7 @@ getRegister (CmmLit (CmmFloat d F64))
 
   | otherwise = do
     lbl <- getNewLabelNat
-    dynRef <- cmmMakeDynamicReference addImportNat False lbl
+    dynRef <- cmmMakeDynamicReference addImportNat DataReference lbl
     Amode addr addr_code <- getAmode dynRef
     let code dst =
            LDATA ReadOnlyData
@@ -869,6 +873,13 @@ getRegister (CmmMachOp (MO_S_Conv I32 I64) [CmmLoad addr _]) = do
 #endif
 
 #if x86_64_TARGET_ARCH
+getRegister (CmmMachOp (MO_Add I64) [CmmReg (CmmGlobal PicBaseReg),
+                                     CmmLit displacement])
+    = return $ Any I64 (\dst -> unitOL $
+        LEA I64 (OpAddr (ripRel (litToImm displacement))) (OpReg dst))
+#endif
+
+#if x86_64_TARGET_ARCH
 getRegister (CmmMachOp (MO_S_Neg F32) [x]) = do
   x_code <- getAnyReg x
   lbl <- getNewLabelNat
@@ -1683,7 +1694,7 @@ getRegister (CmmLit (CmmInt i rep))
 
 getRegister (CmmLit (CmmFloat f frep)) = do
     lbl <- getNewLabelNat
-    dynRef <- cmmMakeDynamicReference addImportNat False lbl
+    dynRef <- cmmMakeDynamicReference addImportNat DataReference lbl
     Amode addr addr_code <- getAmode dynRef
     let code dst = 
            LDATA ReadOnlyData  [CmmDataLabel lbl,
@@ -1782,6 +1793,14 @@ getAmode other
 
 -- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 
+#if x86_64_TARGET_ARCH
+
+getAmode (CmmMachOp (MO_Add I64) [CmmReg (CmmGlobal PicBaseReg),
+                                     CmmLit displacement])
+    = return $ Amode (ripRel (litToImm displacement)) nilOL
+
+#endif
+
 #if i386_TARGET_ARCH || x86_64_TARGET_ARCH
 
 -- This is all just ridiculous, since it carefully undoes 
@@ -3092,7 +3111,7 @@ outOfLineFloatOp :: CallishMachOp -> CmmReg -> [(CmmExpr,MachHint)]
   -> Maybe [GlobalReg] -> NatM InstrBlock
 outOfLineFloatOp mop res args vols
   = do
-      targetExpr <- cmmMakeDynamicReference addImportNat True lbl
+      targetExpr <- cmmMakeDynamicReference addImportNat CallReference lbl
       let target = CmmForeignCall targetExpr CCallConv
         
       if cmmRegRep res == F64
@@ -3448,7 +3467,7 @@ genCCall target dest_regs argsAndHints vols = do
                          )
 outOfLineFloatOp mop =
     do
-      mopExpr <- cmmMakeDynamicReference addImportNat True $
+      mopExpr <- cmmMakeDynamicReference addImportNat CallReference $
                  mkForeignLabel functionName Nothing True
       let mopLabelOrExpr = case mopExpr of
                        CmmLit (CmmLabel lbl) -> Left lbl
@@ -3699,7 +3718,7 @@ genCCall target dest_regs argsAndHints vols
                           
         outOfLineFloatOp mop =
             do
-                mopExpr <- cmmMakeDynamicReference addImportNat True $
+                mopExpr <- cmmMakeDynamicReference addImportNat CallReference $
                               mkForeignLabel functionName Nothing True
                 let mopLabelOrExpr = case mopExpr of
                         CmmLit (CmmLabel lbl) -> Left lbl
@@ -3759,7 +3778,7 @@ genSwitch expr ids
   = do
         (reg,e_code) <- getSomeReg expr
         lbl <- getNewLabelNat
-        dynRef <- cmmMakeDynamicReference addImportNat False lbl
+        dynRef <- cmmMakeDynamicReference addImportNat DataReference lbl
         (tableReg,t_code) <- getSomeReg $ dynRef
         let
             jumpTable = map jumpTableEntryRel ids
@@ -3773,11 +3792,25 @@ genSwitch expr ids
             op = OpAddr (AddrBaseIndex (EABaseReg tableReg)
                                        (EAIndex reg wORD_SIZE) (ImmInt 0))
 
+#if x86_64_TARGET_ARCH && darwin_TARGET_OS
+    -- on Mac OS X/x86_64, put the jump table in the text section
+    -- to work around a limitation of the linker.
+    -- ld64 is unable to handle the relocations for
+    --     .quad L1 - L0
+    -- if L0 is not preceded by a non-anonymous label in its section.
+    
+            code = e_code `appOL` t_code `appOL` toOL [
+                            ADD wordRep op (OpReg tableReg),
+                            JMP_TBL (OpReg tableReg) [ id | Just id <- ids ],
+                            LDATA Text (CmmDataLabel lbl : jumpTable)
+                    ]
+#else
             code = e_code `appOL` t_code `appOL` toOL [
                             LDATA ReadOnlyData (CmmDataLabel lbl : jumpTable),
                             ADD wordRep op (OpReg tableReg),
                             JMP_TBL (OpReg tableReg) [ id | Just id <- ids ]
                     ]
+#endif
         return code
   | otherwise
   = do
@@ -3799,7 +3832,7 @@ genSwitch expr ids
         (reg,e_code) <- getSomeReg expr
         tmp <- getNewRegNat I32
         lbl <- getNewLabelNat
-        dynRef <- cmmMakeDynamicReference addImportNat False lbl
+        dynRef <- cmmMakeDynamicReference addImportNat DatReference lbl
         (tableReg,t_code) <- getSomeReg $ dynRef
         let
             jumpTable = map jumpTableEntryRel ids
@@ -4638,7 +4671,7 @@ coerceInt2FP fromRep toRep x = do
     lbl <- getNewLabelNat
     itmp <- getNewRegNat I32
     ftmp <- getNewRegNat F64
-    dynRef <- cmmMakeDynamicReference addImportNat False lbl
+    dynRef <- cmmMakeDynamicReference addImportNat DataReference lbl
     Amode addr addr_code <- getAmode dynRef
     let
        code' dst = code `appOL` maybe_exts `appOL` toOL [
index ffd6577..523f305 100644 (file)
@@ -1,5 +1,6 @@
 module PositionIndependentCode (
         cmmMakeDynamicReference,
+        ReferenceKind(..),
         needImportedSymbols,
         pprImportedSymbol,
         pprGotDeclaration,
@@ -83,17 +84,22 @@ import Panic            ( panic )
 -- - addImportCmmOpt for the CmmOptM monad
 -- - addImportNat for the NatM monad.
 
+data ReferenceKind = DataReference
+                   | CallReference
+                   | JumpReference
+                   deriving(Eq)
+
 cmmMakeDynamicReference
   :: Monad m => (CLabel -> m ())  -- a monad & a function
                                   -- used for recording imported symbols
-             -> Bool              -- whether this is the target of a jump
+             -> ReferenceKind     -- whether this is the target of a jump
              -> CLabel            -- the label
              -> m CmmExpr
   
-cmmMakeDynamicReference addImport isJumpTarget lbl
+cmmMakeDynamicReference addImport referenceKind lbl
   | Just _ <- dynamicLinkerLabelInfo lbl
   = return $ CmmLit $ CmmLabel lbl   -- already processed it, pass through
-  | otherwise = case howToAccessLabel isJumpTarget lbl of
+  | otherwise = case howToAccessLabel referenceKind lbl of
         AccessViaStub -> do
               let stub = mkDynamicLinkerLabel CodeStub lbl
               addImport stub
@@ -102,12 +108,13 @@ cmmMakeDynamicReference addImport isJumpTarget lbl
               let symbolPtr = mkDynamicLinkerLabel SymbolPtr lbl
               addImport symbolPtr
               return $ CmmLoad (cmmMakePicReference symbolPtr) wordRep
-        AccessDirectly
-                -- all currently supported processors support
-                -- a PC-relative branch instruction, so just jump there
-          | isJumpTarget -> return $ CmmLit $ CmmLabel lbl
+        AccessDirectly -> case referenceKind of
                 -- for data, we might have to make some calculations:
-          | otherwise    -> return $ cmmMakePicReference lbl  
+              DataReference -> return $ cmmMakePicReference lbl  
+                -- all currently supported processors support
+                -- PC-relative branch and call instructions,
+                -- so just jump there if it's a call or a jump
+              _ -> return $ CmmLit $ CmmLabel lbl
   
 -- -------------------------------------------------------------------
   
@@ -154,7 +161,7 @@ data LabelAccessStyle = AccessViaStub
                       | AccessViaSymbolPtr
                       | AccessDirectly
 
-howToAccessLabel :: Bool -> CLabel -> LabelAccessStyle
+howToAccessLabel :: ReferenceKind -> CLabel -> LabelAccessStyle
 
 #if mingw32_TARGET_OS
 -- Windows
@@ -165,45 +172,60 @@ howToAccessLabel :: Bool -> CLabel -> LabelAccessStyle
 
 howToAccessLabel _ lbl | labelDynamic lbl = AccessViaSymbolPtr
                        | otherwise        = AccessDirectly
-
 #elif darwin_TARGET_OS
 -- Mach-O (Darwin, Mac OS X)
 --
 -- Indirect access is required in the following cases:
 --  * things imported from a dynamic library
---  * things from a different module, if we're generating PIC code
+--  * (not on x86_64) data from a different module, if we're generating PIC code
 -- It is always possible to access something indirectly,
 -- even when it's not necessary.
 
-#if powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH
-    -- on i386 and probably also on x86_64, dyld code stubs don't
-    -- work for tailcalls because the stack alignment is only right
-    -- for regular calls.
-
-howToAccessLabel True lbl
-      -- jumps to a dynamic library go via a symbol stub
-    | labelDynamic lbl = AccessViaStub
-      -- when generating PIC code, all cross-module references must
-      -- must go via a symbol pointer, too.
+howToAccessLabel DataReference lbl
+      -- data access to a dynamic library goes via a symbol pointer
+    | labelDynamic lbl = AccessViaSymbolPtr
+    
+#if !x86_64_TARGET_ARCH
+      -- when generating PIC code, all cross-module data references must
+      -- must go via a symbol pointer, too, because the assembler
+      -- cannot generate code for a label difference where one
+      -- label is undefined. Doesn't apply t x86_64.
       -- Unfortunately, we don't know whether it's cross-module,
       -- so we do it for all externally visible labels.
       -- This is a slight waste of time and space, but otherwise
       -- we'd need to pass the current Module all the way in to
       -- this function.
-    | opt_PIC && externallyVisibleCLabel lbl = AccessViaStub
+    | opt_PIC && externallyVisibleCLabel lbl = AccessViaSymbolPtr
 #endif
+    | otherwise = AccessDirectly
+
+
+#if x86_TARGET_ARCH || x86_64_TARGET_ARCH
+    -- dyld code stubs don't work for tailcalls because the
+    -- stack alignment is only right for regular calls.
+    -- Therefore, we have to go via a symbol pointer:
+howToAccessLabel JumpReference lbl
+    | labelDynamic lbl
+    = AccessViaSymbolPtr
+#endif
+
 howToAccessLabel _ lbl
-      -- data access to a dynamic library goes via a symbol pointer
-    | labelDynamic lbl = AccessViaSymbolPtr
-      -- cross-module PIC references: same as above
-    | opt_PIC && externallyVisibleCLabel lbl = AccessViaSymbolPtr
-howToAccessLabel _ _ = AccessDirectly
+#if !x86_64_TARGET_ARCH
+    -- Code stubs are the usual method of choice for imported code;
+    -- not needed on x86_64 because Apple's new linker, ld64, generates
+    -- them automatically.
+    | labelDynamic lbl
+    = AccessViaStub
+#endif
+    | otherwise
+    = AccessDirectly
+
 
 #elif linux_TARGET_OS && powerpc64_TARGET_ARCH
 -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC
 
-howToAccessLabel True lbl = AccessDirectly -- actually, .label instead of label
-howToAccessLabel _ lbl = AccessViaSymbolPtr
+howToAccessLabel DataReference lbl = AccessViaSymbolPtr
+howToAccessLabel _ lbl = AccessDirectly -- actually, .label instead of label
 
 #elif linux_TARGET_OS
 -- ELF (Linux)
@@ -217,49 +239,47 @@ howToAccessLabel _ lbl = AccessViaSymbolPtr
 -- from position independent code. It is also required from the main program
 -- when dynamic libraries containing Haskell code are used.
 
-howToAccessLabel isJump lbl
+howToAccessLabel _ lbl
        -- no PIC -> the dynamic linker does everything for us;
        --           if we don't dynamically link to Haskell code,
        --           it actually manages to do so without messing thins up.
     | not opt_PIC && opt_Static = AccessDirectly
    
-#if !i386_TARGET_ARCH
--- for Intel, we temporarily disable the use of the
--- Procedure Linkage Table, because PLTs on intel require the
--- address of the GOT to be loaded into register %ebx before
--- a jump through the PLT is made.
--- TODO: make the i386 NCG ensure this before jumping to a
---       CodeStub label, so we can remove this special case.
-
-       -- As long as we're in a shared library ourselves,
-       -- we can use the plt.
-       -- NOTE: We might want to disable this, because this
-       --       prevents -fPIC code from being linked statically.
-    | isJump && labelDynamic lbl && opt_PIC = AccessViaStub
-
-       -- TODO: it would be OK to access non-Haskell code via a stub
---  | isJump && labelDynamic lbl && not isHaskellCode lbl = AccessViaStub
-
-       -- Using code stubs for jumps from the main program to an entry
-       -- label in a dynamic library is deadly; this will cause the dynamic
-       -- linker to replace all references (even data references) to that
-       -- label by references to the stub, so we won't find our info tables
-       -- any more.
-#endif
-
+howToAccessLabel DataReference lbl
        -- A dynamic label needs to be accessed via a symbol pointer.
-       -- NOTE: It would be OK to jump to foreign code via a PLT stub.
     | labelDynamic lbl = AccessViaSymbolPtr
-    
 #if powerpc_TARGET_ARCH
        -- For PowerPC32 -fPIC, we have to access even static data
        -- via a symbol pointer (see below for an explanation why
        -- PowerPC32 Linux is especially broken).
-    | opt_PIC && not isJump = AccessViaSymbolPtr
+    | opt_PIC = AccessViaSymbolPtr
 #endif
-
     | otherwise = AccessDirectly
 
+
+-- In most cases, we have to avoid symbol stubs on ELF, for the following reasons:
+-- * on i386, the position-independent symbol stubs in the Procedure Linkage Table
+--   require the address of the GOT to be loaded into register %ebx on entry.
+-- * The linker will take any reference to the symbol stub as a hint that
+--   the label in question is a code label. When linking executables, this
+--   will cause the linker to replace even data references to the label with
+--   references to the symbol stub.
+
+-- This leaves calling a (foreign) function from non-PIC code
+-- (AccessDirectly, because we get an implicit symbol stub)
+-- and calling functions from PIC code on non-i386 platforms (via a symbol stub) 
+
+howToAccessLabel CallLabel lbl
+    | labelDynamic lbl && not opt_PIC
+    = AccessDirectly
+#if !i386_TARGET_ARCH
+    | labelDynamic lbl && opt_PIC
+    = AccessViaSymbolStub
+#endif
+
+howToAccessLabel _ lbl
+    | labelDynamic lbl = AccessViaSymbolPtr
+    | otherwise = AccessDirectly
 #else
 --
 -- all other platforms
@@ -275,8 +295,8 @@ howToAccessLabel _ _
 -- get the address of a label?
 
 picRelative :: CLabel -> CmmLit
-#if darwin_TARGET_OS
--- Darwin:
+#if darwin_TARGET_OS && !x86_64_TARGET_ARCH
+-- Darwin, but not x86_64:
 -- The PIC base register points to the PIC base label at the beginning
 -- of the current CmmTop. We just have to use a label difference to
 -- get the offset.
@@ -297,10 +317,14 @@ picRelative lbl
 picRelative lbl
   = CmmLabelDiffOff lbl gotLabel 0
 
-#elif linux_TARGET_OS
--- Other Linux versions:
+#elif linux_TARGET_OS || (darwin_TARGET_OS && x86_64_TARGET_ARCH)
+-- Most Linux versions:
 -- The PIC base register points to the GOT. Use foo@got for symbol
 -- pointers, and foo@gotoff for everything else.
+-- Linux and Darwin on x86_64:
+-- The PIC base register is %rip, we use foo@gotpcrel for symbol pointers,
+-- and a GotSymbolOffset label for other things.
+-- For reasons of tradition, the symbol offset label is written as a plain label.
 
 picRelative lbl
   | Just (SymbolPtr, lbl') <- dynamicLinkerLabelInfo lbl
@@ -323,7 +347,7 @@ asmSDoc d = Outputable.withPprStyleDoc (
 pprCLabel_asm l = asmSDoc (pprCLabel l)
 
 
-#if darwin_TARGET_OS
+#if darwin_TARGET_OS && !x86_64_TARGET_ARCH
 
 needImportedSymbols = True
 
index 6ca3bde..f1e0240 100644 (file)
@@ -37,8 +37,6 @@ import Pretty
 import FastString
 import qualified Outputable
 
-import StaticFlags      ( opt_PIC, opt_Static )
-
 import Data.Array.ST
 import Data.Word       ( Word8 )
 import Control.Monad.ST
@@ -618,7 +616,8 @@ pprSectionHeader Text
        ,IF_ARCH_i386(IF_OS_darwin(SLIT(".text\n\t.align 2"),
                                   SLIT(".text\n\t.align 4,0x90"))
                                   {-needs per-OS variation!-}
-       ,IF_ARCH_x86_64(SLIT(".text\n\t.align 8") {-needs per-OS variation!-}
+       ,IF_ARCH_x86_64(IF_OS_darwin(SLIT(".text\n.align 3"),
+                                    SLIT(".text\n\t.align 8"))
        ,IF_ARCH_powerpc(SLIT(".text\n.align 2")
        ,)))))
 pprSectionHeader Data
@@ -627,7 +626,8 @@ pprSectionHeader Data
        ,IF_ARCH_sparc(SLIT(".data\n\t.align 8") {-<8 will break double constants -}
        ,IF_ARCH_i386(IF_OS_darwin(SLIT(".data\n\t.align 2"),
                                    SLIT(".data\n\t.align 4"))
-       ,IF_ARCH_x86_64(SLIT(".data\n\t.align 8")
+       ,IF_ARCH_x86_64(IF_OS_darwin(SLIT(".data\n.align 3"),
+                                    SLIT(".data\n\t.align 8"))
         ,IF_ARCH_powerpc(SLIT(".data\n.align 2")
        ,)))))
 pprSectionHeader ReadOnlyData
@@ -636,7 +636,8 @@ pprSectionHeader ReadOnlyData
        ,IF_ARCH_sparc(SLIT(".data\n\t.align 8") {-<8 will break double constants -}
        ,IF_ARCH_i386(IF_OS_darwin(SLIT(".const\n.align 2"),
                                    SLIT(".section .rodata\n\t.align 4"))
-       ,IF_ARCH_x86_64(SLIT(".section .rodata\n\t.align 8")
+       ,IF_ARCH_x86_64(IF_OS_darwin(SLIT(".const\n.align 3"),
+                                    SLIT(".section .rodata\n\t.align 8"))
         ,IF_ARCH_powerpc(IF_OS_darwin(SLIT(".const\n.align 2"),
                                       SLIT(".section .rodata\n\t.align 2"))
        ,)))))
@@ -646,7 +647,8 @@ pprSectionHeader RelocatableReadOnlyData
        ,IF_ARCH_sparc(SLIT(".data\n\t.align 8") {-<8 will break double constants -}
        ,IF_ARCH_i386(IF_OS_darwin(SLIT(".const_data\n.align 2"),
                                    SLIT(".section .rodata\n\t.align 4"))
-       ,IF_ARCH_x86_64(SLIT(".section .rodata\n\t.align 8")
+       ,IF_ARCH_x86_64(IF_OS_darwin(SLIT(".const_data\n.align 3"),
+                                     SLIT(".section .rodata\n\t.align 8"))
         ,IF_ARCH_powerpc(IF_OS_darwin(SLIT(".const_data\n.align 2"),
                                       SLIT(".data\n\t.align 2"))
        ,)))))
@@ -654,9 +656,10 @@ pprSectionHeader UninitialisedData
     = ptext
         IF_ARCH_alpha(SLIT("\t.bss\n\t.align 3")
        ,IF_ARCH_sparc(SLIT(".bss\n\t.align 8") {-<8 will break double constants -}
-       ,IF_ARCH_i386(IF_OS_darwin(SLIT(".const_data\n\t.align 2"),
+       ,IF_ARCH_i386(IF_OS_darwin(SLIT(".data\n\t.align 2"),
                                    SLIT(".section .bss\n\t.align 4"))
-       ,IF_ARCH_x86_64(SLIT(".section .bss\n\t.align 8")
+       ,IF_ARCH_x86_64(IF_OS_darwin(SLIT(".data\n\t.align 3"),
+                                     SLIT(".section .bss\n\t.align 8"))
         ,IF_ARCH_powerpc(IF_OS_darwin(SLIT(".const_data\n.align 2"),
                                       SLIT(".section .bss\n\t.align 2"))
        ,)))))
@@ -666,7 +669,8 @@ pprSectionHeader ReadOnlyData16
        ,IF_ARCH_sparc(SLIT(".data\n\t.align 16")
        ,IF_ARCH_i386(IF_OS_darwin(SLIT(".const\n.align 4"),
                                    SLIT(".section .rodata\n\t.align 16"))
-       ,IF_ARCH_x86_64(SLIT(".section .rodata.cst16\n\t.align 16")
+       ,IF_ARCH_x86_64(IF_OS_darwin(SLIT(".const\n.align 4"),
+                                    SLIT(".section .rodata.cst16\n\t.align 16"))
         ,IF_ARCH_powerpc(IF_OS_darwin(SLIT(".const\n.align 4"),
                                       SLIT(".section .rodata\n\t.align 4"))
        ,)))))
@@ -701,7 +705,7 @@ pprASCII str
 pprAlign bytes =
        IF_ARCH_alpha(ptextSLIT(".align ") <> int pow2,
        IF_ARCH_i386(ptext SLIT(".align ") <> int IF_OS_darwin(pow2,bytes),
-       IF_ARCH_x86_64(ptext SLIT(".align ") <> int bytes,
+       IF_ARCH_x86_64(ptext SLIT(".align ") <> int IF_OS_darwin(pow2,bytes),
        IF_ARCH_sparc(ptext SLIT(".align ") <> int bytes,
        IF_ARCH_powerpc(ptext SLIT(".align ") <> int pow2,)))))
   where
@@ -747,10 +751,10 @@ pprDataItem lit
                     <> int (fromIntegral
                         (fromIntegral (x `shiftR` 32) :: Word32))]
 #endif
-#if i386_TARGET_ARCH
+#if i386_TARGET_ARCH || (darwin_TARGET_OS && x86_64_TARGET_ARCH)
        ppr_item I64  x = [ptext SLIT("\t.quad\t") <> pprImm imm]
 #endif
-#if x86_64_TARGET_ARCH
+#if x86_64_TARGET_ARCH && !darwin_TARGET_OS
        -- x86_64: binutils can't handle the R_X86_64_PC64 relocation
        -- type, which means we can't do pc-relative 64-bit addresses.
        -- Fortunately we're assuming the small memory model, in which
index 27a0966..72bb437 100644 (file)
@@ -277,6 +277,9 @@ DYLD_LIBRARY = $(patsubst %.a,%_dyn.dylib,$(LIBRARY))
     #   Without these options, we'd have to specify the correct dependencies
     #   for each of the dylibs. Twolevel namespaces are in general a good thing
     #   (they make things more robust), so we should fix this sooner or later.
+    # -undefined dynamic_lookup:
+    #   Another way to avoid having to specify the correct dependencies, but
+    #   this time, we don't allow overriding symbols.
     # -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.
@@ -287,7 +290,7 @@ DYLD_LIBRARY = $(patsubst %.a,%_dyn.dylib,$(LIBRARY))
     #         library dir. -- Wolfgang
 
 $(DYLD_LIBRARY) : $(LIBOBJS) $(STUBOBJS)
-       $(CC) -dynamiclib -o $@ $(STUBOBJS) $(LIBOBJS) -flat_namespace -undefined suppress -install_name `pwd`/$@
+       $(CC) -dynamiclib -o $@ $(STUBOBJS) $(LIBOBJS) -undefined dynamic_lookup -install_name `pwd`/$@
 else
 DYLD_LIBRARY = $(patsubst %.a,%_dyn.so,$(LIBRARY))