module Data.LLVM.CFG
( CFG(..)
, BB
, BBId
, blockId
, blockName
, buildCFG
, dummyExitName
)
where
#if !(MIN_VERSION_base(4,8,0))
import Control.Applicative
#endif
import Control.Arrow
import qualified Data.Graph.Inductive.Query.Dominators as Dom
import qualified Data.Graph.Inductive as G
import qualified Data.Map as M
import MonadLib (runId)
import Text.LLVM hiding (BB)
import qualified Text.LLVM.Labels as L
newtype BBId = BBId { unBBId :: G.Node } deriving (Eq)
type BB = BasicBlock' (BBId, BlockLabel)
data CFG = CFG
{ cfgGraph :: G.Gr BB ()
, entryId :: BBId
, exitId :: BBId
, allBBs :: [BB]
, bbById :: BBId -> BB
, asId :: BlockLabel -> BBId
, asName :: BBId -> BlockLabel
, bbPreds :: BBId -> [BBId]
, bbSuccs :: BBId -> [BBId]
, dom :: BBId -> BBId -> Bool
, idom :: BBId -> Maybe BBId
, pdom :: BBId -> BBId -> Bool
, ipdom :: BBId -> Maybe BBId
, pdoms :: [(BBId, [BBId])]
}
dummyExitName :: String
dummyExitName = "_dummy_exit"
buildCFG :: [BasicBlock] -> CFG
buildCFG bs = cfg
where
cfg = CFG
{ cfgGraph = gr
, entryId = BBId 0
, exitId = BBId (either id id exit)
, allBBs = getBBs gr (G.nodes gr)
, bbById = \(BBId x) ->
case bbFromCtx <$> fst (G.match x gr) of
Nothing -> error "buildCFG: bbById: invalid BBId"
Just bb -> bb
, asId = \ident ->
case BBId <$> M.lookup ident nodeByName of
Nothing -> error "buildCFG: asId: invalid ident"
Just bbid -> bbid
, asName = \bbid -> blockName $ bbById cfg bbid
, bbPreds = \(BBId x) -> BBId <$> G.pre gr x
, bbSuccs = \(BBId x) -> BBId <$> G.suc gr x
, dom = \(BBId x) (BBId y) -> lkupDom domInfo x y
, idom = \(BBId x) -> BBId <$> lookup x idomInfo
, pdom = \(BBId x) (BBId y) -> lkupDom pdomInfo x y
, ipdom = \(BBId x) -> BBId <$> lookup x ipdomInfo
, pdoms = map (BBId *** map BBId . reverse . drop 1) pdomInfo
}
cdom g (BBId root) = (Dom.dom g root, Dom.iDom g root)
(domInfo, idomInfo) = cdom gr (entryId cfg)
(pdomInfo, ipdomInfo) = cdom (G.grev gr) (exitId cfg)
lkupDom info x y = maybe False id (elem x <$> lookup y info)
(exit, gr) = stitchDummyExit lab (G.mkGraph nodes' edges')
where lab n = BasicBlock (Just (BBId n, Named $ Ident dummyExitName))
[Effect Unreachable []]
nodes' = map (nodeId &&& id) bs'
edges' = concatMap bbOutEdges bs'
bbOutEdges :: BB -> [G.LEdge ()]
bbOutEdges bb = edgesTo (brTargets bb)
where
srcId = nodeId bb
edgesTo = map (\(BBId tgt,_) -> srcId `to` tgt)
bs' :: [BB]
(bbIds, bs', _, _) = foldr relabel (M.empty, [], length bs 1, 0) bs
where
relabel (BasicBlock mid stmts) (mp, acc, n, s :: Int) =
let (s', nm) = case mid of
Nothing -> (s + 1, Named $ Ident $ "__anon_" ++ show s)
Just nm' -> (s, nm')
bbid = (BBId n, nm)
in
( M.insert nm bbid mp
, BasicBlock (Just bbid) (fixLabels stmts) : acc
, n 1
, s'
)
nodeByName = fmap (\(BBId n, _) -> n) bbIds
fixLabels stmts = runId (mapM (L.relabel f) stmts)
where
f _ lab = return (bbIds M.! lab)
bbFromCtx :: G.Context BB () -> BB
bbFromCtx (_, _, bb, _) = bb
to :: G.Node -> G.Node -> G.LEdge ()
u `to` v = (u, v, ())
requireLabel :: BB -> (BBId, BlockLabel)
requireLabel bb =
case bbLabel bb of
Just lab -> lab
Nothing -> error ("requireLabel: basic block without a label\n" ++ show bb)
blockId :: BB -> BBId
blockId = fst . requireLabel
blockName :: BB -> BlockLabel
blockName = snd . requireLabel
nodeId :: BB -> G.Node
nodeId = unBBId . blockId
getBBs :: G.Gr BB () -> [G.Node] -> [BB]
getBBs gr ns =
case mapM (G.lab gr) ns of
Just bbs -> bbs
Nothing -> error "internal: encountered unlabeled node"
newNode :: G.Graph gr => gr a b -> G.Node
newNode = head . G.newNodes 1
exitNodes :: G.DynGraph gr => gr a b -> [G.Node]
exitNodes gr = map G.node' $ G.gsel (null . G.suc gr . G.node') gr
stitchDummyExit :: G.DynGraph gr =>
(G.Node -> a) -> gr a () -> (Either G.Node G.Node, gr a ())
stitchDummyExit exitLabelF gr = case exitNodes gr of
[] -> error "internal: input graph contains no exit nodes"
[n] -> (Left n, gr)
exits ->
let new = newNode gr
!g0 = G.insNode (new, exitLabelF new) gr
!g1 = foldr G.insEdge g0 $ map (`to` new) exits
in (Right new, g1)
instance Show CFG where
show cfg = unlines [ "Entry : " ++ show (entryId cfg)
, "Exit : " ++ show (exitId cfg)
, "Graph : " ++ ( unlines
. map (\s -> replicate 8 ' ' ++ s)
. lines
$ show (cfgGraph cfg)
)
]
instance Show BBId where show (BBId n) = "BB#" ++ show n