remove empty dir
[ghc-hetmet.git] / ghc / compiler / nativeGen / PositionIndependentCode.hs
index 5e7d43b..0daccb6 100644 (file)
@@ -1,5 +1,3 @@
-#include "../includes/ghcconfig.h"
-
 module PositionIndependentCode (
         cmmMakeDynamicReference,
         needImportedSymbols,
@@ -20,7 +18,7 @@ module PositionIndependentCode (
         CodeStub, SymbolPtr, GotSymbolPtr, GotSymbolOffset
     - labelDynamic predicate
   + module Cmm
-    - The CmmExpr datatype has a CmmPicBaseReg constructor
+    - The GlobalReg datatype has a PicBaseReg constructor
     - The CmmLit datatype has a CmmLabelDiffOff constructor
   + codeGen & RTS
     - When tablesNextToCode, no absolute addresses are stored in info tables
@@ -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, opt_Static )
+import StaticFlags     ( opt_PIC, opt_Static )
 
 import Pretty
 import qualified Outputable
@@ -127,7 +125,7 @@ cmmMakePicReference :: CLabel -> CmmExpr
 
 cmmMakePicReference lbl
     | opt_PIC && absoluteLabel lbl = CmmMachOp (MO_Add wordRep) [
-            CmmPicBaseReg,
+            CmmReg (CmmGlobal PicBaseReg),
             CmmLit $ picRelative lbl
         ]
     where
@@ -172,8 +170,8 @@ howToAccessLabel _ lbl | labelDynamic lbl = AccessViaSymbolPtr
 -- 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
+--  * things imported from a dynamic library
+--  * things from a different module, if we're generating PIC code
 -- It is always possible to access something indirectly,
 -- even when it's not necessary.
 
@@ -323,12 +321,29 @@ pprCLabel_asm l = asmSDoc (pprCLabel l)
 
 needImportedSymbols = True
 
--- We don't need to declare any offset tables
+-- We don't need to declare any offset tables.
+-- However, for PIC on x86, we need a small helper function.
+#if i386_TARGET_ARCH
+pprGotDeclaration
+    | opt_PIC
+    = vcat [
+        ptext SLIT(".section __TEXT,__textcoal_nt,coalesced,no_toc"),
+        ptext SLIT(".weak_definition ___i686.get_pc_thunk.ax"),
+        ptext SLIT(".private_extern ___i686.get_pc_thunk.ax"),
+        ptext SLIT("___i686.get_pc_thunk.ax:"),
+            ptext SLIT("\tmovl (%esp), %eax"),
+            ptext SLIT("\tret")
+    ]
+    | otherwise = Pretty.empty
+#else
 pprGotDeclaration = Pretty.empty
+#endif
 
 -- On Darwin, we have to generate our own stub code for lazy binding..
--- There are two versions, one for PIC and one for non-PIC.
+-- For each processor architecture, there are two versions, one for PIC
+-- and one for non-PIC.
 pprImportedSymbol importedLbl
+#if powerpc_TARGET_ARCH
     | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
     = case opt_PIC of
         False ->
@@ -371,7 +386,49 @@ pprImportedSymbol importedLbl
             ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
             ptext SLIT("\t.long dyld_stub_binding_helper")
     ]
-
+#elif i386_TARGET_ARCH
+    | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
+    = case opt_PIC of
+        False ->
+            vcat [
+                ptext SLIT(".symbol_stub"),
+                ptext SLIT("L") <> pprCLabel_asm lbl <> ptext SLIT("$stub:"),
+                    ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
+                    ptext SLIT("\tjmp *L") <> pprCLabel_asm lbl
+                        <> ptext SLIT("$lazy_ptr"),
+                ptext SLIT("L") <> pprCLabel_asm lbl
+                    <> ptext SLIT("$stub_binder:"),
+                    ptext SLIT("\tpushl $L") <> pprCLabel_asm lbl
+                        <> ptext SLIT("$lazy_ptr"),
+                    ptext SLIT("\tjmp dyld_stub_binding_helper")
+            ]
+        True ->
+            vcat [
+                ptext SLIT(".section __TEXT,__picsymbolstub2,")
+                    <> ptext SLIT("symbol_stubs,pure_instructions,25"),
+                ptext SLIT("L") <> pprCLabel_asm lbl <> ptext SLIT("$stub:"),
+                    ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
+                    ptext SLIT("\tcall ___i686.get_pc_thunk.ax"),
+                ptext SLIT("1:"),
+                    ptext SLIT("\tmovl L") <> pprCLabel_asm lbl
+                        <> ptext SLIT("$lazy_ptr-1b(%eax),%edx"),
+                    ptext SLIT("\tjmp %edx"),
+                ptext SLIT("L") <> pprCLabel_asm lbl
+                    <> ptext SLIT("$stub_binder:"),
+                    ptext SLIT("\tlea L") <> pprCLabel_asm lbl
+                        <> ptext SLIT("$lazy_ptr-1b(%eax),%eax"),
+                    ptext SLIT("\tpushl %eax"),
+                    ptext SLIT("\tjmp dyld_stub_binding_helper")
+            ]
+    $+$ vcat [        ptext SLIT(".section __DATA, __la_sym_ptr")
+                    <> (if opt_PIC then int 2 else int 3)
+                    <> ptext SLIT(",lazy_symbol_pointers"),
+        ptext SLIT("L") <> pprCLabel_asm lbl <> ptext SLIT("$lazy_ptr:"),
+            ptext SLIT("\t.indirect_symbol") <+> pprCLabel_asm lbl,
+            ptext SLIT("\t.long L") <> pprCLabel_asm lbl
+                    <> ptext SLIT("$stub_binder")
+    ]
+#endif
 -- We also have to declare our symbol pointers ourselves:
     | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl
     = vcat [
@@ -383,41 +440,66 @@ pprImportedSymbol importedLbl
 
     | otherwise = empty
 
-#elif powerpc_TARGET_ARCH && linux_TARGET_OS
+#elif linux_TARGET_OS && !powerpc64_TARGET_ARCH
 
--- PowerPC Linux
+-- ELF / 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.
-
--- We need to do this whenever we explicitly access something via
--- a symbol pointer.
+-- 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
 
--- If we're generating PIC, we need to create our own "fake GOT".
-
+-- 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 [
@@ -452,9 +534,21 @@ pprImportedSymbol _ = empty
 
 initializePicBase :: Reg -> [NatCmmTop] -> NatM [NatCmmTop]
 
-#if powerpc_TARGET_ARCH && darwin_TARGET_OS
+#if darwin_TARGET_OS
 
 -- Darwin is simple: just fetch the address of a local label.
+-- The FETCHPC pseudo-instruction is expanded to multiple instructions
+-- during pretty-printing so that we don't have to deal with the
+-- local label:
+
+-- PowerPC version:
+--          bcl 20,31,1f.
+--      1:  mflr picReg
+
+-- i386 version:
+--          call 1f
+--      1:  popl %picReg
+
 initializePicBase picReg (CmmProc info lab params blocks : statics)
     = return (CmmProc info lab params (b':tail blocks) : statics)
     where BasicBlock bID insns = head blocks
@@ -490,23 +584,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)
 
--- mingw32_TARGET_OS: not needed, won't be called
+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)
 
--- i386_TARGET_ARCH && darwin_TARGET_OS:
--- (just for completeness ;-)
---              call 1f
--- 1:           popl %picReg
+#else
+initializePicBase picReg proc = panic "initializePicBase"
+
+-- mingw32_TARGET_OS: not needed, won't be called
 #endif