module DepTrack.Dot (DotDescription(..), dotifyGraphWith, dotify) where
import DepTrack (DepTrackT, GraphData, buildGraph, evalDepForest1)
import Data.Graph (edges, vertices)
import qualified Text.Dot as Dot
newtype DotDescription = DotDescription { getDotDescription :: String }
deriving (Eq, Ord, Show)
dotifyGraphWith
:: (x -> [(String,String)])
-> GraphData x k
-> DotDescription
dotifyGraphWith attributes (g,lookupF,_) =
DotDescription $ Dot.showDot dotted
where
dotted :: Dot.Dot ()
dotted = do
let node v = y where (y,_,_) = lookupF v
let vs = vertices g
let es = filter (uncurry (/=)) $ edges g
mapM_ (\i -> Dot.userNode (Dot.userNodeId i) (attributes (node i))) vs
mapM_ (\(i,j) -> Dot.edge (Dot.userNodeId i) (Dot.userNodeId j) []) es
dotify
:: (Monad m, Ord k, Show x)
=> (x -> [(String,String)])
-> (x -> k)
-> DepTrackT x m a
-> m DotDescription
dotify labelsF keyF x =
dotifyGraphWith labelsF . buildGraph keyF . snd <$> evalDepForest1 x