module Sound.DF.Draw ( -- * Graph drawing view ) where import Sound.DF.Node import Sound.DF.Graph import Control.Monad import qualified Data.Graph.Inductive as G import qualified Data.Graph.Inductive.Graphviz as G import Data.Maybe import Data.List import System.Cmd import System.Directory import System.FilePath -- | Implicit edge from wR to rW. r_edge :: [(NodeID, Node)] -> (NodeID, Node) -> Maybe Edge r_edge ns (i, R (R_ID d) (Left _)) = let f x (_, (R (R_ID y) (Right _))) = x == y f _ _ = False (j, _) = fromMaybe (error "r_edge") (find (f d) ns) in Just ((j,0),(i,0)) r_edge _ _ = Nothing -- | Transform the actual graph into the viewing graph. vgraph :: G.Gr Node (PortID, PortID) -> G.Gr Node (PortID, PortID) vgraph g = let ns = G.labNodes g es = G.labEdges g es' = map mod_e (catMaybes (map (r_edge ns) ns)) in G.mkGraph ns (es ++ es') draw :: Node -> String draw = G.graphviz' . vgraph . graph -- | Draw graph using graphviz. view :: Node -> IO () view n = do t <- getTemporaryDirectory let s = draw n fn = t "df_view" <.> "dot" writeFile fn s rawSystem "dotty" [fn] return ()