change the zipper representation of calls
[ghc-hetmet.git] / compiler / cmm / CmmCvt.hs
1 {-# LANGUAGE PatternGuards #-}
2 {-# OPTIONS -Wall -fno-warn-name-shadowing #-}
3
4 module CmmCvt
5   ( cmmToZgraph, cmmOfZgraph )
6 where
7
8 import Cmm
9 import CmmExpr
10 import MkZipCfgCmm hiding (CmmGraph)
11 import ZipCfgCmmRep -- imported for reverse conversion
12 import CmmZipUtil
13 import PprCmm()
14 import PprCmmZ()
15 import qualified ZipCfg as G
16
17 import FastString
18 import Outputable
19 import Panic
20 import UniqSet
21 import UniqSupply
22
23 import Maybe
24
25 cmmToZgraph :: GenCmm d h (ListGraph CmmStmt) -> UniqSM (GenCmm d h CmmGraph)
26 cmmOfZgraph :: GenCmm d h (CmmGraph)          ->         GenCmm d h (ListGraph CmmStmt)
27
28 cmmToZgraph = cmmMapGraphM toZgraph
29 cmmOfZgraph = cmmMapGraph  ofZgraph
30
31
32 toZgraph :: String -> ListGraph CmmStmt -> UniqSM CmmGraph
33 toZgraph _ (ListGraph []) = lgraphOfAGraph emptyAGraph
34 toZgraph fun_name g@(ListGraph (BasicBlock id ss : other_blocks)) = 
35            labelAGraph id $ mkStmts ss <*> foldr addBlock emptyAGraph other_blocks
36   where addBlock (BasicBlock id ss) g = mkLabel id   <*> mkStmts ss <*> g
37         mkStmts (CmmNop        : ss)  = mkNop        <*> mkStmts ss 
38         mkStmts (CmmComment s  : ss)  = mkComment s  <*> mkStmts ss
39         mkStmts (CmmAssign l r : ss)  = mkAssign l r <*> mkStmts ss
40         mkStmts (CmmStore  l r : ss)  = mkStore  l r <*> mkStmts ss
41         mkStmts (CmmCall (CmmCallee f conv) res args (CmmSafe srt) CmmMayReturn : ss) =
42                       mkCall       f conv res args srt <*> mkStmts ss 
43         mkStmts (CmmCall (CmmPrim {}) _ _ (CmmSafe _) _ : _) =
44             panic "safe call to a primitive CmmPrim CallishMachOp"
45         mkStmts (CmmCall f res args CmmUnsafe CmmMayReturn : ss) =
46                       mkUnsafeCall f res args     <*> mkStmts ss
47         mkStmts (CmmCondBranch e l : fbranch) =
48             mkCmmIfThenElse e (mkBranch l) (mkStmts fbranch)
49         mkStmts (last : []) = mkLast last
50         mkStmts []          = bad "fell off end"
51         mkStmts (_ : _ : _) = bad "last node not at end"
52         bad msg = pprPanic (msg ++ " in function " ++ fun_name) (ppr g)
53         mkLast (CmmCall (CmmCallee f conv) []     args _ CmmNeverReturns) =
54             mkFinalCall f conv args
55         mkLast (CmmCall (CmmPrim {}) _ _ _ CmmNeverReturns) =
56             panic "Call to CmmPrim never returns?!"
57         mkLast (CmmSwitch scrutinee table) = mkSwitch scrutinee table
58         mkLast (CmmJump tgt args)          = mkJump tgt args
59         mkLast (CmmReturn ress)            = mkReturn ress
60         mkLast (CmmBranch tgt)             = mkBranch tgt
61         mkLast (CmmCall _f (_:_) _args _ CmmNeverReturns) =
62                    panic "Call never returns but has results?!"
63         mkLast _ = panic "fell off end of block"
64
65 ofZgraph :: CmmGraph -> ListGraph CmmStmt
66 ofZgraph g = ListGraph $ swallow blocks
67     where blocks = G.postorder_dfs g
68           -- | the next two functions are hooks on which to hang debugging info
69           extend_entry stmts = stmts
70           extend_block _id stmts = stmts
71           _extend_entry stmts = scomment showblocks : scomment cscomm : stmts
72           showblocks = "LGraph has " ++ show (length blocks) ++ " blocks:" ++
73                        concat (map (\(G.Block id _) -> " " ++ show id) blocks)
74           cscomm = "Call successors are" ++
75                    (concat $ map (\id -> " " ++ show id) $ uniqSetToList call_succs)
76           swallow [] = []
77           swallow (G.Block id t : rest) = tail id [] Nothing t rest
78           tail id prev' out (G.ZTail (CopyOut conv actuals) t) rest =
79               case out of
80                 Nothing -> tail id prev' (Just (conv, actuals)) t rest
81                 Just _ -> panic "multiple CopyOut nodes in one basic block"
82           tail id prev' out (G.ZTail m t) rest = tail id (mid m : prev') out t rest
83           tail id prev' out (G.ZLast G.LastExit)      rest = exit id prev' out rest
84           tail id prev' out (G.ZLast (G.LastOther l)) rest = last id prev' out l rest
85           mid (MidNop)        = CmmNop
86           mid (MidComment s)  = CmmComment s
87           mid (MidAssign l r) = CmmAssign l r
88           mid (MidStore  l r) = CmmStore  l r
89           mid (MidUnsafeCall f ress args) = CmmCall f ress args CmmUnsafe CmmMayReturn
90           mid m@(CopyOut {})  = pcomment (ppr m)
91           mid m@(CopyIn {})   = pcomment (ppr m <+> text "(proc point)")
92           pcomment p = scomment $ showSDoc p
93           block' id prev'
94               | id == G.lg_entry g = BasicBlock id $ extend_entry    (reverse prev')
95               | otherwise          = BasicBlock id $ extend_block id (reverse prev')
96           last id prev' out l n =
97             let endblock stmt = block' id (stmt : prev') : swallow n in
98             case l of
99               LastBranch _ (_:_) -> panic "unrepresentable branch"
100               LastBranch tgt [] ->
101                   case n of
102                     G.Block id' t : bs
103                         | tgt == id', unique_pred id' 
104                         -> tail id prev' out t bs -- optimize out redundant labels
105                     _ -> if isNothing out then endblock (CmmBranch tgt)
106                          else pprPanic "can't convert LGraph with pending CopyOut"
107                                   (ppr g)
108               LastCondBranch expr tid fid ->
109                 if isJust out then pprPanic "CopyOut before conditional branch" (ppr g)
110                 else
111                   case n of
112                     G.Block id' t : bs
113                       | id' == fid, unique_pred id' ->
114                                  tail id (CmmCondBranch expr tid : prev') Nothing t bs
115                       | id' == tid, unique_pred id',
116                         Just e' <- maybeInvertCmmExpr expr ->
117                                  tail id (CmmCondBranch e'   fid : prev') Nothing t bs
118                     _ -> let instrs' = CmmBranch fid : CmmCondBranch expr tid : prev'
119                          in block' id instrs' : swallow n
120               LastJump expr params -> endblock $ CmmJump expr params 
121               LastReturn params    -> endblock $ CmmReturn params
122               LastSwitch arg ids   -> endblock $ CmmSwitch arg $ ids
123               LastCall e cont
124                   | Just (conv, args) <- out
125                   -> let tgt = CmmCallee e (conv_to_cconv conv) in
126                      case cont of
127                        Nothing ->
128                            endblock $ CmmCall tgt [] args CmmUnsafe CmmNeverReturns
129                        Just k
130                          | G.Block id' (G.ZTail (CopyIn _ ress srt) t) : bs <- n,
131                            id' == k, unique_pred k
132                          -> let call = CmmCall tgt ress args (CmmSafe srt) CmmMayReturn
133                             in  tail id (call : prev') Nothing t bs
134                          | G.Block id' t : bs <- n, id' == k, unique_pred k
135                          -> let (ress, srt) = findCopyIn t
136                                 call = CmmCall tgt ress args (CmmSafe srt) CmmMayReturn
137                                 delayed = scomment "delayed CopyIn follows prev. call"
138                             in  tail id (delayed : call : prev') Nothing t bs
139                          | otherwise -> panic "unrepairable call"
140                   | otherwise -> panic "call with no CopyOut"
141           findCopyIn (G.ZTail (CopyIn _ ress srt) _) = (ress, srt)
142           findCopyIn (G.ZTail _ t) = findCopyIn t
143           findCopyIn (G.ZLast _) = panic "missing CopyIn after call"
144           exit id prev' out n = -- highly irregular (assertion violation?)
145               let endblock stmt = block' id (stmt : prev') : swallow n in
146               case n of [] -> endblock (scomment "procedure falls off end")
147                         G.Block id' t : bs -> 
148                             if unique_pred id' then
149                                 tail id (scomment "went thru exit" : prev') out t bs 
150                             else
151                                 endblock (CmmBranch id')
152           conv_to_cconv (ConventionStandard c _) = c
153           conv_to_cconv (ConventionPrivate {}) =
154               panic "tried to convert private calling convention back to Cmm"
155           preds = zipPreds g
156           single_preds =
157               let add b single =
158                     let id = G.blockId b
159                     in  case G.lookupBlockEnv preds id of
160                           Nothing -> single
161                           Just s -> if sizeUniqSet s == 1 then
162                                         G.extendBlockSet single id
163                                     else single
164               in  G.fold_blocks add G.emptyBlockSet g
165           unique_pred id = G.elemBlockSet id single_preds
166           call_succs = 
167               let add b succs =
168                       case G.last (G.unzip b) of
169                         G.LastOther (LastCall _ (Just id)) -> extendBlockSet succs id
170                         _ -> succs
171               in  G.fold_blocks add emptyBlockSet g
172           _is_call_succ id = elemBlockSet id call_succs
173
174 scomment :: String -> CmmStmt
175 scomment s = CmmComment $ mkFastString s