module GHC.CmmToAsm.Utils
   ( topInfoTable
   , entryBlocks
   )
where

import GHC.Prelude

import GHC.Cmm.BlockId
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm.Dataflow.Label
import GHC.Cmm hiding (topInfoTable)

-- | Returns the info table associated with the CmmDecl's entry point,
-- if any.
topInfoTable :: GenCmmDecl a (LabelMap i) (ListGraph b) -> Maybe i
topInfoTable :: forall a i b. GenCmmDecl a (LabelMap i) (ListGraph b) -> Maybe i
topInfoTable (CmmProc LabelMap i
infos CLabel
_ [GlobalReg]
_ (ListGraph (GenBasicBlock b
b:[GenBasicBlock b]
_)))
  = forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup (forall i. GenBasicBlock i -> BlockId
blockId GenBasicBlock b
b) LabelMap i
infos
topInfoTable GenCmmDecl a (LabelMap i) (ListGraph b)
_
  = forall a. Maybe a
Nothing

-- | Return the list of BlockIds in a CmmDecl that are entry points
-- for this proc (i.e. they may be jumped to from outside this proc).
entryBlocks :: GenCmmDecl a (LabelMap i) (ListGraph b) -> [BlockId]
entryBlocks :: forall a i b. GenCmmDecl a (LabelMap i) (ListGraph b) -> [BlockId]
entryBlocks (CmmProc LabelMap i
info CLabel
_ [GlobalReg]
_ (ListGraph [GenBasicBlock b]
code)) = [KeyOf LabelMap]
entries
  where
        infos :: [KeyOf LabelMap]
infos = forall (map :: * -> *) a. IsMap map => map a -> [KeyOf map]
mapKeys LabelMap i
info
        entries :: [KeyOf LabelMap]
entries = case [GenBasicBlock b]
code of
                    [] -> [KeyOf LabelMap]
infos
                    BasicBlock BlockId
entry [b]
_ : [GenBasicBlock b]
_ -- first block is the entry point
                       | BlockId
entry forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [KeyOf LabelMap]
infos -> [KeyOf LabelMap]
infos
                       | Bool
otherwise          -> BlockId
entry forall a. a -> [a] -> [a]
: [KeyOf LabelMap]
infos
entryBlocks GenCmmDecl a (LabelMap i) (ListGraph b)
_ = []