module Hoopl.Graph
( Body
, Graph
, Graph'(..)
, NonLocal(..)
, addBlock
, bodyList
, emptyBody
, labelsDefined
, mapGraph
, mapGraphBlocks
, revPostorderFrom
) where
import GhcPrelude
import Util
import Hoopl.Label
import Hoopl.Block
import Hoopl.Collections
type Body n = LabelMap (Block n C C)
type Body' block (n :: * -> * -> *) = LabelMap (block n C C)
class NonLocal thing where
entryLabel :: thing C x -> Label
successors :: thing e C -> [Label]
instance NonLocal n => NonLocal (Block n) where
entryLabel (BlockCO f _) = entryLabel f
entryLabel (BlockCC f _ _) = entryLabel f
successors (BlockOC _ n) = successors n
successors (BlockCC _ _ n) = successors n
emptyBody :: Body' block n
emptyBody = mapEmpty
bodyList :: Body' block n -> [(Label,block n C C)]
bodyList body = mapToList body
addBlock
:: (NonLocal block, HasDebugCallStack)
=> block C C -> LabelMap (block C C) -> LabelMap (block C C)
addBlock block body = mapAlter add lbl body
where
lbl = entryLabel block
add Nothing = Just block
add _ = error $ "duplicate label " ++ show lbl ++ " in graph"
type Graph = Graph' Block
data Graph' block (n :: * -> * -> *) e x where
GNil :: Graph' block n O O
GUnit :: block n O O -> Graph' block n O O
GMany :: MaybeO e (block n O C)
-> Body' block n
-> MaybeO x (block n C O)
-> Graph' block n e x
mapGraph :: (forall e x. n e x -> n' e x) -> Graph n e x -> Graph n' e x
mapGraph f = mapGraphBlocks (mapBlock f)
mapGraphBlocks :: forall block n block' n' e x .
(forall e x . block n e x -> block' n' e x)
-> (Graph' block n e x -> Graph' block' n' e x)
mapGraphBlocks f = map
where map :: Graph' block n e x -> Graph' block' n' e x
map GNil = GNil
map (GUnit b) = GUnit (f b)
map (GMany e b x) = GMany (fmap f e) (mapMap f b) (fmap f x)
labelsDefined :: forall block n e x . NonLocal (block n) => Graph' block n e x
-> LabelSet
labelsDefined GNil = setEmpty
labelsDefined (GUnit{}) = setEmpty
labelsDefined (GMany _ body x) = mapFoldlWithKey addEntry (exitLabel x) body
where addEntry :: forall a. LabelSet -> ElemOf LabelSet -> a -> LabelSet
addEntry labels label _ = setInsert label labels
exitLabel :: MaybeO x (block n C O) -> LabelSet
exitLabel NothingO = setEmpty
exitLabel (JustO b) = setSingleton (entryLabel b)
revPostorderFrom
:: forall block. (NonLocal block)
=> LabelMap (block C C) -> Label -> [block C C]
revPostorderFrom graph start = go start_worklist setEmpty []
where
start_worklist = lookup_for_descend start Nil
go :: DfsStack (block C C) -> LabelSet -> [block C C] -> [block C C]
go Nil !_ !result = result
go (ConsMark block rest) !wip_or_done !result =
go rest wip_or_done (block : result)
go (ConsTodo block rest) !wip_or_done !result
| entryLabel block `setMember` wip_or_done = go rest wip_or_done result
| otherwise =
let new_worklist =
foldr lookup_for_descend
(ConsMark block rest)
(successors block)
in go new_worklist (setInsert (entryLabel block) wip_or_done) result
lookup_for_descend :: Label -> DfsStack (block C C) -> DfsStack (block C C)
lookup_for_descend label wl
| Just b <- mapLookup label graph = ConsTodo b wl
| otherwise =
error $ "Label that doesn't have a block?! " ++ show label
data DfsStack a = ConsTodo a (DfsStack a) | ConsMark a (DfsStack a) | Nil