remove remaining redundancies from ZipCfgCmmRep
[ghc-hetmet.git] / compiler / cmm / PprCmmZ.hs
1
2 module PprCmmZ
3     ( pprCmmGraphLikeCmm
4     )
5 where
6
7 #include "HsVersions.h"
8
9 import Cmm
10 import CmmExpr
11 import ForeignCall
12 import PprCmm
13 import Outputable
14 import qualified ZipCfgCmmRep as G
15 import qualified ZipCfg as Z
16 import CmmZipUtil
17
18 import Maybe
19 import UniqSet
20 import FastString
21
22 ----------------------------------------------------------------
23 -- | The purpose of this function is to print a Cmm zipper graph "as if it were"
24 -- a Cmm program.  The objective is dodgy, so it's unsurprising parts of the
25 -- code are dodgy as well.
26
27 pprCmmGraphLikeCmm :: G.CmmGraph -> SDoc
28 pprCmmGraphLikeCmm g = vcat (swallow blocks)
29     where blocks = Z.postorder_dfs g
30           swallow :: [G.CmmBlock] -> [SDoc]
31           swallow [] = []
32           swallow (Z.Block id t : rest) = tail id [] Nothing t rest
33           tail id prev' out (Z.ZTail (G.CopyOut conv args) t) rest =
34               if isJust out then panic "multiple CopyOut nodes in one basic block"
35               else
36                   tail id (prev') (Just (conv, args)) t rest
37           tail id prev' out (Z.ZTail m t) rest = tail id (mid m : prev') out t rest
38           tail id prev' out (Z.ZLast Z.LastExit)      rest = exit id prev' out rest
39           tail id prev' out (Z.ZLast (Z.LastOther l)) rest = last id prev' out l rest
40           mid (G.CopyIn _ [] _) = text "// proc point (no parameters)"
41           mid m@(G.CopyIn {}) = ppr m <+> text "(proc point)"
42           mid m = ppr m
43           block' id prev'
44               | id == Z.lg_entry g, entry_has_no_pred =
45                             vcat (text "<entry>" : reverse prev')
46               | otherwise = hang (ppr id <> colon) 4 (vcat (reverse prev'))
47           last id prev' out l n =
48               let endblock stmt = block' id (stmt : prev') : swallow n in
49               case l of
50                 G.LastBranch tgt ->
51                     case n of
52                       Z.Block id' t : bs
53                           | tgt == id', unique_pred id' 
54                           -> tail id prev' out t bs  -- optimize out redundant labels
55                       _ -> endblock (ppr $ CmmBranch tgt)
56                 l@(G.LastCondBranch expr tid fid) ->
57                   let ft id = text "// fall through to " <> ppr id in
58                   case n of
59                     Z.Block id' t : bs
60                       | id' == fid, isNothing out ->
61                           tail id (ft fid : ppr (CmmCondBranch expr tid) : prev') Nothing t bs
62                       | id' == tid, Just e' <- maybeInvertCmmExpr expr, isNothing out->
63                           tail id (ft tid : ppr (CmmCondBranch e'   fid) : prev') Nothing t bs
64                     _ -> endblock $ with_out out l
65                 l@(G.LastJump   {}) -> endblock $ with_out out l
66                 l@(G.LastReturn {}) -> endblock $ with_out out l
67                 l@(G.LastSwitch {}) -> endblock $ with_out out l
68                 l@(G.LastCall _ Nothing) -> endblock $ with_out out l
69                 l@(G.LastCall tgt (Just k))
70                    | Z.Block id' (Z.ZTail (G.CopyIn _ ress srt) t) : bs <- n,
71                      Just (conv, args) <- out,
72                      id' == k ->
73                          let call = CmmCall tgt' ress args (CmmSafe srt) CmmMayReturn
74                              tgt' = CmmCallee tgt (cconv_of_conv conv)
75                              ppcall = ppr call <+> parens (text "ret to" <+> ppr k)
76                          in if unique_pred k then
77                                 tail id (ppcall : prev') Nothing t bs
78                             else
79                                 endblock (ppcall)
80                    | Z.Block id' t : bs <- n, id' == k, unique_pred k,
81                      Just (conv, args) <- out,
82                      Just (ress, srt) <- findCopyIn t ->
83                          let call = CmmCall tgt' ress args (CmmSafe srt) CmmMayReturn
84                              tgt' = CmmCallee tgt (cconv_of_conv conv)
85                              delayed =
86                                  ptext SLIT("// delayed CopyIn follows previous call")
87                          in  tail id (delayed : ppr call : prev') Nothing t bs
88                    | otherwise -> endblock $ with_out out l
89           findCopyIn (Z.ZTail (G.CopyIn _ ress srt) _) = Just (ress, srt)
90           findCopyIn (Z.ZTail _ t) = findCopyIn t
91           findCopyIn (Z.ZLast _) = Nothing
92           exit id prev' out n = -- highly irregular (assertion violation?)
93               let endblock stmt = block' id (stmt : prev') : swallow n in
94               case out of Nothing -> endblock (text "// <exit>")
95                           Just (conv, args) -> endblock (ppr (G.CopyOut conv args) $$
96                                                          text "// <exit>")
97           preds = zipPreds g
98           entry_has_no_pred = case Z.lookupBlockEnv preds (Z.lg_entry g) of
99                                 Nothing -> True
100                                 Just s -> isEmptyUniqSet s
101           single_preds =
102               let add b single =
103                     let id = Z.blockId b
104                     in  case Z.lookupBlockEnv preds id of
105                           Nothing -> single
106                           Just s -> if sizeUniqSet s == 1 then
107                                         Z.extendBlockSet single id
108                                     else single
109               in  Z.fold_blocks add Z.emptyBlockSet g
110           unique_pred id = Z.elemBlockSet id single_preds
111           cconv_of_conv (G.ConventionStandard conv _) = conv
112           cconv_of_conv (G.ConventionPrivate {}) = CmmCallConv -- XXX totally bogus
113
114 with_out :: Maybe (G.Convention, CmmActuals) -> G.Last -> SDoc
115 with_out Nothing l = ptext SLIT("??no-arguments??") <+> ppr l
116 with_out (Just (conv, args)) l = last l
117     where last (G.LastCall e k) =
118               hcat [ptext SLIT("... = foreign "),
119                     doubleQuotes(ppr conv), space,
120                     ppr_target e, parens ( commafy $ map ppr args ),
121                     ptext SLIT(" \"safe\""),
122                     case k of Nothing -> ptext SLIT(" never returns")
123                               Just _ -> empty,
124                     semi ]
125           last (G.LastReturn) = ppr (CmmReturn args)
126           last (G.LastJump e) = ppr (CmmJump e args)
127           last l = ppr (G.CopyOut conv args) $$ ppr l
128           ppr_target (CmmLit lit) = pprLit lit
129           ppr_target fn'          = parens (ppr fn')
130           commafy xs = hsep $ punctuate comma xs