1 {-# LANGUAGE PatternGuards #-}
4 ( cmmToZgraph, cmmOfZgraph )
9 import MkZipCfgCmm hiding (CmmGraph)
10 import ZipCfgCmmRep -- imported for reverse conversion
13 import qualified ZipCfg as G
20 cmmToZgraph :: GenCmm d h (ListGraph CmmStmt) -> UniqSM (GenCmm d h (CmmStackInfo, CmmGraph))
21 cmmOfZgraph :: GenCmm d h (CmmStackInfo, CmmGraph) -> GenCmm d h (ListGraph CmmStmt)
23 cmmToZgraph (Cmm tops) = liftM Cmm $ mapM mapTop tops
24 where mapTop (CmmProc h l args g) =
25 toZgraph (showSDoc $ ppr l) args g >>= return . CmmProc h l args
26 mapTop (CmmData s ds) = return $ CmmData s ds
27 cmmOfZgraph = cmmMapGraph (ofZgraph . snd)
29 toZgraph :: String -> CmmFormals -> ListGraph CmmStmt -> UniqSM (CmmStackInfo, CmmGraph)
30 toZgraph _ _ (ListGraph []) =
31 do g <- lgraphOfAGraph emptyAGraph
32 return ((0, Nothing), g)
33 toZgraph fun_name args g@(ListGraph (BasicBlock id ss : other_blocks)) =
34 let (offset, entry) = mkEntry id NativeNodeCall args in
35 do g <- labelAGraph id $
36 entry <*> mkStmts ss <*> foldr addBlock emptyAGraph other_blocks
37 return ((offset, Nothing), g)
38 where addBlock (BasicBlock id ss) g =
39 mkLabel id <*> mkStmts ss <*> g
40 updfr_sz = 0 -- panic "upd frame size lost in cmm conversion"
41 mkStmts (CmmNop : ss) = mkNop <*> mkStmts ss
42 mkStmts (CmmComment s : ss) = mkComment s <*> mkStmts ss
43 mkStmts (CmmAssign l r : ss) = mkAssign l r <*> mkStmts ss
44 mkStmts (CmmStore l r : ss) = mkStore l r <*> mkStmts ss
45 mkStmts (CmmCall (CmmCallee f conv) res args (CmmSafe _) CmmMayReturn : ss) =
46 mkCall f (conv', conv') (map hintlessCmm res) (map hintlessCmm args) updfr_sz
48 where conv' = Foreign (ForeignConvention conv [] []) -- JD: DUBIOUS
49 mkStmts (CmmCall (CmmPrim {}) _ _ (CmmSafe _) _ : _) =
50 panic "safe call to a primitive CmmPrim CallishMachOp"
51 mkStmts (CmmCall f res args CmmUnsafe CmmMayReturn : ss) =
52 mkUnsafeCall (convert_target f res args)
53 (strip_hints res) (strip_hints args)
55 mkStmts (CmmCondBranch e l : fbranch) =
56 mkCmmIfThenElse e (mkBranch l) (mkStmts fbranch)
57 mkStmts (last : []) = mkLast last
58 mkStmts [] = bad "fell off end"
59 mkStmts (_ : _ : _) = bad "last node not at end"
60 bad msg = pprPanic (msg ++ " in function " ++ fun_name) (ppr g)
61 mkLast (CmmCall (CmmCallee f conv) [] args _ CmmNeverReturns) =
62 mkFinalCall f conv (map hintlessCmm args) updfr_sz
63 mkLast (CmmCall (CmmPrim {}) _ _ _ CmmNeverReturns) =
64 panic "Call to CmmPrim never returns?!"
65 mkLast (CmmSwitch scrutinee table) = mkSwitch scrutinee table
66 -- SURELY, THESE HINTLESS ARGS ARE WRONG AND WILL BE FIXED WHEN CALLING
67 -- CONVENTIONS ARE HONORED?
68 mkLast (CmmJump tgt args) = mkJump tgt (map hintlessCmm args) updfr_sz
69 mkLast (CmmReturn ress) =
70 mkReturnSimple (map hintlessCmm ress) updfr_sz
71 mkLast (CmmBranch tgt) = mkBranch tgt
72 mkLast (CmmCall _f (_:_) _args _ CmmNeverReturns) =
73 panic "Call never returns but has results?!"
74 mkLast _ = panic "fell off end of block"
76 strip_hints :: [CmmHinted a] -> [a]
77 strip_hints = map hintlessCmm
79 convert_target :: CmmCallTarget -> HintedCmmFormals -> HintedCmmActuals -> MidCallTarget
80 convert_target (CmmCallee e cc) ress args = ForeignTarget e (ForeignConvention cc (map cmmHint args) (map cmmHint ress))
81 convert_target (CmmPrim op) _ress _args = PrimTarget op
83 add_hints :: Convention -> ValueDirection -> [a] -> [CmmHinted a]
84 add_hints conv vd args = zipWith CmmHinted args (get_hints conv vd)
86 get_hints :: Convention -> ValueDirection -> [ForeignHint]
87 get_hints (Foreign (ForeignConvention _ hints _)) Arguments = hints
88 get_hints (Foreign (ForeignConvention _ _ hints)) Results = hints
89 get_hints _other_conv _vd = repeat NoHint
91 get_conv :: MidCallTarget -> Convention
92 get_conv (PrimTarget _) = NativeNodeCall -- JD: SUSPICIOUS
93 get_conv (ForeignTarget _ fc) = Foreign fc
95 cmm_target :: MidCallTarget -> CmmCallTarget
96 cmm_target (PrimTarget op) = CmmPrim op
97 cmm_target (ForeignTarget e (ForeignConvention cc _ _)) = CmmCallee e cc
99 ofZgraph :: CmmGraph -> ListGraph CmmStmt
100 ofZgraph g = ListGraph $ swallow blocks
101 where blocks = G.postorder_dfs g
102 -- | the next two functions are hooks on which to hang debugging info
103 extend_entry stmts = stmts
104 extend_block _id stmts = stmts
105 _extend_entry stmts = scomment showblocks : scomment cscomm : stmts
106 showblocks = "LGraph has " ++ show (length blocks) ++ " blocks:" ++
107 concat (map (\(G.Block id _) -> " " ++ show id) blocks)
108 cscomm = "Call successors are" ++
109 (concat $ map (\id -> " " ++ show id) $ blockSetToList call_succs)
111 swallow (G.Block id t : rest) = tail id [] t rest
112 tail id prev' (G.ZTail m t) rest = tail id (mid m : prev') t rest
113 tail id prev' (G.ZLast G.LastExit) rest = exit id prev' rest
114 tail id prev' (G.ZLast (G.LastOther l)) rest = last id prev' l rest
115 mid (MidComment s) = CmmComment s
116 mid (MidAssign l r) = CmmAssign l r
117 mid (MidStore l r) = CmmStore l r
118 mid (MidForeignCall _ (PrimTarget MO_Touch) _ _) = CmmNop
119 mid (MidForeignCall _ target ress args)
120 = CmmCall (cmm_target target)
121 (add_hints conv Results ress)
122 (add_hints conv Arguments args)
123 CmmUnsafe CmmMayReturn
125 conv = get_conv target
127 | id == G.lg_entry g = BasicBlock id $ extend_entry (reverse prev')
128 | otherwise = BasicBlock id $ extend_block id (reverse prev')
130 let endblock stmt = block' id (stmt : prev') : swallow n in
134 -- THIS OPT IS WRONG -- LABELS CAN SHOW UP ELSEWHERE IN THE GRAPH
135 --G.Block id' _ t : bs
136 -- | tgt == id', unique_pred id'
137 -- -> tail id prev' t bs -- optimize out redundant labels
138 _ -> endblock (CmmBranch tgt)
139 LastCondBranch expr tid fid ->
142 -- It would be better to handle earlier, but we still must
143 -- generate correct code here.
144 | id' == fid, tid == fid, unique_pred id' ->
146 | id' == fid, unique_pred id' ->
147 tail id (CmmCondBranch expr tid : prev') t bs
148 | id' == tid, unique_pred id',
149 Just e' <- maybeInvertCmmExpr expr ->
150 tail id (CmmCondBranch e' fid : prev') t bs
151 _ -> let instrs' = CmmBranch fid : CmmCondBranch expr tid : prev'
152 in block' id instrs' : swallow n
153 LastSwitch arg ids -> endblock $ CmmSwitch arg $ ids
154 LastCall e _ _ _ _ -> endblock $ CmmJump e []
155 exit id prev' n = -- highly irregular (assertion violation?)
156 let endblock stmt = block' id (stmt : prev') : swallow n in
157 case n of [] -> endblock (scomment "procedure falls off end")
158 G.Block id' t : bs ->
159 if unique_pred id' then
160 tail id (scomment "went thru exit" : prev') t bs
162 endblock (CmmBranch id')
167 in case lookupBlockEnv preds id of
169 Just s -> if sizeBlockSet s == 1 then
170 extendBlockSet single id
172 in G.fold_blocks add emptyBlockSet g
173 unique_pred id = elemBlockSet id single_preds
176 case G.last (G.unzip b) of
177 G.LastOther (LastCall _ (Just id) _ _ _) ->
178 extendBlockSet succs id
180 in G.fold_blocks add emptyBlockSet g
181 _is_call_succ id = elemBlockSet id call_succs
183 scomment :: String -> CmmStmt
184 scomment s = CmmComment $ mkFastString s