#if __GLASGOW_HASKELL__ >= 723
#endif
module Compiler.Hoopl.Passes.Dominator
  ( Doms, DPath(..), domPath, domEntry, domLattice, extendDom
  , DominatorNode(..), DominatorTree(..), tree
  , immediateDominators
  , domPass
  )
where
import Data.Maybe
import qualified Data.Set as Set
import Compiler.Hoopl
type Doms = WithBot DPath
domEntry :: Doms
domEntry = PElem (DPath [])
newtype DPath = DPath [Label]
  
  
  
instance Show DPath where
  show (DPath ls) = concat (foldr (\l path -> show l : " -> " : path) ["entry"] ls)
domPath :: Doms -> [Label]
domPath Bot = [] 
domPath (PElem (DPath ls)) = ls
extendDom :: Label -> DPath -> DPath
extendDom l (DPath ls) = DPath (l:ls)
domLattice :: DataflowLattice Doms
domLattice = addPoints "dominators" extend
extend :: JoinFun DPath
extend _ (OldFact (DPath l)) (NewFact (DPath l')) =
                                (changeIf (l `lengthDiffers` j), DPath j)
    where lx = filter (\elem -> Set.member elem common) l
          rx = filter (\elem -> Set.member elem common) l'
          common = Set.intersection (Set.fromList l) (Set.fromList l')
          j = [x | (x, y) <- zip lx rx, x == y]
          lengthDiffers [] [] = False
          lengthDiffers (_:xs) (_:ys) = lengthDiffers xs ys
          lengthDiffers [] (_:_) = True
          lengthDiffers (_:_) [] = True
domPass :: (NonLocal n, Monad m) => FwdPass m n Doms
domPass = FwdPass domLattice (mkFTransfer3 first (const id) distributeFact) noFwdRewrite
  where first n = fmap (extendDom $ entryLabel n)
data DominatorNode = Entry | Labelled Label
data DominatorTree = Dominates DominatorNode [DominatorTree]
tree :: [(Label, Doms)] -> DominatorTree
tree facts = Dominates Entry $ merge $ map reverse $ map mkList facts
   
   
   
   
   
  where merge lists = mapTree $ children $ filter (not . null) lists
        children = foldl addList noFacts
        addList :: FactBase [[Label]] -> [Label] -> FactBase [[Label]]
        addList map (x:xs) = mapInsert x (xs:existing) map
            where existing = fromMaybe [] $ lookupFact x map
        addList _ [] = error "this can't happen"
        mapTree :: FactBase [[Label]] -> [DominatorTree]
        mapTree map = [Dominates (Labelled x) (merge lists) |
                                                    (x, lists) <- mapToList map]
        mkList (l, doms) = l : domPath doms
instance Show DominatorTree where
  show = tree2dot
tree2dot :: DominatorTree -> String
tree2dot t = concat $ "digraph {\n" : dot t ["}\n"]
  where
    dot :: DominatorTree -> [String] -> [String]
    dot (Dominates root trees) = 
                   (dotnode root :) . outedges trees . flip (foldl subtree) trees
      where outedges [] = id
            outedges (Dominates n _ : ts) =
                \s -> "  " : show root : " -> " : show n : "\n" : outedges ts s
            dotnode Entry = "  entryNode [shape=plaintext, label=\"entry\"]\n"
            dotnode (Labelled l) = "  " ++ show l ++ "\n"
            subtree = flip dot
instance Show DominatorNode where
  show Entry = "entryNode"
  show (Labelled l) = show l
immediateDominators :: FactBase Doms -> LabelMap Label
immediateDominators = mapFoldWithKey add mapEmpty
    where add l (PElem (DPath (idom:_))) = mapInsert l idom 
          add _ _ = id