[project @ 2005-01-28 12:55:17 by simonmar]
[ghc-hetmet.git] / ghc / compiler / nativeGen / PositionIndependentCode.hs
index a6a7b27..936b76a 100644 (file)
@@ -1,5 +1,3 @@
-#include "../includes/ghcconfig.h"
-
 module PositionIndependentCode (
         cmmMakeDynamicReference,
         needImportedSymbols,
@@ -55,7 +53,7 @@ import CLabel           ( CLabel, pprCLabel,
                           dynamicLinkerLabelInfo, mkPicBaseLabel,
                           labelDynamic, externallyVisibleCLabel )
 
-#if powerpc_TARGET_ARCH && linux_TARGET_OS
+#if linux_TARGET_OS
 import CLabel           ( mkForeignLabel )
 #endif
 
@@ -63,7 +61,7 @@ import MachRegs
 import MachInstrs
 import NCGMonad         ( NatM, getNewRegNat, getNewLabelNat )
 
-import CmdLineOpts      ( opt_PIC )
+import CmdLineOpts      ( opt_PIC, opt_Static )
 
 import Pretty
 import qualified Outputable
@@ -195,46 +193,30 @@ howToAccessLabel False lbl
     | opt_PIC && externallyVisibleCLabel lbl = AccessViaSymbolPtr
 howToAccessLabel _ _ = AccessDirectly
 
-#elif linux_TARGET_OS && powerpc_TARGET_ARCH
--- PowerPC Linux
---
--- PowerPC Linux is just plain broken.
--- While it's theoretically possible to use GOT offsets larger
--- than 16 bit, the standard crt*.o files don't, which leads to
--- linker errors as soon as the GOT size exceeds 16 bit.
--- Also, the assembler doesn't support @gotoff labels.
--- In order to be able to use a larger GOT, we circumvent the
--- entire GOT mechanism and do it ourselves (this is what GCC does).
-
--- In this scheme, we need to do _all data references_ (even refs
--- to static data) via a SymbolPtr when we are generating PIC.
--- Luckily, the PLT works as expected, so we can simply access
--- dynamically linked code via the PLT.
-
-howToAccessLabel _ _ | not opt_PIC = AccessDirectly
-howToAccessLabel True lbl
-    = if labelDynamic lbl then AccessViaStub
-                          else AccessDirectly
-howToAccessLabel False lbl
-    = AccessViaSymbolPtr
+#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
 
 #elif linux_TARGET_OS
 -- ELF (Linux)
 --
+-- ELF tries to pretend to the main application code that dynamic linking does 
+-- not exist. While this may sound convenient, it tends to mess things up in
+-- very bad ways, so we have to be careful when we generate code for the main
+-- program (-dynamic but no -fPIC).
+--
 -- Indirect access is required for references to imported symbols
--- from position independent code.
--- It is always possible to access something indirectly,
--- even when it's not necessary.
-
--- For code, we can use a relative jump to a piece of
--- stub code instead (this allows lazy binding of imported symbols).
+-- from position independent code. It is also required from the main program
+-- when dynamic libraries containing Haskell code are used.
 
 howToAccessLabel isJump lbl
-        -- no PIC -> the dynamic linker does everything for us
-   | not opt_PIC = AccessDirectly
-        -- if it's not imported, we need no indirection
-        -- ("foo" will end up being accessed as "foo@GOTOFF")
-   | not (labelDynamic lbl) = AccessDirectly
+       -- 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
@@ -242,9 +224,35 @@ howToAccessLabel isJump lbl
 -- 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.
-   | isJump = AccessViaStub
+
+       -- 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
-   | otherwise = AccessViaSymbolPtr
+
+       -- 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
+#endif
+
+    | otherwise = AccessDirectly
 
 #else
 --
@@ -373,27 +381,66 @@ pprImportedSymbol importedLbl
 
     | otherwise = empty
 
-#elif powerpc_TARGET_ARCH && linux_TARGET_OS
-
--- For PowerPC linux, we don't do anything unless we're generating PIC.
-needImportedSymbols = opt_PIC
+#elif linux_TARGET_OS && !powerpc32_TARGET_ARCH
 
--- If we're generating PIC, we need to create our own "fake GOT".
+-- ELF / Linux
+--
+-- In theory, we don't need to generate any stubs or symbol pointers
+-- by hand for Linux.
+--
+-- Reality differs from this in two areas.
+--
+-- 1) If we just use a dynamically imported symbol directly in a read-only
+--    section of the main executable (as GCC does), ld generates R_*_COPY
+--    relocations, which are fundamentally incompatible with reversed info
+--    tables. Therefore, we need a table of imported addresses in a writable
+--    section.
+--    The "official" GOT mechanism (label@got) isn't intended to be used
+--    in position dependent code, so we have to create our own "fake GOT"
+--    when not opt_PCI && not opt_Static.
+--
+-- 2) PowerPC Linux is just plain broken.
+--    While it's theoretically possible to use GOT offsets larger
+--    than 16 bit, the standard crt*.o files don't, which leads to
+--    linker errors as soon as the GOT size exceeds 16 bit.
+--    Also, the assembler doesn't support @gotoff labels.
+--    In order to be able to use a larger GOT, we have to circumvent the
+--    entire GOT mechanism and do it ourselves (this is also what GCC does).
+
+
+-- When needImportedSymbols is defined,
+-- the NCG will keep track of all DynamicLinkerLabels it uses
+-- and output each of them using pprImportedSymbol.
+#if powerpc_TARGET_ARCH
+    -- PowerPC Linux: -fPIC or -dynamic
+needImportedSymbols = opt_PIC || not opt_Static
+#else
+    -- i386 (and others?): -dynamic but not -fPIC
+needImportedSymbols = not opt_Static && not opt_PIC
+#endif
 
