[commit: ghc] master: PPC NCG: Fix and refactor TOC handling. (f4b0488)

git at git.haskell.org git at git.haskell.org
Sat Jun 18 22:23:25 UTC 2016


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

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

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

commit f4b0488dba4c97630ed1e4417eef546abd5c3df5
Author: Peter Trommler <ptrommler at acm.org>
Date:   Sat Jun 18 12:29:12 2016 +0200

    PPC NCG: Fix and refactor TOC handling.
    
    In a call to a fixed function the TOC does not need to be saved.
    The linker handles TOC saving.
    
    Refactor TOC handling by folding the two functions toc_before and
    toc_after into the code generating the call sequence. This saves
    repeating the case distinction in those two functions.
    
    Test Plan: validate on PowerPC 32-bit Linux and AIX
    
    Reviewers: hvr, simonmar, austin, erikd, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2328


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

f4b0488dba4c97630ed1e4417eef546abd5c3df5
 compiler/nativeGen/PPC/CodeGen.hs | 56 +++++++++++++++++++--------------------
 1 file changed, 28 insertions(+), 28 deletions(-)

diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index 86903e4..1b719fc 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -1150,7 +1150,13 @@ genCCall'
 
     PowerPC 64 Linux uses the System V Release 4 Calling Convention for
     64-bit PowerPC. It is specified in
-    "64-bit PowerPC ELF Application Binary Interface Supplement 1.9".
+    "64-bit PowerPC ELF Application Binary Interface Supplement 1.9"
+    (PPC64 ELF v1.9).
+    PowerPC 64 Linux in little endian mode uses the "Power Architecture 64-Bit
+    ELF V2 ABI Specification -- OpenPOWER ABI for Linux Supplement"
+    (PPC64 ELF v2).
+    AIX follows the "PowerOpen ABI: Application Binary Interface Big-Endian
+    32-Bit Hardware Implementation"
 
     According to all conventions, the parameter area should be part of the
     caller's stack frame, allocated in the caller's prologue code (large enough
@@ -1191,41 +1197,46 @@ genCCall' dflags gcp target dest_regs args
             PrimTarget mop -> outOfLineMachOp mop
 
         let codeBefore = move_sp_down finalStack `appOL` passArgumentsCode
-                         `appOL` toc_before
-            codeAfter = toc_after labelOrExpr `appOL` move_sp_up finalStack
-                        `appOL` moveResult reduceToFF32
+            codeAfter = move_sp_up finalStack `appOL` moveResult reduceToFF32
 
         case labelOrExpr of
             Left lbl -> do -- the linker does all the work for us
                 return (         codeBefore
                         `snocOL` BL lbl usedRegs
+                        `appOL`  maybeNOP -- some ABI require a NOP after BL
                         `appOL`  codeAfter)
             Right dyn -> do -- implement call through function pointer
                 (dynReg, dynCode) <- getSomeReg dyn
                 case gcp of
                      GCPLinux64ELF 1 -> return ( dynCode
                        `appOL`  codeBefore
+                       `snocOL` ST spFormat toc (AddrRegImm sp (ImmInt 40))
                        `snocOL` LD II64 r11 (AddrRegImm dynReg (ImmInt 0))
                        `snocOL` LD II64 toc (AddrRegImm dynReg (ImmInt 8))
                        `snocOL` MTCTR r11
                        `snocOL` LD II64 r11 (AddrRegImm dynReg (ImmInt 16))
                        `snocOL` BCTRL usedRegs
+                       `snocOL` LD spFormat toc (AddrRegImm sp (ImmInt 40))
                        `appOL`  codeAfter)
                      GCPLinux64ELF 2 -> return ( dynCode
                        `appOL`  codeBefore
+                       `snocOL` ST spFormat toc (AddrRegImm sp (ImmInt 24))
                        `snocOL` MR r12 dynReg
                        `snocOL` MTCTR r12
                        `snocOL` BCTRL usedRegs
+                       `snocOL` LD spFormat toc (AddrRegImm sp (ImmInt 24))
                        `appOL`  codeAfter)
                      GCPAIX          -> return ( dynCode
                        -- AIX/XCOFF follows the PowerOPEN ABI
                        -- which is quite similiar to LinuxPPC64/ELFv1
                        `appOL`  codeBefore
+                       `snocOL` ST spFormat toc (AddrRegImm sp (ImmInt 20))
                        `snocOL` LD II32 r11 (AddrRegImm dynReg (ImmInt 0))
                        `snocOL` LD II32 toc (AddrRegImm dynReg (ImmInt 4))
                        `snocOL` MTCTR r11
                        `snocOL` LD II32 r11 (AddrRegImm dynReg (ImmInt 8))
                        `snocOL` BCTRL usedRegs
+                       `snocOL` LD spFormat toc (AddrRegImm sp (ImmInt 20))
                        `appOL`  codeAfter)
                      _              -> return ( dynCode
                        `snocOL` MTCTR dynReg
@@ -1281,30 +1292,6 @@ genCCall' dflags gcp target dest_regs args
                               DELTA (-delta)]
                | otherwise = nilOL
                where delta = stackDelta finalStack
-        toc_before = case gcp of
-           GCPLinux64ELF 1 -> unitOL $ ST spFormat toc (AddrRegImm sp (ImmInt 40))
-           GCPLinux64ELF 2 -> unitOL $ ST spFormat toc (AddrRegImm sp (ImmInt 24))
-           GCPAIX          -> unitOL $ ST spFormat toc (AddrRegImm sp (ImmInt 20))
-           _               -> nilOL
-        toc_after labelOrExpr = case gcp of
-           GCPLinux64ELF 1 -> case labelOrExpr of
-                                Left _  -> toOL [ NOP ]
-                                Right _ -> toOL [ LD spFormat toc
-                                                     (AddrRegImm sp
-                                                      (ImmInt 40))
-                                                ]
-           GCPLinux64ELF 2 -> case labelOrExpr of
-                                Left _  -> toOL [ NOP ]
-                                Right _ -> toOL [ LD spFormat toc
-                                                     (AddrRegImm sp
-                                                      (ImmInt 24))
-                                                ]
-           GCPAIX          -> case labelOrExpr of
-                                Left _  -> unitOL NOP
-                                Right _ -> unitOL (LD spFormat toc
-                                                      (AddrRegImm sp
-                                                       (ImmInt 20)))
-           _               -> nilOL
         move_sp_up finalStack
                | delta > 64 =  -- TODO: fix-up stack back-chain
                         toOL [ADD sp sp (RIImm (ImmInt delta)),
@@ -1312,6 +1299,19 @@ genCCall' dflags gcp target dest_regs args
                | otherwise = nilOL
                where delta = stackDelta finalStack
 
+        -- A NOP instruction is required after a call (bl instruction)
+        -- on AIX and 64-Bit Linux.
+        -- If the call is to a function with a different TOC (r2) the
+        -- link editor replaces the NOP instruction with a load of the TOC
+        -- from the stack to restore the TOC.
+        maybeNOP = case gcp of
+           -- See Section 3.9.4 of OpenPower ABI
+           GCPAIX          -> unitOL NOP
+           -- See Section 3.5.11 of PPC64 ELF v1.9
+           GCPLinux64ELF 1 -> unitOL NOP
+           -- See Section 2.3.6 of PPC64 ELF v2
+           GCPLinux64ELF 2 -> unitOL NOP
+           _               -> nilOL
 
         passArguments [] _ _ stackOffset accumCode accumUsed = return (stackOffset, accumCode, accumUsed)
         passArguments ((arg,arg_ty):args) gprs fprs stackOffset



More information about the ghc-commits mailing list