Hi,<br><br>I wrote a Haskell program to parse K-ary forest and convert it to dot script (Graphviz).<br><br>Here is the literate program.<br><br>-- First is some stuff imported:<br>module Main where<br><br>import System.Environment (getArgs)<br>import Text.ParserCombinators.Parsec<br>import Control.Monad (mapM_)<br>import Data.List (concatMap, intercalate)<br>import System.IO (writeFile)<br>import Data.Char (isSpace)<br><br>-- For each tree in the forest, it is described in pre-order.<br>-- Example description string of a forest of CLRS[1] Figure 19.5(a):<br>--&nbsp;&nbsp; (12), (7, (25)), (15, (28, (41)), (33))<br><br>-- Definition of K-ary node<br>data Node a = Node { root :: a <br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; , children :: [Node a]} deriving (Eq, Show)<br><br>-- Definition of Forest<br>type Forest a = [Node a]<br><br><br>-- parsers<br><br>-- a forest is a list of trees separate by ','<br>forest = do <br>&nbsp; ts &lt;- node `sepBy` (char ',')<br>&nbsp; return ts<br><br>-- a node contains a key then followed by a children forest or nothing (leaf case)<br>node = do<br>&nbsp; char '('<br>&nbsp; elem &lt;- key<br>&nbsp; ts &lt;- (try (char ',')&gt;&gt;forest) &lt;|&gt; return []<br>&nbsp; char ')'<br>&nbsp; return (Node elem ts)<br><br>-- a key is just a plain literate string.<br>key = many (noneOf ",()")<br><br>-- Command line arguments handling<br>parseArgs :: [String] -&gt; (String, String)<br>parseArgs [fname, s] = (fname, s)<br>parseArgs _ = error "wrong usage\nexample:\nfr2dot output.dot \"(12), (7, (25)), (15, ((28, (41)), 33))\""<br><br><br>-- A simplified function to generate dot script from parsed result.<br>toDot f = forestToDot f "t" True<br><br>-- a handy function to convert children of a K-ary tree to dot script<br>treesToDot ts prefix = forestToDot ts prefix False<br><br>-- convert a forest to dot script<br>forestToDot []&nbsp; _ _ = ""<br>forestToDot [t] prefix _ = nodeToDot t prefix<br>forestToDot ts@(_:_:_) prefix lnk = <br>&nbsp;&nbsp;&nbsp; (concatMap (\t-&gt;nodeToDot t prefix) ts) ++ consRoot<br>&nbsp;&nbsp;&nbsp; where<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; consRoot = "{rank=same " ++ ns ++ vis ++ "}\n" <br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; ns = intercalate "-&gt;" $ map (\t -&gt; prefix ++ root t) ts<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; vis = if lnk then "" else "[style=invis]"<br><br><br>-- convert a node to dot script<br>nodeToDot (Node x ts) prefix = <br>&nbsp;&nbsp;&nbsp; prefix'++"[label=\""++x++"\"];\n" ++<br>&nbsp;&nbsp;&nbsp; (treesToDot ts prefix') ++<br>&nbsp;&nbsp;&nbsp; (defCons ts prefix')<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; where prefix' = prefix ++ x<br><br>-- define connections among nodes in dot format<br>defCons ts prefix = concatMap f ts where<br>&nbsp;&nbsp;&nbsp; f (Node x _) = prefix++"-&gt;"++prefix++x++";\n"<br><br>-- generate dot script from a parsed forest<br>genDot fname (Right f) = writeFile fname dots &gt;&gt; putStrLn dots<br>&nbsp;&nbsp;&nbsp; where<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; dots = "digraph G{\n\tnode[shape=circle]\n"++(addTab $ toDot f)++"}"<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; addTab s = unlines $ map ("\t"++) (lines s)<br><br>main = do<br>&nbsp; args &lt;- getArgs<br>&nbsp; let (fname, s) = parseArgs args<br>&nbsp; genDot fname (parse forest "unknown" (filter (not.isSpace) s))<br><br>-- END<br><br>I tested with the following simple cases:<br>./fr2dot foo.dot "(12), (7, (25)), (15, (28, (41)), (33))"<br>./fr2dot bar.dot "(18), (3, (37)), (6, (8, (30, (45, (55)), (32)), (23, (24)), (22)), (29, (48, (50)), (31)), (10, (17)), (44))"<br><br>Run the following commands can convert to PNG files:<br>./dot -Tpng -o foo.png foo.dot<br>./dot -Tpng -o bar.png bar.dot<br><br>Reference:<br><br>[1]. Thomas H. Cormen, Charles E. Leiserson, Ronald L. Rivest and 
Clifford Stein. ``Introduction to Algorithms, Second Edition''. The MIT 
Press, 2001. ISBN: 0262032937.<br><br>Best regards.<br>--<br>Larry, LIU<br><a href="https://sites.google.com/site/algoxy/home">https://sites.google.com/site/algoxy/home</a><br>