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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/5633b56169b49dfb96e4add8475e3c4303db7e1e

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

commit 5633b56169b49dfb96e4add8475e3c4303db7e1e
Author: Ian Lynagh <[email protected]>
Date:   Wed Jun 13 17:20:46 2012 +0100

    Remove some more Platform arguments

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

 compiler/main/HscMain.hs                   |    2 +-
 compiler/nativeGen/SPARC/CodeGen.hs        |   12 ++++--------
 compiler/nativeGen/SPARC/CodeGen/Sanity.hs |    6 ++----
 compiler/profiling/ProfInit.hs             |    5 ++---
 4 files changed, 9 insertions(+), 16 deletions(-)

diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 0c0b3d9..ecfef91 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1266,7 +1266,7 @@ hscGenHardCode cgguts mod_summary = do
             <- {-# SCC "CoreToStg" #-}
                myCoreToStg dflags this_mod prepd_binds
 
-        let prof_init = profilingInitCode platform this_mod cost_centre_info
+        let prof_init = profilingInitCode this_mod cost_centre_info
             foreign_stubs = foreign_stubs0 `appendStubC` prof_init
 
         ------------------  Code generation ------------------
diff --git a/compiler/nativeGen/SPARC/CodeGen.hs 
b/compiler/nativeGen/SPARC/CodeGen.hs
index 0f3041e..e0656db 100644
--- a/compiler/nativeGen/SPARC/CodeGen.hs
+++ b/compiler/nativeGen/SPARC/CodeGen.hs
@@ -61,10 +61,7 @@ cmmTopCodeGen :: RawCmmDecl
               -> NatM [NatCmmDecl CmmStatics Instr]
 
 cmmTopCodeGen (CmmProc info lab (ListGraph blocks))
- = do
-      dflags <- getDynFlags
-      let platform = targetPlatform dflags
-      (nat_blocks,statics) <- mapAndUnzipM (basicBlockCodeGen platform) blocks
+ = do (nat_blocks,statics) <- mapAndUnzipM basicBlockCodeGen blocks
 
       let proc = CmmProc info lab (ListGraph $ concat nat_blocks)
       let tops = proc : concat statics
@@ -80,12 +77,11 @@ cmmTopCodeGen (CmmData sec dat) = do
 --      are indicated by the NEWBLOCK instruction.  We must split up the
 --      instruction stream into basic blocks again.  Also, we extract
 --      LDATAs here too.
-basicBlockCodeGen :: Platform
-                  -> CmmBasicBlock
+basicBlockCodeGen :: CmmBasicBlock
                   -> NatM ( [NatBasicBlock Instr]
                           , [NatCmmDecl CmmStatics Instr])
 
-basicBlockCodeGen platform cmm@(BasicBlock id stmts) = do
+basicBlockCodeGen cmm@(BasicBlock id stmts) = do
   instrs <- stmtsToInstrs stmts
   let
         (top,other_blocks,statics)
@@ -102,7 +98,7 @@ basicBlockCodeGen platform cmm@(BasicBlock id stmts) = do
 
         -- do intra-block sanity checking
         blocksChecked
-                = map (checkBlock platform cmm)
+                = map (checkBlock cmm)
                 $ BasicBlock id top : other_blocks
 
   return (blocksChecked, statics)
diff --git a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs 
b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs
index 3eea016..7eb8bb4 100644
--- a/compiler/nativeGen/SPARC/CodeGen/Sanity.hs
+++ b/compiler/nativeGen/SPARC/CodeGen/Sanity.hs
@@ -22,17 +22,15 @@ import Instruction
 import OldCmm
 
 import Outputable
-import Platform
 
 
 -- | Enforce intra-block invariants.
 --
-checkBlock :: Platform
-           -> CmmBasicBlock
+checkBlock :: CmmBasicBlock
            -> NatBasicBlock Instr
            -> NatBasicBlock Instr
 
-checkBlock _ cmm block@(BasicBlock _ instrs)
+checkBlock cmm block@(BasicBlock _ instrs)
        | checkBlockInstrs instrs
        = block
        
diff --git a/compiler/profiling/ProfInit.hs b/compiler/profiling/ProfInit.hs
index 6934a07..7e223f8 100644
--- a/compiler/profiling/ProfInit.hs
+++ b/compiler/profiling/ProfInit.hs
@@ -11,7 +11,6 @@ module ProfInit (profilingInitCode) where
 import CLabel
 import CostCentre
 import Outputable
-import Platform
 import StaticFlags
 import FastString
 import Module
@@ -22,8 +21,8 @@ import Module
 -- We must produce declarations for the cost-centres defined in this
 -- module;
 
-profilingInitCode :: Platform -> Module -> CollectedCCs -> SDoc
-profilingInitCode _ this_mod (local_CCs, ___extern_CCs, singleton_CCSs)
+profilingInitCode :: Module -> CollectedCCs -> SDoc
+profilingInitCode this_mod (local_CCs, ___extern_CCs, singleton_CCSs)
  | not opt_SccProfilingOn = empty
  | otherwise
  = vcat



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

Reply via email to