Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/152f1eb222d1a06c876a65c5a2d643d0c750cda1

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

commit 152f1eb222d1a06c876a65c5a2d643d0c750cda1
Author: Ian Lynagh <[email protected]>
Date:   Tue Aug 28 21:07:15 2012 +0100

    Remove some CPP from nativeGen/PPC/Regs.h

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

 compiler/nativeGen/PPC/CodeGen.hs |    3 ++-
 compiler/nativeGen/PPC/Instr.hs   |    4 ++--
 compiler/nativeGen/PPC/Regs.hs    |   36 ++++++++++++------------------------
 3 files changed, 16 insertions(+), 27 deletions(-)

diff --git a/compiler/nativeGen/PPC/CodeGen.hs 
b/compiler/nativeGen/PPC/CodeGen.hs
index 19cdfc7..ce4a54c 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -908,7 +908,8 @@ genCCall' platform gcp target dest_regs argsAndHints
     do
         (finalStack,passArgumentsCode,usedRegs) <- passArguments
                                                         (zip args argReps)
-                                                        allArgRegs allFPArgRegs
+                                                        allArgRegs
+                                                        (allFPArgRegs platform)
                                                         initialStackOffset
                                                         (toOL []) []
 
diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs
index ff70353..1af08a6 100644
--- a/compiler/nativeGen/PPC/Instr.hs
+++ b/compiler/nativeGen/PPC/Instr.hs
@@ -194,8 +194,8 @@ ppc_regUsageOfInstr platform instr
     BCCFAR _ _         -> noUsage
     MTCTR reg          -> usage ([reg],[])
     BCTR  _ _          -> noUsage
-    BL    _ params     -> usage (params, callClobberedRegs)
-    BCTRL params       -> usage (params, callClobberedRegs)
+    BL    _ params     -> usage (params, callClobberedRegs platform)
+    BCTRL params       -> usage (params, callClobberedRegs platform)
     ADD          reg1 reg2 ri  -> usage (reg2 : regRI ri, [reg1])
     ADDC  reg1 reg2 reg3-> usage ([reg2,reg3], [reg1])
     ADDE  reg1 reg2 reg3-> usage ([reg2,reg3], [reg1])
diff --git a/compiler/nativeGen/PPC/Regs.hs b/compiler/nativeGen/PPC/Regs.hs
index 2172d6d..7dccb60 100644
--- a/compiler/nativeGen/PPC/Regs.hs
+++ b/compiler/nativeGen/PPC/Regs.hs
@@ -221,19 +221,12 @@ allArgRegs = map regSingle [3..10]
 
 
 -- these are the regs which we cannot assume stay alive over a C call.
-callClobberedRegs :: [Reg]
-#if   defined(darwin_TARGET_OS)
-callClobberedRegs
-  = map regSingle (0:[2..12] ++ map fReg [0..13])
-
-#elif defined(linux_TARGET_OS)
-callClobberedRegs
-  = map regSingle (0:[2..13] ++ map fReg [0..13])
-
-#else
-callClobberedRegs
-        = panic "PPC.Regs.callClobberedRegs: not defined for this architecture"
-#endif
+callClobberedRegs :: Platform -> [Reg]
+callClobberedRegs platform
+  = case platformOS platform of
+    OSDarwin -> map regSingle (0:[2..12] ++ map fReg [0..13])
+    OSLinux  -> map regSingle (0:[2..13] ++ map fReg [0..13])
+    _        -> panic "PPC.Regs.callClobberedRegs: not defined for this 
architecture"
 
 
 allMachRegNos   :: [RegNo]
@@ -259,17 +252,12 @@ showReg n
 
 -- machine specific 
------------------------------------------------------------
 
-allFPArgRegs :: [Reg]
-#if    defined(darwin_TARGET_OS)
-allFPArgRegs = map (regSingle . fReg) [1..13]
-
-#elif  defined(linux_TARGET_OS)
-allFPArgRegs = map (regSingle . fReg) [1..8]
-
-#else
-allFPArgRegs = panic "PPC.Regs.allFPArgRegs: not defined for this architecture"
-
-#endif
+allFPArgRegs :: Platform -> [Reg]
+allFPArgRegs platform
+    = case platformOS platform of
+      OSDarwin -> map (regSingle . fReg) [1..13]
+      OSLinux  -> map (regSingle . fReg) [1..8]
+      _        -> panic "PPC.Regs.allFPArgRegs: not defined for this 
architecture"
 
 fits16Bits :: Integral a => a -> Bool
 fits16Bits x = x >= -32768 && x < 32768



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to