X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fcmm%2FZipCfg.hs;h=be5f97cd70873e9d70adb5546d2fea4bf9c376f2;hb=78a980177f263e5c59a7a71e844c32ee5bf735a7;hp=b3973db7c8f422e8e9dc5f62167919041c17fa2e;hpb=4559ed114a3c16ee6840abc503c5438d799505f1;p=ghc-hetmet.git diff --git a/compiler/cmm/ZipCfg.hs b/compiler/cmm/ZipCfg.hs index b3973db..be5f97c 100644 --- a/compiler/cmm/ZipCfg.hs +++ b/compiler/cmm/ZipCfg.hs @@ -1,8 +1,6 @@ -{-# LANGUAGE ScopedTypeVariables #-} module ZipCfg ( -- These data types and names are carefully thought out - BlockId(..), freshBlockId -- ToDo: BlockId should be abstract, - -- but it isn't yet + BlockId(..) -- ToDo: BlockId should be abstract, but it isn't yet , BlockEnv, emptyBlockEnv, lookupBlockEnv, extendBlockEnv, insertBlock, mkBlockEnv , BlockSet, emptyBlockSet, elemBlockSet, extendBlockSet, mkBlockSet , Graph(..), LGraph(..), FGraph(..) @@ -15,7 +13,7 @@ module ZipCfg , blockId, zip, unzip, last, goto_end, zipht, tailOfLast , splice_tail, splice_head, splice_head_only', splice_head' , of_block_list, to_block_list - , map_nodes + , map_blocks, map_nodes , postorder_dfs, postorder_dfs_from, postorder_dfs_from_except , fold_layout , fold_blocks @@ -44,7 +42,6 @@ import Panic import Unique import UniqFM import UniqSet -import UniqSupply import Maybe import Prelude hiding (zip, unzip, last) @@ -100,13 +97,13 @@ increasing complexity, they are: There are three types because each type offers a slightly different invariant or cost model. - * The distinguished entry of a Graph has no label. Because labels must - be unique, acquiring one requires a monadic operation ('freshBlockId'). - The primary advantage of the Graph representation is that we can build - a small Graph purely functionally, without entering a monad. For - example, during optimization we can easily rewrite a single middle - node into a Graph containing a sequence of two middle nodes followed by - LastExit. + * The distinguished entry of a Graph has no label. Because labels must be + unique, acquiring one requires a supply of Unique labels (BlockId's). + The primary advantage of the Graph representation is that we can build a + small Graph purely functionally, without needing a fresh BlockId or + Unique. For example, during optimization we can easily rewrite a single + middle node into a Graph containing a sequence of two middle nodes + followed by LastExit. * In an LGraph, every basic block is labelled. The primary advantage of this representation is its simplicity: each basic block can be treated @@ -168,11 +165,6 @@ data FGraph m l = FGraph { fg_entry :: BlockId ---- Utility functions --- --- | The string argument to 'freshBlockId' was originally helpful in debugging the Quick C-- --- compiler, so I have kept it here even though at present it is thrown away at --- this spot---there's no reason a BlockId couldn't one day carry a string. -freshBlockId :: String -> UniqSM BlockId - blockId :: Block m l -> BlockId zip :: ZBlock m l -> Block m l unzip :: Block m l -> ZBlock m l @@ -274,11 +266,14 @@ fold_blocks :: (Block m l -> a -> a) -> a -> LGraph m l -> a map_nodes :: (BlockId -> BlockId) -> (m -> m') -> (l -> l') -> LGraph m l -> LGraph m' l' -- mapping includes the entry id! +map_blocks :: (Block m l -> Block m' l') -> LGraph m l -> LGraph m' l' + -- | These translation functions are speculative. I hope eventually -- they will be used in the native-code back ends ---NR -translate :: (m -> UniqSM (LGraph m' l')) -> - (l -> UniqSM (LGraph m' l')) -> - (LGraph m l -> UniqSM (LGraph m' l')) +translate :: Monad tm => + (m -> tm (LGraph m' l')) -> + (l -> tm (LGraph m' l')) -> + (LGraph m l -> tm (LGraph m' l')) {- -- | It's possible that another form of translation would be more suitable: @@ -336,8 +331,6 @@ instance LastNode l => HavingSuccessors (ZTail m l) where blockId (Block id _) = id -freshBlockId _ = do { u <- getUniqueUs; return $ BlockId u } - -- | Convert block between forms. -- These functions are tail-recursive, so we can go as deep as we like -- without fear of stack overflow. @@ -436,41 +429,12 @@ single_exitg (Graph tail blocks) = foldUFM add (exit_count (lastTail tail)) bloc -- Better to geot [A,B,C,D] -postorder_dfs' :: LastNode l => LGraph m l -> [Block m l] -postorder_dfs' g@(LGraph _ blocks) = - let FGraph _ eblock _ = entry g - in vnode (zip eblock) (\acc _visited -> acc) [] emptyBlockSet - where - -- vnode :: - -- Block m l -> ([Block m l] -> BlockSet -> a) -> [Block m l] -> BlockSet -> a - vnode block@(Block id _) cont acc visited = - if elemBlockSet id visited then - cont acc visited - else - vchildren block (get_children block) cont acc (extendBlockSet visited id) - vchildren block bs cont acc visited = - let next children acc visited = - case children of [] -> cont (block : acc) visited - (b:bs) -> vnode b (next bs) acc visited - in next bs acc visited - get_children block = foldl add_id [] (succs block) - add_id rst id = case lookupBlockEnv blocks id of - Just b -> b : rst - Nothing -> rst - postorder_dfs g@(LGraph _ blockenv) = - let FGraph id eblock _ = entry g - dfs1 = zip eblock : - postorder_dfs_from_except blockenv eblock (unitUniqSet id) - dfs2 = postorder_dfs' g --- in ASSERT (map blockId dfs1 == map blockId dfs2) dfs2 - in if (map blockId dfs1 == map blockId dfs2) then dfs2 else panic "inconsistent DFS" - -postorder_dfs_from - :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> [Block m l] -postorder_dfs_from blocks b = postorder_dfs_from_except blocks b emptyBlockSet + let FGraph id eblock _ = entry g in + zip eblock : postorder_dfs_from_except blockenv eblock (unitUniqSet id) -postorder_dfs_from_except :: forall b m l . (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> BlockSet -> [Block m l] +postorder_dfs_from_except :: (HavingSuccessors b, LastNode l) + => BlockEnv (Block m l) -> b -> BlockSet -> [Block m l] postorder_dfs_from_except blocks b visited = vchildren (get_children b) (\acc _visited -> acc) [] visited where @@ -492,6 +456,11 @@ postorder_dfs_from_except blocks b visited = Just b -> b : rst Nothing -> rst +postorder_dfs_from + :: (HavingSuccessors b, LastNode l) => BlockEnv (Block m l) -> b -> [Block m l] +postorder_dfs_from blocks b = postorder_dfs_from_except blocks b emptyBlockSet + + -- | Slightly more complicated than the usual fold because we want to tell block -- 'b1' what its inline successor is going to be, so that if 'b1' ends with @@ -508,6 +477,8 @@ fold_layout f z g@(LGraph eid _) = fold (postorder_dfs g) z -- | The rest of the traversals are straightforward +map_blocks f (LGraph eid blocks) = LGraph eid (mapUFM f blocks) + map_nodes idm middle last (LGraph eid blocks) = LGraph (idm eid) (mapUFM block blocks) where block (Block id t) = Block (idm id) (tail t) tail (ZTail m t) = ZTail (middle m) (tail t) @@ -624,12 +595,12 @@ translate txm txl (LGraph eid blocks) = return $ LGraph eid blocks' where -- txblock :: - -- Block m l -> UniqSM (BlockEnv (Block m' l')) -> UniqSM (BlockEnv (Block m' l')) + -- Block m l -> tm (BlockEnv (Block m' l')) -> tm (BlockEnv (Block m' l')) txblock (Block id t) expanded = do blocks' <- expanded txtail (ZFirst id) t blocks' -- txtail :: ZHead m' -> ZTail m l -> BlockEnv (Block m' l') -> - -- UniqSM (BlockEnv (Block m' l')) + -- tm (BlockEnv (Block m' l')) txtail h (ZTail m t) blocks' = do m' <- txm m let (g, h') = splice_head h m'