[commit: ghc] master: Revert "codeGen: Remove binutils<2.17 hack, fixes T11758" (b2c5e4c)

git at git.haskell.org git at git.haskell.org
Fri Aug 19 08:01:28 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b2c5e4ce5c44a7be7c2b81c2600cae40c5b225ad/ghc

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

commit b2c5e4ce5c44a7be7c2b81c2600cae40c5b225ad
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Aug 18 18:16:01 2016 +0100

    Revert "codeGen: Remove binutils<2.17 hack, fixes T11758"
    
    This reverts commit e3e2e49a8f6952e1c8a19321c729c17b294d8c92.
    
    I'm reverting because it makes ghc-stage2 seg-fault on
    64-bit Windows machines.  Even ghc-stage2 --version seg-faults.


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

b2c5e4ce5c44a7be7c2b81c2600cae40c5b225ad
 compiler/nativeGen/X86/CodeGen.hs | 15 ++++++++++++++-
 compiler/nativeGen/X86/Ppr.hs     | 23 +++++++++++++++++++++--
 includes/rts/storage/InfoTables.h | 11 +++++++++++
 3 files changed, 46 insertions(+), 3 deletions(-)

diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index 2bfcd9a..cd45d92 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -2624,10 +2624,23 @@ genSwitch dflags expr targets
         let op = OpAddr (AddrBaseIndex (EABaseReg tableReg)
                                        (EAIndex reg (wORD_SIZE dflags)) (ImmInt 0))
 
-        return $ e_code `appOL` t_code `appOL` toOL [
+        return $ if is32bit || os == OSDarwin
+                 then e_code `appOL` t_code `appOL` toOL [
                                 ADD (intFormat (wordWidth dflags)) op (OpReg tableReg),
                                 JMP_TBL (OpReg tableReg) ids rosection lbl
                        ]
+                 else -- HACK: On x86_64 binutils<2.17 is only able to generate
+                      -- PC32 relocations, hence we only get 32-bit offsets in
+                      -- the jump table. As these offsets are always negative
+                      -- we need to properly sign extend them to 64-bit. This
+                      -- hack should be removed in conjunction with the hack in
+                      -- PprMach.hs/pprDataItem once binutils 2.17 is standard.
+                      e_code `appOL` t_code `appOL` toOL [
+                               MOVSxL II32 op (OpReg reg),
+                               ADD (intFormat (wordWidth dflags)) (OpReg reg)
+                                   (OpReg tableReg),
+                               JMP_TBL (OpReg tableReg) ids rosection lbl
+                       ]
   | otherwise
   = do
         (reg,e_code) <- getSomeReg (cmmOffset dflags expr offset)
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index 090ff53..7809ae1 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -454,8 +454,27 @@ pprDataItem' dflags lit
                   _ -> panic "X86.Ppr.ppr_item: no match for II64"
                | otherwise ->
                   [text "\t.quad\t" <> pprImm imm]
-
-              _ -> [text "\t.quad\t" <> pprImm imm]
+              _
+               | target32Bit platform ->
+                  [text "\t.quad\t" <> pprImm imm]
+               | otherwise ->
+                  -- 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 all such
+                  -- offsets will fit into 32 bits, so we have to stick
+                  -- to 32-bit offset fields and modify the RTS
+                  -- appropriately
+                  --
+                  -- See Note [x86-64-relative] in includes/rts/storage/InfoTables.h
+                  --
+                  case lit of
+                  -- A relative relocation:
+                  CmmLabelDiffOff _ _ _ ->
+                      [text "\t.long\t" <> pprImm imm,
+                       text "\t.long\t0"]
+                  _ ->
+                      [text "\t.quad\t" <> pprImm imm]
 
         ppr_item _ _
                 = panic "X86.Ppr.ppr_item: no match"
diff --git a/includes/rts/storage/InfoTables.h b/includes/rts/storage/InfoTables.h
index e6bd15c..fb14ac5 100644
--- a/includes/rts/storage/InfoTables.h
+++ b/includes/rts/storage/InfoTables.h
@@ -15,6 +15,17 @@
    Several pointer fields in info tables are expressed as offsets
    relative to the info pointer, so that we can generate
    position-independent code.
+
+   Note [x86-64-relative]
+   There is a complication on the x86_64 platform, where pointers are
+   64 bits, but the tools don't support 64-bit relative relocations.
+   However, the default memory model (small) ensures that all symbols
+   have values in the lower 2Gb of the address space, so offsets all
+   fit in 32 bits.  Hence we can use 32-bit offset fields.
+
+   Somewhere between binutils-2.16.1 and binutils-2.16.91.0.6,
+   support for 64-bit PC-relative relocations was added, so maybe this
+   hackery can go away sometime.
    ------------------------------------------------------------------------- */
 
 #if x86_64_TARGET_ARCH



More information about the ghc-commits mailing list