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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/929578081e8b2b0f14e9518329f516eebf4315ce

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

commit 929578081e8b2b0f14e9518329f516eebf4315ce
Author: Simon Marlow <marlo...@gmail.com>
Date:   Mon Nov 12 12:02:44 2012 +0000

    Fix warnings

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

 compiler/cmm/CmmOpt.hs                  |    1 -
 compiler/cmm/PprC.hs                    |    3 +++
 compiler/llvmGen/LlvmCodeGen.hs         |    2 +-
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs |    5 +++--
 compiler/nativeGen/AsmCodeGen.lhs       |    1 -
 compiler/nativeGen/Instruction.hs       |    1 -
 6 files changed, 7 insertions(+), 6 deletions(-)

diff --git a/compiler/cmm/CmmOpt.hs b/compiler/cmm/CmmOpt.hs
index f89c081..f4cf864 100644
--- a/compiler/cmm/CmmOpt.hs
+++ b/compiler/cmm/CmmOpt.hs
@@ -16,7 +16,6 @@ module CmmOpt (
 import CmmUtils
 import Cmm
 import DynFlags
-import CLabel
 
 import FastTypes
 import Outputable
diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs
index ee964d8..9ebb12d 100644
--- a/compiler/cmm/PprC.hs
+++ b/compiler/cmm/PprC.hs
@@ -168,6 +168,7 @@ pprStmt :: CmmNode e x -> SDoc
 pprStmt stmt =
     sdocWithDynFlags $ \dflags ->
     case stmt of
+    CmmEntry _ -> empty
     CmmComment _ -> empty -- (hang (ptext (sLit "/*")) 3 (ftext s)) $$ ptext 
(sLit "*/")
                           -- XXX if the string contains "*/", we need to fix it
                           -- XXX we probably want to emit these comments when
@@ -255,6 +256,8 @@ pprStmt stmt =
     CmmSwitch arg ids        -> sdocWithDynFlags $ \dflags ->
                                 pprSwitch dflags arg ids
 
+    _other -> pprPanic "PprC.pprStmt" (ppr stmt)
+
 type Hinted a = (a, ForeignHint)
 
 pprForeignCall :: SDoc -> CCallConv -> [Hinted CmmFormal] -> [Hinted CmmActual]
diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs
index 241e52e..4b8455f 100644
--- a/compiler/llvmGen/LlvmCodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen.hs
@@ -42,7 +42,7 @@ llvmCodeGen dflags h us cmms
         (cdata,env) = {-# SCC "llvm_split" #-}
                       foldr split ([], initLlvmEnv dflags) cmm
         split (CmmData s d' ) (d,e) = ((s,d'):d,e)
-        split p@(CmmProc h l live g) (d,e) =
+        split (CmmProc h l live g) (d,e) =
             let lbl = strCLabel_llvm env $
                         case mapLookup (g_entry g) h of
                           Nothing                   -> l
diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs 
b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index b5d4b4a..ef9fc2b 100644
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@ -40,8 +40,8 @@ type LlvmStatements = OrdList LlvmStatement
 -- | Top-level of the LLVM proc Code generator
 --
 genLlvmProc :: LlvmEnv -> RawCmmDecl -> UniqSM (LlvmEnv, [LlvmCmmDecl])
-genLlvmProc env proc0@(CmmProc infos lbl live graph) = do
-    let blocks = toBlockList graph
+genLlvmProc env (CmmProc infos lbl live graph) = do
+    let blocks = toBlockListEntryFirst graph
     (env', lmblocks, lmdata) <- basicBlocksCodeGen env live blocks ([], [])
     let info = mapLookup (g_entry graph) infos
         proc = CmmProc info lbl live (ListGraph lmblocks)
@@ -274,6 +274,7 @@ genCall env target res args = do
                                  _          -> CC_Ccc
                  CCallConv    -> CC_Ccc
                  CApiConv     -> CC_Ccc
+                 PrimCallConv -> panic "LlvmCodeGen.CodeGen.genCall: 
PrimCallConv"
 
             PrimTarget   _ -> CC_Ccc
 
diff --git a/compiler/nativeGen/AsmCodeGen.lhs 
b/compiler/nativeGen/AsmCodeGen.lhs
index 7710691..53d1949 100644
--- a/compiler/nativeGen/AsmCodeGen.lhs
+++ b/compiler/nativeGen/AsmCodeGen.lhs
@@ -953,7 +953,6 @@ cmmStmtConFold stmt
 
         CmmCondBranch test true false
            -> do test' <- cmmExprConFold DataReference test
-                 dflags <- getDynFlags
                  return $ case test' of
                    CmmLit (CmmInt 0 _) -> CmmBranch false
                    CmmLit (CmmInt _ _) -> CmmBranch true
diff --git a/compiler/nativeGen/Instruction.hs 
b/compiler/nativeGen/Instruction.hs
index 48d6a33..076129f 100644
--- a/compiler/nativeGen/Instruction.hs
+++ b/compiler/nativeGen/Instruction.hs
@@ -19,7 +19,6 @@ import BlockId
 import DynFlags
 import Cmm hiding (topInfoTable)
 import Platform
-import Outputable
 
 -- | Holds a list of source and destination registers used by a
 --      particular instruction.



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to