X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fcmm%2FZipCfg.hs;h=f07d2fa56e84b268b2d41ba973369648d9900ee0;hb=4c6a3f787abcaed009a574196d82237d9ae64fc8;hp=ec2368fb57781c10058ca6448a521ee6cdf0c56a;hpb=f74d318db9db0b95eb4f41e29a3bea43097ae9d5;p=ghc-hetmet.git diff --git a/compiler/cmm/ZipCfg.hs b/compiler/cmm/ZipCfg.hs index ec2368f..f07d2fa 100644 --- a/compiler/cmm/ZipCfg.hs +++ b/compiler/cmm/ZipCfg.hs @@ -1,7 +1,6 @@ -{-# LANGUAGE ScopedTypeVariables #-} module ZipCfg ( -- These data types and names are carefully thought out - BlockId(..) -- ToDo: BlockId should be abstract, but it isn't yet + BlockId(..), mkBlockId -- ToDo: BlockId should be abstract, but it isn't yet , BlockEnv, emptyBlockEnv, lookupBlockEnv, extendBlockEnv, insertBlock, mkBlockEnv , BlockSet, emptyBlockSet, elemBlockSet, extendBlockSet, mkBlockSet , Graph(..), LGraph(..), FGraph(..) @@ -14,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, mapM_blocks , postorder_dfs, postorder_dfs_from, postorder_dfs_from_except , fold_layout , fold_blocks @@ -22,7 +21,7 @@ module ZipCfg , pprLgraph, pprGraph - , entry -- exported for the convenience of ZipDataflow, at least for now + , entry -- exported for the convenience of ZipDataflow0, at least for now {- -- the following functions might one day be useful and can be found @@ -38,6 +37,8 @@ where #include "HsVersions.h" +import CmmExpr ( UserOfLocalRegs(..) ) --for an instance + import Outputable hiding (empty) import Panic import Unique @@ -76,7 +77,7 @@ the data constructor 'LastExit'. A graph may contain at most one 'LastExit' node, and a graph representing a full procedure should not contain any 'LastExit' nodes. 'LastExit' nodes are used only to splice graphs together, either during graph construction (see module 'MkZipCfg') -or during optimization (see module 'ZipDataflow'). +or during optimization (see module 'ZipDataflow0'). A graph is parameterized over the types of middle and last nodes. Each of these types will typically be instantiated with a subset of C-- statements @@ -141,6 +142,14 @@ data ZLast l -- so we don't want to pollute the 'l' type parameter with it | LastOther l +--So that we don't have orphan instances, this goes here or in CmmExpr. +--At least UserOfLocalRegs (ZLast Last) is needed (Last defined elsewhere), +--but there's no need for non-Haskell98 instances for that. +instance UserOfLocalRegs a => UserOfLocalRegs (ZLast a) where + foldRegsUsed f z (LastOther l) = foldRegsUsed f z l + foldRegsUsed _f z LastExit = z + + data ZHead m = ZFirst BlockId | ZHead (ZHead m) m -- ZHead is a (reversed) sequence of middle nodes labeled by a BlockId data ZTail m l = ZLast (ZLast l) | ZTail m (ZTail m l) @@ -267,13 +276,16 @@ 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' +map_blocks :: (Block m l -> Block m' l') -> LGraph m l -> LGraph m' l' +mapM_blocks :: Monad mm + => (Block m l -> mm (Block m' l')) -> LGraph m l -> mm (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: @@ -429,41 +441,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 @@ -485,6 +468,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 @@ -509,6 +497,14 @@ map_nodes idm middle last (LGraph eid blocks) = LGraph (idm eid) (mapUFM block b tail (ZLast LastExit) = ZLast LastExit tail (ZLast (LastOther l)) = ZLast (LastOther (last l)) + +mapM_blocks f (LGraph eid blocks) = blocks' >>= return . LGraph eid + where blocks' = + foldUFM (\b mblocks -> do { blocks <- mblocks + ; b <- f b + ; return $ insertBlock b blocks }) + (return emptyBlockEnv) blocks + fold_blocks f z (LGraph _ blocks) = foldUFM f z blocks of_block_list e blocks = LGraph e $ foldr insertBlock emptyBlockEnv blocks @@ -619,12 +615,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' @@ -653,6 +649,9 @@ newtype BlockId = BlockId Unique instance Uniquable BlockId where getUnique (BlockId u) = u +mkBlockId :: Unique -> BlockId +mkBlockId uniq = BlockId uniq + instance Show BlockId where show (BlockId u) = show u @@ -689,6 +688,9 @@ mkBlockSet = mkUniqSet instance (Outputable m, Outputable l) => Outputable (ZTail m l) where ppr = pprTail +instance (Outputable m, Outputable l, LastNode l) => Outputable (LGraph m l) where + ppr = pprLgraph + pprTail :: (Outputable m, Outputable l) => ZTail m l -> SDoc pprTail (ZTail m t) = ppr m $$ ppr t pprTail (ZLast LastExit) = text "" @@ -705,5 +707,3 @@ pprGraph (Graph tail blockenv) = where pprBlock (Block id tail) = ppr id <> colon $$ ppr tail blocks = postorder_dfs_from blockenv tail -_unused :: FS.FastString -_unused = undefined