[project @ 2005-01-16 05:31:39 by wolfgang]
authorwolfgang <unknown>
Sun, 16 Jan 2005 05:31:45 +0000 (05:31 +0000)
committerwolfgang <unknown>
Sun, 16 Jan 2005 05:31:45 +0000 (05:31 +0000)
A first stab at position independent code generation for i386-linux.
It doesn't work yet, but it shouldn't break anything.

What we need now is one or both of the following:
a) A volunteer to implement PIC for x86 -fvia-C
    (I definitely refuse to touch any piece of code that contains
     both Perl and x86 assembly).
b) A volunteer to improve the NCG to the point where it can compile
   the RTS (so we won't need point a).

ghc/compiler/cmm/CLabel.hs
ghc/compiler/nativeGen/AsmCodeGen.lhs
ghc/compiler/nativeGen/MachInstrs.hs
ghc/compiler/nativeGen/PositionIndependentCode.hs
ghc/compiler/nativeGen/PprMach.hs
ghc/compiler/nativeGen/RegAllocInfo.hs

index 8a5f133..6f95be9 100644 (file)
@@ -796,6 +796,8 @@ pprDynamicLinkerAsmLabel GotSymbolPtr lbl
   = pprCLabel lbl <> text "@got"
 pprDynamicLinkerAsmLabel GotSymbolOffset lbl
   = pprCLabel lbl <> text "@gotoff"
+pprDynamicLinkerAsmLabel SymbolPtr lbl
+  = text ".LC_" <> pprCLabel lbl
 #elif mingw32_TARGET_OS
 pprDynamicLinkerAsmLabel SymbolPtr lbl
   = text "__imp_" <> pprCLabel lbl
index 95a5b6c..b8fd0e3 100644 (file)
@@ -33,10 +33,8 @@ import UniqFM
 import Unique          ( Unique, getUnique )
 import UniqSupply
 import FastTypes
-#if darwin_TARGET_OS || (powerpc_TARGET_ARCH && linux_TARGET_OS)
 import List            ( groupBy, sortBy )
 import CLabel           ( pprCLabel )
-#endif
 import ErrUtils                ( dumpIfSet_dyn )
 import CmdLineOpts     ( DynFlags, DynFlag(..), dopt, opt_Static,
                          opt_EnsureSplittableC, opt_PIC )
@@ -133,7 +131,6 @@ nativeCodeGen dflags cmms us
 
     split_marker = CmmProc [] mkSplitMarkerLabel [] []
 
-#if darwin_TARGET_OS || (powerpc_TARGET_ARCH && linux_TARGET_OS)
         -- Generate "symbol stubs" for all external symbols that might
         -- come from a dynamic library.
 {-    dyld_stubs imps = Pretty.vcat $ map pprDyldSymbolStub $
@@ -155,9 +152,6 @@ nativeCodeGen dflags cmms us
         
         where doPpr lbl = (lbl, Pretty.render $ pprCLabel lbl astyle)
               astyle = mkCodeStyle AsmStyle
-#else
-    dyld_stubs imps = Pretty.empty
-#endif
 
 #ifndef NCG_DEBUG
     my_vcat sds = Pretty.vcat sds
index 4cfcc17..e48e1a9 100644 (file)
@@ -465,6 +465,12 @@ bit or 64 bit precision.
 -- Other things.
        | CLTD -- sign extend %eax into %edx:%eax
 
+       | FETCHGOT    Reg  -- pseudo-insn for position-independent code
+                           -- pretty-prints as
+                           --       call 1f
+                           -- 1:    popl %reg
+                           --       addl __GLOBAL_OFFSET_TABLE__+.-1b, %reg
+                    
 data Operand
   = OpReg  Reg         -- register
   | OpImm  Imm         -- immediate value
index 5e7d43b..a58d6ca 100644 (file)
@@ -55,7 +55,7 @@ import CLabel           ( CLabel, pprCLabel,
                           dynamicLinkerLabelInfo, mkPicBaseLabel,
                           labelDynamic, externallyVisibleCLabel )
 
-#if powerpc_TARGET_ARCH && linux_TARGET_OS
+#if linux_TARGET_OS
 import CLabel           ( mkForeignLabel )
 #endif
 
@@ -383,41 +383,66 @@ pprImportedSymbol importedLbl
 
     | otherwise = empty
 
-#elif powerpc_TARGET_ARCH && linux_TARGET_OS
+#elif linux_TARGET_OS && !powerpc32_TARGET_ARCH
 
--- PowerPC Linux
+-- 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.
 --
--- 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.
+-- 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 [
@@ -490,18 +515,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
 
index a807cc2..b1547f1 100644 (file)
@@ -1335,6 +1335,12 @@ pprInstr GFREE
             ptext SLIT("\tffree %st(4) ;ffree %st(5) ;ffree %st(6) ;ffree %st(7)") 
           ]
 
+pprInstr (FETCHGOT reg)
+   = vcat [ ptext SLIT("\tcall 1f"),
+            hcat [ ptext SLIT("1:\tpopl\t"), pprReg I32 reg ],
+            hcat [ ptext SLIT("\taddl\t$_GLOBAL_OFFSET_TABLE_+(.-1b), "),
+                   pprReg I32 reg ]
+          ]
 
 -- Emit code to make hi_reg:lo_reg be the 64-bit product of hi_reg and lo_reg
 pprInstr_imul64 hi_reg lo_reg
index c1c259a..7d1bf48 100644 (file)
@@ -202,6 +202,8 @@ regUsage instr = case instr of
     GCOS   sz src dst  -> mkRU [src] [dst]
     GTAN   sz src dst  -> mkRU [src] [dst]
 
+    FETCHGOT reg        -> mkRU [] [reg]
+
     COMMENT _          -> noUsage
     DELTA   _           -> noUsage
 
@@ -503,7 +505,9 @@ patchRegs instr env = case instr of
 
     CALL (Left imm)    -> instr
     CALL (Right reg)   -> CALL (Right (env reg))
-
+    
+    FETCHGOT reg        -> FETCHGOT (env reg)
+    
     NOP                        -> instr
     COMMENT _          -> instr
     DELTA _            -> instr