never executed always true always false
    1 module GHC.CmmToAsm.Utils
    2    ( topInfoTable
    3    , entryBlocks
    4    )
    5 where
    6 
    7 import GHC.Prelude
    8 
    9 import GHC.Cmm.BlockId
   10 import GHC.Cmm.Dataflow.Collections
   11 import GHC.Cmm.Dataflow.Label
   12 import GHC.Cmm hiding (topInfoTable)
   13 
   14 -- | Returns the info table associated with the CmmDecl's entry point,
   15 -- if any.
   16 topInfoTable :: GenCmmDecl a (LabelMap i) (ListGraph b) -> Maybe i
   17 topInfoTable (CmmProc infos _ _ (ListGraph (b:_)))
   18   = mapLookup (blockId b) infos
   19 topInfoTable _
   20   = Nothing
   21 
   22 -- | Return the list of BlockIds in a CmmDecl that are entry points
   23 -- for this proc (i.e. they may be jumped to from outside this proc).
   24 entryBlocks :: GenCmmDecl a (LabelMap i) (ListGraph b) -> [BlockId]
   25 entryBlocks (CmmProc info _ _ (ListGraph code)) = entries
   26   where
   27         infos = mapKeys info
   28         entries = case code of
   29                     [] -> infos
   30                     BasicBlock entry _ : _ -- first block is the entry point
   31                        | entry `elem` infos -> infos
   32                        | otherwise          -> entry : infos
   33 entryBlocks _ = []