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

On branch  : ghc-7.2

http://hackage.haskell.org/trac/ghc/changeset/0694fbbf793695c61fdb140af7f1ea04026dcb07

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

commit 0694fbbf793695c61fdb140af7f1ea04026dcb07
Author: Ian Lynagh <[email protected]>
Date:   Fri Jul 15 17:42:24 2011 +0100

    Remove some more defaultTargetPlatform uses

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

 compiler/nativeGen/AsmCodeGen.lhs          |   11 ++++++-----
 compiler/nativeGen/RegAlloc/Graph/Main.hs  |   11 ++++++-----
 compiler/nativeGen/RegAlloc/Graph/Stats.hs |    8 ++++----
 compiler/nativeGen/TargetReg.hs            |   12 ++++++------
 4 files changed, 22 insertions(+), 20 deletions(-)

diff --git a/compiler/nativeGen/AsmCodeGen.lhs 
b/compiler/nativeGen/AsmCodeGen.lhs
index 9941546..c868488 100644
--- a/compiler/nativeGen/AsmCodeGen.lhs
+++ b/compiler/nativeGen/AsmCodeGen.lhs
@@ -212,7 +212,8 @@ nativeCodeGen' :: (Outputable statics, PlatformOutputable 
instr, Instruction ins
                -> Handle -> UniqSupply -> [RawCmm] -> IO ()
 nativeCodeGen' dflags ncgImpl h us cmms
  = do
-       let split_cmms  = concat $ map add_split cmms
+       let platform = targetPlatform dflags
+           split_cmms  = concat $ map add_split cmms
         -- BufHandle is a performance hack.  We could hide it inside
         -- Pretty if it weren't for the fact that we do lots of little
         -- printDocs here (in order to do codegen in constant space).
@@ -226,7 +227,7 @@ nativeCodeGen' dflags ncgImpl h us cmms
        -- dump native code
        dumpIfSet_dyn dflags
                Opt_D_dump_asm "Asm code"
-               (vcat $ map (docToSDoc . pprNatCmmTop ncgImpl (targetPlatform 
dflags)) $ concat native)
+               (vcat $ map (docToSDoc . pprNatCmmTop ncgImpl platform) $ 
concat native)
 
        -- dump global NCG stats for graph coloring allocator
        (case concat $ catMaybes colorStats of
@@ -245,9 +246,9 @@ nativeCodeGen' dflags ncgImpl h us cmms
                        Opt_D_dump_asm_conflicts "Register conflict graph"
                        $ Color.dotGraph 
                                targetRegDotColor 
-                               (Color.trivColorable (targetPlatform dflags)
-                                       targetVirtualRegSqueeze 
-                                       targetRealRegSqueeze)
+                               (Color.trivColorable platform
+                                       (targetVirtualRegSqueeze platform)
+                                       (targetRealRegSqueeze platform))
                        $ graphGlobal)
 
 
diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs 
b/compiler/nativeGen/RegAlloc/Graph/Main.hs
index 1b3ecd1..3cdc122 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Main.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs
@@ -59,9 +59,10 @@ regAlloc dflags regsFree slotsFree code
        -- TODO: the regClass function is currently hard coded to the default 
target
        --       architecture. Would prefer to determine this from dflags.
        --       There are other uses of targetRegClass later in this module.
-       let triv = trivColorable (targetPlatform dflags)
-                       targetVirtualRegSqueeze
-                       targetRealRegSqueeze
+       let platform = targetPlatform dflags
+           triv = trivColorable platform
+                       (targetVirtualRegSqueeze platform)
+                       (targetRealRegSqueeze platform)
 
        (code_final, debug_codeGraphs, _)
                <- regAlloc_spin dflags 0 
@@ -349,8 +350,8 @@ patchRegsFromGraph platform graph code
                        $$ Color.dotGraph 
                                (\_ -> text "white") 
                                (trivColorable platform
-                                       targetVirtualRegSqueeze
-                                       targetRealRegSqueeze)
+                                       (targetVirtualRegSqueeze platform)
+                                       (targetRealRegSqueeze platform))
                                graph)
 
    in  patchEraseLive patchF code
diff --git a/compiler/nativeGen/RegAlloc/Graph/Stats.hs 
b/compiler/nativeGen/RegAlloc/Graph/Stats.hs
index 4b10e9f..ccbe3fe 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Stats.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Stats.hs
@@ -76,8 +76,8 @@ instance (Outputable statics, PlatformOutputable instr) => 
PlatformOutputable (R
        $$ Color.dotGraph 
                targetRegDotColor
                (trivColorable platform
-                       targetVirtualRegSqueeze
-                       targetRealRegSqueeze)
+                       (targetVirtualRegSqueeze platform)
+                       (targetRealRegSqueeze platform))
                (raGraph s)
 
 
@@ -113,8 +113,8 @@ instance (Outputable statics, PlatformOutputable instr) => 
PlatformOutputable (R
        $$ Color.dotGraph 
                targetRegDotColor
                (trivColorable platform
-                       targetVirtualRegSqueeze
-                       targetRealRegSqueeze)
+                       (targetVirtualRegSqueeze platform)
+                       (targetRealRegSqueeze platform))
                (raGraphColored s)
        $$ text ""
 
diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs
index e6427ed..cf2cf80 100644
--- a/compiler/nativeGen/TargetReg.hs
+++ b/compiler/nativeGen/TargetReg.hs
@@ -44,9 +44,9 @@ import qualified SPARC.Regs     as SPARC
 --       We should be passing DynFlags in instead, and looking at
 --       its targetPlatform.
 
-targetVirtualRegSqueeze :: RegClass -> VirtualReg -> FastInt
-targetVirtualRegSqueeze
-    = case platformArch defaultTargetPlatform of
+targetVirtualRegSqueeze :: Platform -> RegClass -> VirtualReg -> FastInt
+targetVirtualRegSqueeze platform
+    = case platformArch platform of
       ArchX86     -> X86.virtualRegSqueeze
       ArchX86_64  -> X86.virtualRegSqueeze
       ArchPPC     -> PPC.virtualRegSqueeze
@@ -55,9 +55,9 @@ targetVirtualRegSqueeze
       ArchARM     -> panic "targetVirtualRegSqueeze ArchARM"
       ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown"
 
-targetRealRegSqueeze :: RegClass -> RealReg -> FastInt
-targetRealRegSqueeze
-    = case platformArch defaultTargetPlatform of
+targetRealRegSqueeze :: Platform -> RegClass -> RealReg -> FastInt
+targetRealRegSqueeze platform
+    = case platformArch platform of
       ArchX86     -> X86.realRegSqueeze
       ArchX86_64  -> X86.realRegSqueeze
       ArchPPC     -> PPC.realRegSqueeze



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

Reply via email to