~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to compiler/cmm/PprCmmZ.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
 
 
2
module PprCmmZ
 
3
    ( pprCmmGraphLikeCmm
 
4
    )
 
5
where
 
6
 
 
7
import BlockId
 
8
import Cmm
 
9
import PprCmm
 
10
import Outputable
 
11
import qualified ZipCfgCmmRep as G
 
12
import qualified ZipCfg as Z
 
13
import CmmZipUtil
 
14
 
 
15
import Data.Maybe
 
16
import FastString
 
17
 
 
18
----------------------------------------------------------------
 
19
-- | The purpose of this function is to print a Cmm zipper graph "as if it were"
 
20
-- a Cmm program.  The objective is dodgy, so it's unsurprising parts of the
 
21
-- code are dodgy as well.
 
22
 
 
23
pprCmmGraphLikeCmm :: G.CmmGraph -> SDoc
 
24
pprCmmGraphLikeCmm g = vcat (swallow blocks)
 
25
    where blocks = Z.postorder_dfs g
 
26
          swallow :: [G.CmmBlock] -> [SDoc]
 
27
          swallow [] = []
 
28
          swallow (Z.Block id t : rest) = tail id [] Nothing t rest
 
29
          tail id prev' out (Z.ZTail m t) rest = tail id (mid m : prev') out t rest
 
30
          tail id prev' out (Z.ZLast (Z.LastOther l)) rest = last id prev' out l rest
 
31
          tail id prev' _   (Z.ZLast Z.LastExit)      rest = exit id prev' rest
 
32
          mid m = ppr m
 
33
          block' id prev'
 
34
              | id == Z.lg_entry g, entry_has_no_pred =
 
35
                            vcat (text "<entry>" : reverse prev')
 
36
              | otherwise = hang (ppr id <> colon) 4 (vcat (reverse prev'))
 
37
          last id prev' out l n =
 
38
              let endblock stmt = block' id (stmt : prev') : swallow n in
 
39
              case l of
 
40
                G.LastBranch tgt ->
 
41
                    case n of
 
42
                      Z.Block id' t : bs
 
43
                          | tgt == id', unique_pred id' 
 
44
                          -> tail id prev' out t bs  -- optimize out redundant labels
 
45
                      _ -> endblock (ppr $ CmmBranch tgt)
 
46
                l@(G.LastCondBranch expr tid fid) ->
 
47
                  let ft id = text "// fall through to " <> ppr id in
 
48
                  case n of
 
49
                    Z.Block id' t : bs
 
50
                      | id' == fid, isNothing out ->
 
51
                          tail id (ft fid : ppr (CmmCondBranch expr tid) : prev') Nothing t bs
 
52
                      | id' == tid, Just e' <- maybeInvertCmmExpr expr, isNothing out->
 
53
                          tail id (ft tid : ppr (CmmCondBranch e'   fid) : prev') Nothing t bs
 
54
                    _ -> endblock $ with_out out l
 
55
                l@(G.LastSwitch {})      -> endblock $ with_out out l
 
56
                l@(G.LastCall _ _ _ _ _) -> endblock $ with_out out l
 
57
          exit id prev' n = -- highly irregular (assertion violation?)
 
58
              let endblock stmt = block' id (stmt : prev') : swallow n in
 
59
              endblock (text "// <exit>")
 
60
          preds = zipPreds g
 
61
          entry_has_no_pred = case lookupBlockEnv preds (Z.lg_entry g) of
 
62
                                Nothing -> True
 
63
                                Just s -> isEmptyBlockSet s
 
64
          single_preds =
 
65
              let add b single =
 
66
                    let id = Z.blockId b
 
67
                    in  case lookupBlockEnv preds id of
 
68
                          Nothing -> single
 
69
                          Just s -> if sizeBlockSet s == 1 then
 
70
                                        extendBlockSet single id
 
71
                                    else single
 
72
              in  Z.fold_blocks add emptyBlockSet g
 
73
          unique_pred id = elemBlockSet id single_preds
 
74
 
 
75
with_out :: Maybe (G.Convention, CmmActuals) -> G.Last -> SDoc
 
76
with_out Nothing l = ptext (sLit "??no-arguments??") <+> ppr l
 
77
with_out (Just (conv, args)) l = last l
 
78
    where last (G.LastCall e k _ _ _) =
 
79
              hcat [ptext (sLit "... = foreign "),
 
80
                    doubleQuotes(ppr conv), space,
 
81
                    ppr_target e, parens ( commafy $ map ppr args ),
 
82
                    ptext (sLit " \"safe\""),
 
83
                    text " returns to " <+> ppr k,
 
84
                    semi ]
 
85
          last l = ppr l
 
86
          ppr_target (CmmLit lit) = pprLit lit
 
87
          ppr_target fn'          = parens (ppr fn')
 
88
          commafy xs = hsep $ punctuate comma xs