+-- gotLabel
+-- The label used to refer to our "fake GOT" from
+-- position-independent code.
 gotLabel = mkForeignLabel -- HACK: it's not really foreign
                            FSLIT(".LCTOC1") Nothing False
 
+-- pprGotDeclaration
+-- Output whatever needs to be output once per .s file.
 -- The .LCTOC1 label is defined to point 32768 bytes into the table,
 -- to make the most of the PPC's 16-bit displacements.
+-- Only needed for PIC.
 
-pprGotDeclaration = vcat [
+pprGotDeclaration
+    | not opt_PIC = Pretty.empty
+    | otherwise = vcat [
         ptext SLIT(".section \".got2\",\"aw\""),
         ptext SLIT(".LCTOC1 = .+32768")
     ]
 
 -- We generate one .long literal for every symbol we import;
 -- the dynamic linker will relocate those addresses.
-    
+
 pprImportedSymbol importedLbl
     | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
     = vcat [
@@ -466,18 +513,22 @@ initializePicBase picReg
                                : ADD picReg picReg (RIReg tmp)
                                : insns)
         return (CmmProc info lab params (b' : tail blocks) : gotOffset : statics)
-#else
-initializePicBase picReg proc = panic "initializePicBase"
+#elif i386_TARGET_ARCH && linux_TARGET_OS
 
--- TODO:
--- i386_TARGET_ARCH && linux_TARGET_OS:
--- generate something like:
+-- We cheat a bit here by defining a pseudo-instruction named FETCHGOT
+-- which pretty-prints as:
 --              call 1f
 -- 1:           popl %picReg
 --              addl __GLOBAL_OFFSET_TABLE__+.-1b, %picReg
--- It might be a good idea to use a FETCHPC pseudo-instruction (like for PowerPC)
--- in order to avoid having to create a new basic block.
--- ((FETCHPC reg) should pretty-print as call 1f; 1: popl reg)
+-- (See PprMach.lhs)
+
+initializePicBase picReg (CmmProc info lab params blocks : statics)
+    = return (CmmProc info lab params (b':tail blocks) : statics)
+    where BasicBlock bID insns = head blocks
+          b' = BasicBlock bID (FETCHGOT picReg : insns)
+
+#else
+initializePicBase picReg proc = panic "initializePicBase"
 
 -- mingw32_TARGET_OS: not needed, won't be called