diff options
author | David Terei <davidterei@gmail.com> | 2011-12-22 14:40:22 -0800 |
---|---|---|
committer | David Terei <davidterei@gmail.com> | 2012-01-05 17:05:42 -0800 |
commit | 1cb4a07cf284444ed89057f4661db100ea740dc5 (patch) | |
tree | f2308443d9f2a0f9bb4c74bcbc7334f3a69247e2 /compiler | |
parent | 9ee9e518fe485107c9a21fed68a7dcc86fe08b4c (diff) | |
download | haskell-1cb4a07cf284444ed89057f4661db100ea740dc5.tar.gz |
Remove unused argument field on CmmJump
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/cmm/CmmCvt.hs | 2 | ||||
-rw-r--r-- | compiler/cmm/CmmLint.hs | 2 | ||||
-rw-r--r-- | compiler/cmm/CmmOpt.hs | 6 | ||||
-rw-r--r-- | compiler/cmm/CmmParse.y | 6 | ||||
-rw-r--r-- | compiler/cmm/OldCmm.hs | 3 | ||||
-rw-r--r-- | compiler/cmm/OldPprCmm.hs | 8 | ||||
-rw-r--r-- | compiler/cmm/PprC.hs | 4 | ||||
-rw-r--r-- | compiler/codeGen/CgClosure.lhs | 4 | ||||
-rw-r--r-- | compiler/codeGen/CgCon.lhs | 4 | ||||
-rw-r--r-- | compiler/codeGen/CgHeapery.lhs | 2 | ||||
-rw-r--r-- | compiler/codeGen/CgInfoTbls.hs | 2 | ||||
-rw-r--r-- | compiler/codeGen/CgMonad.lhs | 2 | ||||
-rw-r--r-- | compiler/codeGen/CgTailCall.lhs | 10 | ||||
-rw-r--r-- | compiler/codeGen/CgUtils.hs | 2 | ||||
-rw-r--r-- | compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/AsmCodeGen.lhs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/CodeGen.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/X86/CodeGen.hs | 2 |
19 files changed, 33 insertions, 36 deletions
diff --git a/compiler/cmm/CmmCvt.hs b/compiler/cmm/CmmCvt.hs index c82f517849..42aaabc305 100644 --- a/compiler/cmm/CmmCvt.hs +++ b/compiler/cmm/CmmCvt.hs @@ -105,7 +105,7 @@ ofZgraph g = Old.ListGraph $ mapMaybe convert_block $ postorderDfs g , Just expr' <- maybeInvertCmmExpr expr -> Old.CmmCondBranch expr' fid : tail_of tid | otherwise -> [Old.CmmCondBranch expr tid, Old.CmmBranch fid] CmmSwitch arg ids -> [Old.CmmSwitch arg ids] - CmmCall e _ _ _ _ -> [Old.CmmJump e []] + CmmCall e _ _ _ _ -> [Old.CmmJump e] CmmForeignCall {} -> panic "ofZgraph: CmmForeignCall" tail_of bid = case foldBlockNodesB3 (first, middle, last) block () of Old.BasicBlock _ stmts -> stmts diff --git a/compiler/cmm/CmmLint.hs b/compiler/cmm/CmmLint.hs index ee53c1b6c7..db6dd2fc26 100644 --- a/compiler/cmm/CmmLint.hs +++ b/compiler/cmm/CmmLint.hs @@ -143,7 +143,7 @@ lintCmmStmt platform labels = lint then return () else cmmLintErr (text "switch scrutinee is not a word: " <> pprPlatform platform e <> text " :: " <> ppr erep) - lint (CmmJump e args) = lintCmmExpr platform e >> mapM_ (lintCmmExpr platform . hintlessCmm) args + lint (CmmJump e) = lintCmmExpr platform e >> return () lint (CmmReturn ress) = mapM_ (lintCmmExpr platform . hintlessCmm) ress lint (CmmBranch id) = checkTarget id checkTarget id = if setMember id labels then return () diff --git a/compiler/cmm/CmmOpt.hs b/compiler/cmm/CmmOpt.hs index 007b7a715e..649dbb578c 100644 --- a/compiler/cmm/CmmOpt.hs +++ b/compiler/cmm/CmmOpt.hs @@ -65,7 +65,7 @@ cmmEliminateDeadBlocks blocks@(BasicBlock base_id _:_) = stmt m (CmmBranch b) = b:m stmt m (CmmCondBranch e b) = b:(expr m e) stmt m (CmmSwitch e bs) = catMaybes bs ++ expr m e - stmt m (CmmJump e as) = expr (actuals m as) e + stmt m (CmmJump e) = expr m e stmt m (CmmReturn as) = actuals m as actuals m as = foldl' (\m h -> expr m (hintlessCmm h)) m as -- We have to do a deep fold into CmmExpr because @@ -273,7 +273,7 @@ inlineStmt u a (CmmCall target regs es ret) es' = [ (CmmHinted (inlineExpr u a e) hint) | (CmmHinted e hint) <- es ] inlineStmt u a (CmmCondBranch e d) = CmmCondBranch (inlineExpr u a e) d inlineStmt u a (CmmSwitch e d) = CmmSwitch (inlineExpr u a e) d -inlineStmt u a (CmmJump e d) = CmmJump (inlineExpr u a e) d +inlineStmt u a (CmmJump e) = CmmJump (inlineExpr u a e) inlineStmt _ _ other_stmt = other_stmt inlineExpr :: Unique -> CmmExpr -> CmmExpr -> CmmExpr @@ -669,7 +669,7 @@ cmmLoopifyForC (CmmProc (Just info@(Statics info_lbl _)) entry_lbl where blocks' = [ BasicBlock id (map do_stmt stmts) | BasicBlock id stmts <- blocks ] - do_stmt (CmmJump (CmmLit (CmmLabel lbl)) _) | lbl == jump_lbl + do_stmt (CmmJump (CmmLit (CmmLabel lbl))) | lbl == jump_lbl = CmmBranch top_id do_stmt stmt = stmt diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index e0d3da8a62..6660a0c33e 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -411,8 +411,8 @@ stmt :: { ExtCode } { do as <- sequence $5; doSwitch $2 $3 as $6 } | 'goto' NAME ';' { do l <- lookupLabel $2; stmtEC (CmmBranch l) } - | 'jump' expr maybe_actuals ';' - { do e1 <- $2; e2 <- sequence $3; stmtEC (CmmJump e1 e2) } + | 'jump' expr ';' + { do e <- $2; stmtEC (CmmJump e) } | 'return' maybe_actuals ';' { do e <- sequence $2; stmtEC (CmmReturn e) } | 'if' bool_expr 'goto' NAME @@ -945,7 +945,7 @@ emitRetUT args = do -- or regs that we assign to, so better use -- simultaneous assignments here (#3546) when (sp /= 0) $ stmtC (CmmAssign spReg (cmmRegOffW spReg (-sp))) - stmtC (CmmJump (entryCode (CmmLoad (cmmRegOffW spReg sp) bWord)) []) + stmtC $ CmmJump (entryCode (CmmLoad (cmmRegOffW spReg sp) bWord)) -- TODO (when using CPS): emitStmt (CmmReturn (map snd args)) -- ----------------------------------------------------------------------------- diff --git a/compiler/cmm/OldCmm.hs b/compiler/cmm/OldCmm.hs index a8a9d5dde0..343d7c1541 100644 --- a/compiler/cmm/OldCmm.hs +++ b/compiler/cmm/OldCmm.hs @@ -169,7 +169,6 @@ data CmmStmt -- Old-style -- Undefined outside range, and when there's a Nothing | CmmJump CmmExpr -- Jump to another C-- function, - [HintedCmmActual] -- with these parameters. (parameters never used) | CmmReturn -- Return from a native C-- function, [HintedCmmActual] -- with these return values. (parameters never used) @@ -195,7 +194,7 @@ instance UserOfLocalRegs CmmStmt where stmt (CmmBranch _) = id stmt (CmmCondBranch e _) = gen e stmt (CmmSwitch e _) = gen e - stmt (CmmJump e es) = gen e . gen es + stmt (CmmJump e) = gen e stmt (CmmReturn es) = gen es gen :: UserOfLocalRegs a => a -> b -> b diff --git a/compiler/cmm/OldPprCmm.hs b/compiler/cmm/OldPprCmm.hs index 07dfbf63bf..d6db11bd4f 100644 --- a/compiler/cmm/OldPprCmm.hs +++ b/compiler/cmm/OldPprCmm.hs @@ -153,7 +153,7 @@ pprStmt platform stmt = case stmt of CmmBranch ident -> genBranch ident CmmCondBranch expr ident -> genCondBranch platform expr ident - CmmJump expr params -> genJump platform expr params + CmmJump expr -> genJump platform expr CmmReturn params -> genReturn platform params CmmSwitch arg ids -> genSwitch platform arg ids @@ -203,8 +203,8 @@ genCondBranch platform expr ident = -- -- jump foo(a, b, c); -- -genJump :: Platform -> CmmExpr -> [CmmHinted CmmExpr] -> SDoc -genJump platform expr args = +genJump :: Platform -> CmmExpr -> SDoc +genJump platform expr = hcat [ ptext (sLit "jump") , space , if isTrivialCmmExpr expr @@ -212,8 +212,6 @@ genJump platform expr args = else case expr of CmmLoad (CmmReg _) _ -> pprExpr platform expr _ -> parens (pprExpr platform expr) - , space - , parens ( commafy $ map (pprPlatform platform) args ) , semi ] diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 21826f8224..e4a5c5f896 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -248,7 +248,7 @@ pprStmt platform stmt = case stmt of CmmBranch ident -> pprBranch ident CmmCondBranch expr ident -> pprCondBranch platform expr ident - CmmJump lbl _params -> mkJMP_(pprExpr platform lbl) <> semi + CmmJump lbl -> mkJMP_(pprExpr platform lbl) <> semi CmmSwitch arg ids -> pprSwitch platform arg ids pprCFunType :: SDoc -> CCallConv -> [HintedCmmFormal] -> [HintedCmmActual] -> SDoc @@ -930,7 +930,7 @@ te_Stmt (CmmCall _ rs es _) = mapM_ (te_temp.hintlessCmm) rs >> mapM_ (te_Expr.hintlessCmm) es te_Stmt (CmmCondBranch e _) = te_Expr e te_Stmt (CmmSwitch e _) = te_Expr e -te_Stmt (CmmJump e _) = te_Expr e +te_Stmt (CmmJump e) = te_Expr e te_Stmt _ = return () te_Expr :: CmmExpr -> TE () diff --git a/compiler/codeGen/CgClosure.lhs b/compiler/codeGen/CgClosure.lhs index 96e6395e95..8e599c3fb5 100644 --- a/compiler/codeGen/CgClosure.lhs +++ b/compiler/codeGen/CgClosure.lhs @@ -374,7 +374,7 @@ mkSlowEntryCode cl_info reg_args stk_adj_pop = CmmAssign spReg (cmmRegOffW spReg final_stk_offset) stk_adj_push = CmmAssign spReg (cmmRegOffW spReg (- final_stk_offset)) - jump_to_entry = CmmJump (mkLblExpr (entryLabelFromCI cl_info)) [] + jump_to_entry = CmmJump (mkLblExpr (entryLabelFromCI cl_info)) \end{code} @@ -590,7 +590,7 @@ link_caf cl_info _is_upd = do -- assuming lots of things, like the stack pointer hasn't -- moved since we entered the CAF. let target = entryCode (closureInfoPtr (CmmReg nodeReg)) in - stmtC (CmmJump target []) + stmtC (CmmJump target) ; returnFC hp_rel } where diff --git a/compiler/codeGen/CgCon.lhs b/compiler/codeGen/CgCon.lhs index 17bb9d0ad8..99690945cb 100644 --- a/compiler/codeGen/CgCon.lhs +++ b/compiler/codeGen/CgCon.lhs @@ -352,8 +352,8 @@ cgReturnDataCon con amodes } where enter_it = stmtsC [ CmmAssign nodeReg (cmmUntag (CmmReg nodeReg)), - CmmJump (entryCode (closureInfoPtr (CmmReg nodeReg))) [] ] - jump_to lbl = stmtC (CmmJump (CmmLit lbl) []) + CmmJump (entryCode (closureInfoPtr (CmmReg nodeReg)))] + jump_to lbl = stmtC (CmmJump (CmmLit lbl)) build_it_then return_code = do { -- BUILD THE OBJECT IN THE HEAP -- The first "con" says that the name bound to this diff --git a/compiler/codeGen/CgHeapery.lhs b/compiler/codeGen/CgHeapery.lhs index 03b5deb058..d8ac298b58 100644 --- a/compiler/codeGen/CgHeapery.lhs +++ b/compiler/codeGen/CgHeapery.lhs @@ -464,7 +464,7 @@ do_checks' stk_expr hp_expr stk_nonzero hp_nonzero reg_save_code rts_lbl -- the appropriate RTS stub. ; exit_blk_id <- forkLabelledCode $ do { ; emitStmts reg_save_code - ; stmtC (CmmJump rts_lbl []) } + ; stmtC (CmmJump rts_lbl) } -- In the case of a heap-check failure, we must also set -- HpAlloc. NB. HpAlloc is *only* set if Hp has been diff --git a/compiler/codeGen/CgInfoTbls.hs b/compiler/codeGen/CgInfoTbls.hs index 25ba154d12..9f003a2302 100644 --- a/compiler/codeGen/CgInfoTbls.hs +++ b/compiler/codeGen/CgInfoTbls.hs @@ -253,7 +253,7 @@ emitAlgReturnTarget name branches mb_deflt fam_sz emitReturnInstr :: Code emitReturnInstr = do { info_amode <- getSequelAmode - ; stmtC (CmmJump (entryCode info_amode) []) } + ; stmtC (CmmJump (entryCode info_amode)) } ----------------------------------------------------------------------------- -- diff --git a/compiler/codeGen/CgMonad.lhs b/compiler/codeGen/CgMonad.lhs index 490f9520f1..4617aaa8a3 100644 --- a/compiler/codeGen/CgMonad.lhs +++ b/compiler/codeGen/CgMonad.lhs @@ -249,7 +249,7 @@ flattenCgStmts id stmts = where (block,blocks) = flatten ss isJump :: CmmStmt -> Bool -isJump (CmmJump _ _) = True +isJump (CmmJump _ ) = True isJump (CmmBranch _ ) = True isJump (CmmSwitch _ _) = True isJump (CmmReturn _ ) = True diff --git a/compiler/codeGen/CgTailCall.lhs b/compiler/codeGen/CgTailCall.lhs index fb8f854c0b..07be7f23fa 100644 --- a/compiler/codeGen/CgTailCall.lhs +++ b/compiler/codeGen/CgTailCall.lhs @@ -123,7 +123,7 @@ performTailCall fun_info arg_amodes pending_assts EnterIt -> do { emitSimultaneously (node_asst `plusStmts` pending_assts) ; let target = entryCode (closureInfoPtr (CmmReg nodeReg)) - enterClosure = stmtC (CmmJump target []) + enterClosure = stmtC (CmmJump target) -- If this is a scrutinee -- let's check if the closure is a constructor -- so we can directly jump to the alternatives switch @@ -203,7 +203,7 @@ performTailCall fun_info arg_amodes pending_assts -- No, enter the closure. ; enterClosure ; labelC is_constr - ; stmtC (CmmJump (entryCode $ CmmLit (CmmLabel lbl)) []) + ; stmtC (CmmJump (entryCode $ CmmLit (CmmLabel lbl))) } {- -- This is a scrutinee for a case expression @@ -218,7 +218,7 @@ performTailCall fun_info arg_amodes pending_assts ; stmtC (CmmCondBranch (cond1 tag) no_cons) ; stmtC (CmmCondBranch (cond2 tag) no_cons) -- Yes, jump to switch statement - ; stmtC (CmmJump (CmmLit (CmmLabel lbl)) []) + ; stmtC (CmmJump (CmmLit (CmmLabel lbl))) ; labelC no_cons -- No, enter the closure. ; enterClosure @@ -438,9 +438,9 @@ pushReturnAddress _ = nopC -- ----------------------------------------------------------------------------- -- Misc. -jumpToLbl :: CLabel -> Code -- Passes no argument to the destination procedure -jumpToLbl lbl = stmtC (CmmJump (CmmLit (CmmLabel lbl)) [{- No args -}]) +jumpToLbl :: CLabel -> Code +jumpToLbl lbl = stmtC (CmmJump (CmmLit (CmmLabel lbl))) assignToRegs :: [(CmmExpr, GlobalReg)] -> CmmStmts assignToRegs reg_args diff --git a/compiler/codeGen/CgUtils.hs b/compiler/codeGen/CgUtils.hs index 5274a176a0..2a524a182c 100644 --- a/compiler/codeGen/CgUtils.hs +++ b/compiler/codeGen/CgUtils.hs @@ -1020,7 +1020,7 @@ fixStgRegStmt stmt CmmSwitch expr ids -> CmmSwitch (fixStgRegExpr expr) ids - CmmJump addr regs -> CmmJump (fixStgRegExpr addr) regs + CmmJump addr -> CmmJump (fixStgRegExpr addr) -- CmmNop, CmmComment, CmmBranch, CmmReturn _other -> stmt diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index d8507ab810..821ef5b933 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -127,7 +127,7 @@ stmtToInstrs env stmt = case stmt of -> genCall env target res args ret -- Tail call - CmmJump arg _ -> genJump env arg + CmmJump arg -> genJump env arg -- CPS, only tail calls, no return's -- Actually, there are a few return statements that occur because of hand diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs index f56238fd12..b404e87f31 100644 --- a/compiler/nativeGen/AsmCodeGen.lhs +++ b/compiler/nativeGen/AsmCodeGen.lhs @@ -878,9 +878,9 @@ cmmStmtConFold stmt src' <- cmmExprConFold DataReference src return $ CmmStore addr' src' - CmmJump addr regs + CmmJump addr -> do addr' <- cmmExprConFold JumpReference addr - return $ CmmJump addr' regs + return $ CmmJump addr' CmmCall target regs args returns -> do target' <- case target of diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index d0cae69cad..6d91bacb31 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -141,7 +141,7 @@ stmtToInstrs stmt = do CmmBranch id -> genBranch id CmmCondBranch arg id -> genCondJump id arg CmmSwitch arg ids -> genSwitch arg ids - CmmJump arg _ -> genJump arg + CmmJump arg -> genJump arg CmmReturn _ -> panic "stmtToInstrs: return statement should have been cps'd away" diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index ff1e9f2eb2..c37cdd6760 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -141,7 +141,7 @@ stmtToInstrs stmt = case stmt of CmmBranch id -> genBranch id CmmCondBranch arg id -> genCondJump id arg CmmSwitch arg ids -> genSwitch arg ids - CmmJump arg _ -> genJump arg + CmmJump arg -> genJump arg CmmReturn _ -> panic "stmtToInstrs: return statement should have been cps'd away" diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index e69aab40f4..9ddcf460b4 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -166,7 +166,7 @@ stmtToInstrs stmt = do CmmBranch id -> genBranch id CmmCondBranch arg id -> genCondJump id arg CmmSwitch arg ids -> genSwitch arg ids - CmmJump arg _ -> genJump arg + CmmJump arg -> genJump arg CmmReturn _ -> panic "stmtToInstrs: return statement should have been cps'd away" |