summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen/CgUtils.hs
diff options
context:
space:
mode:
authorsimonmar <unknown>2004-08-20 12:21:05 +0000
committersimonmar <unknown>2004-08-20 12:21:05 +0000
commit557d889d9db42c76b8b4cd07f07eb3616ff3236b (patch)
treeb2cdc66f90dfe03d3f0aa62a83da5a6ef71c26b9 /ghc/compiler/codeGen/CgUtils.hs
parentfa93dff5b78e422d2d3abcc99f3918f6726a6719 (diff)
downloadhaskell-557d889d9db42c76b8b4cd07f07eb3616ff3236b.tar.gz
[project @ 2004-08-20 12:21:03 by simonmar]
Simplify the "impossible branch" handling, and fix a bug in the process. CmmSwitch encodes the possibility of having impossible branches (the destinations are Maybe BlockId rather than just BlockId) so we don't need to encode impossible branches as dummy blocks containing a jump to an impossible location (currently 0). However, PprC and PprCmm weren't set up to cope with Nothings in a CmmSwitch, so this commit fixes that too.
Diffstat (limited to 'ghc/compiler/codeGen/CgUtils.hs')
-rw-r--r--ghc/compiler/codeGen/CgUtils.hs25
1 files changed, 5 insertions, 20 deletions
diff --git a/ghc/compiler/codeGen/CgUtils.hs b/ghc/compiler/codeGen/CgUtils.hs
index ffd25eb908..5dbef8b438 100644
--- a/ghc/compiler/codeGen/CgUtils.hs
+++ b/ghc/compiler/codeGen/CgUtils.hs
@@ -394,16 +394,14 @@ mk_switch tag_expr [(tag,stmts)] (Just deflt) lo_tag hi_tag
-- DENSE TAG RANGE: use a switch statment
mk_switch tag_expr branches mb_deflt lo_tag hi_tag
| use_switch -- Use a switch
- = do { deflt_id <- get_deflt_id mb_deflt
- ; branch_ids <- mapM forkCgStmts (map snd branches)
+ = do { branch_ids <- mapM forkCgStmts (map snd branches)
; let
- tagged_blk_ids = zip (map fst branches) branch_ids
+ tagged_blk_ids = zip (map fst branches) (map Just branch_ids)
- find_branch :: BlockId -> ConTagZ -> BlockId
- find_branch deflt_id i = assocDefault deflt_id tagged_blk_ids i
+ find_branch :: ConTagZ -> Maybe BlockId
+ find_branch i = assocDefault mb_deflt tagged_blk_ids i
- arms = [ Just (find_branch deflt_id (i+lo_tag))
- | i <- [0..n_tags-1]]
+ arms = [ find_branch (i+lo_tag) | i <- [0..n_tags-1]]
switch_stmt = CmmSwitch (cmmOffset tag_expr (- lo_tag)) arms
@@ -443,19 +441,6 @@ mk_switch tag_expr branches mb_deflt lo_tag hi_tag
(lo_branches, hi_branches) = span is_lo branches
is_lo (t,_) = t < mid_tag
- -- Add a default block if the case is not exhaustive
- get_deflt_id (Just deflt_id) = return deflt_id
- get_deflt_id Nothing
- | exhaustive
- = return (pprPanic "mk_deflt_blks" (ppr tag_expr))
- | otherwise
- = do { stmts <- getCgStmts (stmtC jump_to_impossible)
- ; id <- forkCgStmts stmts
- ; return id }
-
- jump_to_impossible
- = CmmJump (mkLblExpr mkErrorStdEntryLabel) []
-
assignTemp' e
| isTrivialCmmExpr e = return (CmmNop, e)