module DDC.Core.Llvm.Metadata.Graph
(
UG(..), DG(..)
, orientUG, partitionDG
, Tree(..)
, sources, anchor
, Dom, Rel
, fromList, toList
, transClosure, transOrient
, aliasMeasure, isTree )
where
import Data.List
import Data.Ord
import Data.Maybe
type Rel a = a -> a -> Bool
type Dom a = [a]
toList :: Dom a -> Rel a -> [(a, a)]
toList dom r = [ (x, y) | x <- dom, y <- dom, r x y ]
fromList :: Eq a => [(a, a)] -> Rel a
fromList s = \x y -> (x,y) `elem` s
unionR :: Rel a -> Rel a -> Rel a
unionR f g = \x y -> f x y || g x y
transClosure :: (Eq a) => Dom a -> Rel a -> Rel a
transClosure dom r = fromList $ step dom $ toList dom r
where step [] es = es
step (_:xs) es = step xs
$ nub (es ++ [(a, d)
| (a, b) <- es
, (c, d) <- es
, b == c])
newtype UG a = UG (Dom a, Rel a)
newtype DG a = DG (Dom a, Rel a)
instance Show a => Show (UG a) where
show (UG (d,r)) = "UG (" ++ (show d) ++ ", fromList " ++ (show $ toList d r) ++ ")"
instance Show a => Show (DG a) where
show (DG (d,r)) = "DG (" ++ (show d) ++ ", fromList " ++ (show $ toList d r) ++ ")"
instance Show a => Eq (DG a) where
a == b = show a == show b
neighbourUG :: Rel a -> a -> a -> Bool
neighbourUG f v x = f v x || f x v
type Class a = [a]
forceOrder :: Ord a => Class a -> Rel a -> Rel a
forceOrder ordering f
= let index = fromJust . (flip elemIndex ordering)
in \x y -> neighbourUG f x y && index x < index y
nonSingleton :: Class a -> Bool
nonSingleton [] = False
nonSingleton [_] = False
nonSingleton _ = True
lexBFS :: (Show a, Ord a) => UG a -> Class a
lexBFS (UG (vertices, f)) = refine [] [vertices]
where refine acc classes
| any nonSingleton classes = pivot acc classes
| otherwise = concat classes ++ acc
pivot acc ([vertex]:classes) = refine (vertex:acc) $ classes `splitAllOn` vertex
pivot acc ((vertex:vs):classes) = refine (vertex:acc) $ (vs:classes) `splitAllOn` vertex
pivot _ _ = error "ddc-core-llvm.lexBFS: bogus warning suppression."
splitAllOn [] _ = []
splitAllOn (cl:classes) vertex
| (neighbours, nonneighbours) <- partition (neighbourUG f vertex) cl
, all (not . null) [neighbours, nonneighbours]
= nonneighbours : neighbours : (classes `splitAllOn` vertex)
| otherwise
= cl : (classes `splitAllOn` vertex)
transOrient :: (Show a, Ord a) => UG a -> DG a
transOrient g@(UG (vertices, f))
= let vertices' = refine $ [(lexBFS g, maxBound)]
in DG (vertices, forceOrder vertices' f)
where refine classes
| any nonSingleton $ map fst classes
= let (before, after) = partition (\(c,lastused) -> length c > lastused `div` 2) classes
in refine (splitOthers before after)
| otherwise = concatMap fst classes
splitOthers before [] = splitLargest (largestClass before) before
splitOthers before ((pivot,_):after)
= foldl' (split True) before pivot
++ [(pivot, length pivot)]
++ foldl' (split False) after pivot
split _ [] _ = []
split isBefore (cl:classes) vertex
| (neighbours, nonneighbours) <- partition (neighbourUG f vertex) $ fst cl
, all (not . null) [neighbours, nonneighbours]
= let lastused = snd cl
in if isBefore
then (nonneighbours, lastused) : (neighbours, lastused) : (split isBefore classes vertex)
else (neighbours, lastused) : (nonneighbours, lastused) : (split isBefore classes vertex)
| otherwise = cl:classes
splitLargest _ [] = []
splitLargest cl ((cs, lastused):css)
| cl == cs = (tail cs, lastused) : ([head cs], maxBound) : css
| otherwise = (cs, lastused) : (splitLargest cl css)
largestClass [] = []
largestClass classes = maximumBy (comparing length) $ map fst classes
orientUG :: (Show a, Ord a) => UG a -> DG a
orientUG = transOrient
type Partitioning a = [Class a]
partitionings :: Eq a => [a] -> [Partitioning a]
partitionings [] = [[]]
partitionings (x:xs) = concatMap (nondetPut x) $ partitionings xs
where nondetPut :: a -> Partitioning a -> [Partitioning a]
nondetPut y [] = [ [[y]] ]
nondetPut y (l:ls) = let putHere = (y:l):ls
putLater = map (l:) $ nondetPut y ls
in putHere:putLater
aliasMeasure :: Eq a => Rel a -> Partitioning a -> Int
aliasMeasure g p
= (outerAliasing $ map length p) + (sum $ map innerAliasing p)
where innerAliasing t = length $ toList t $ transClosure t g
outerAliasing (l:ls) = l * (sum ls) + outerAliasing ls
outerAliasing [] = 0
newtype Tree a = Tree (Dom a, Rel a)
instance Show a => Show (Tree a) where
show (Tree (d,r)) = "tree (" ++ (show d) ++ ", " ++ (show $ toList d r) ++ ")"
isTree :: Dom a -> Rel a -> Bool
isTree dom r
= let neighbours x = filter (r x) dom
in all ((<=1) . length . neighbours) dom
sources :: Eq a => a -> Tree a -> [a]
sources x (Tree (d, r)) = [y | y <- d, r y x]
partitionDG :: Eq a => DG a -> [Tree a]
partitionDG (DG (d,g))
= let mkGraph g' nodes = (nodes, fromList [ (x,y) | x <- nodes, y <- nodes, g' x y ])
in map Tree $ fromMaybe (error "ddc-core-llvm.partitionDG: no partition found!")
$ find (all $ uncurry isTree)
$ map (map (mkGraph g))
$ sortBy (comparing (aliasMeasure g))
$ partitionings d
anchor :: Eq a => a -> Tree a -> Tree a
anchor root (Tree (d,g))
= let leaves = filter (null . flip filter d . g) d
arcs = map (, root) leaves
in Tree (root:d, g `unionR` fromList arcs)