[Haskell-cafe] Graph diagram tools?

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Fri Apr 17 01:23:22 UTC 2015


Wow, you really have resurrected an old thread!

On 17 April 2015 at 03:12, Ivan Zakharyaschev <imz at altlinux.org> wrote:
> Hi,
>
> I have some feedback on the API of the graphviz library's monadic API
> (resulting form my explorations written down at
> http://mathoverflow.net/a/203099/13991 ).
>
> Le jeudi 23 juin 2011 04:38:21 UTC+4, Ivan Lazar Miljenovic a écrit :
>>
>> On 23 June 2011 02:48, Stephen Tetley <stephen... at gmail.com> wrote:
>> > Or Andy Gill's Dotgen - simple and stable:
>> >
>> > http://hackage.haskell.org/package/dotgen
>>
>> Within the next month, I should hopefully finally finish the new
>> version of graphviz.  Various improvements include:
>>
>> As such, I would greatly appreciate knowing what it is that makes you
>>
>> want to use a different library (admittedly the graphviz API isn't as
>> stable as the others, but that's because I keep trying to improve it,
>> and typically state in the Changelog exactly what has changed).
>>
>>
>
>  ### graphviz Haskell library and other ones
>
> An alternative to "graphviz" Haskell package mentioned in
> [haskell-cafe](https://groups.google.com/d/msg/haskell-cafe/ZfZaw2E9a18/xZ0OeHCGzVgJ)
> is [dotgen](http://hackage.haskell.org/package/dotgen).
>
> In [a
> follow-up](https://groups.google.com/d/msg/haskell-cafe/ZfZaw2E9a18/9P-dazcd0FsJ)
> to the post mentioning `dotgen`, the author of graphviz gives some
> comparison between them (and other similar Haskell libs). I assume his
> "plans" (about a monadic interface) have been implemented already:

Yup: http://hackage.haskell.org/package/graphviz-2999.17.0.2/docs/Data-GraphViz-Types-Monadic.html

>
>> Within the next month, I should hopefully finally finish the new
>> version of graphviz.  Various improvements include:
>>
>> ...
>>
>> * A Dot graph representation based loosely upon **dotgen**'s monadic
>> interface (with Andy's blessing) but with the various Attributes being
>> used rather than (String, String).  I think I'm going to be able to
>> make it such that you can define a graph using the monadic interface
>> that will almost look identical to actual Dot code.
>>
>> ...
>>
>> I would like to stress to people considering using other bindings to
>> Graphviz/Dot (such as **dotgen**, language-dot, or their own
>> cobbled-together interface): be very careful about quoting, etc.  I
>> have spent a _lot_ of time checking how to properly escape different
>> values and ensuring correctness under the hood (i.e. there is no need
>> to pre-escape your Text/String values; graphviz will do that for you
>> when generating the actual Dot code).  This, after all, is the point
>> of having existing libraries rather than rolling your own each time.
>
> Both points are related. (So, graphviz's monadic iterface is a safer
> improvement upon dotgen's one.)
>
> ### Considering dotgen vs graphviz closer
>
> But looking into the examples, I see that `dotgen` can use "Haskell
> ids" to identify created nodes, whereas in graphviz's monad (see the
> example above) one must supply extra strings as the unique ids (by
> which we refer to the nodes).

I used Strings as an example, as I was directly converting an existing
piece of Dot code; the original can be found here:
http://hackage.haskell.org/package/graphviz-2999.17.0.2/docs/Data-GraphViz-Types.html

But, you can use any type you like for the node identifiers, as long
as you make them an instance of the PrintDot class.  That's where the
`n` in the `Dot n` type comes in.

>
> I like the first approach more ("Haskell ids").

I admittedly don't have any ability in graphviz to create new
identifiers for you.  I could (just add a StateT to the internal
monadic stack which keeps track of the next unused node identifier)
but I think that would _reduce_ the flexibility of being able to use
your own type (it would either only work for `Dot Int`, or even if you
could apply a mapping function to use something like `GraphID`, but
that has a problem if you have a `Double` with the same value - and
hence same textual representation - as your Int).

The way I see it, graphviz is usually used for converting existing
Haskell values into Dot code and then processing with dot, neato, etc.
the Monadic interface exists so that you can still use the library for
static pre-specified graphs (I wrote the module for a specific use
case, but in practice found it not as useful as I thought it would be
as I typically don't have a need for static graphs in my Haskell
code).

>
> Cf. dotgen (from
> <https://github.com/ku-fpg/dotgen/blob/master/test/DotTest.hs>):
>
>     module Main (main) where
>     import Text.Dot
>     -- data Animation = Start
>     src, box, diamond :: String -> Dot NodeId
>     src label = node $ [ ("shape","none"),("label",label) ]
>     box label = node $ [ ("shape","box"),("style","rounded"),("label",label)
> ]
>     diamond label = node $
> [("shape","diamond"),("label",label),("fontsize","10")]
>     main :: IO ()
>     main = putStrLn $ showDot $ do
>     attribute ("size","40,15")
>     attribute ("rankdir","LR")
>     refSpec <- src "S"
>     tarSpec <- src "T"
>     same [refSpec,tarSpec]
>     c1 <- box "S"
>     c2 <- box "C"
>     c3 <- box "F"
>     same [c1,c2,c3]
>     refSpec .->. c1
>     tarSpec .->. c2
>     tarSpec .->. c3
>     m1 <- box "x"
>     m2 <- box "y"
>     ntm <- box "z"
>     same [m1,m2,ntm]
>     c1 .->. m1
>     c2 .->. m2
>     xilinxSynthesis <- box "x"
>     c3 .->. xilinxSynthesis
>     gns <- box "G"
>     xilinxSynthesis .->. gns
>     gns .->. ntm
>     ecs <- sequence
>     [ diamond "E"
>     , diamond "E"
>     , diamond "Eq"
>     ]
>     same ecs
>     m1 .->. (ecs !! 0)
>     m1 .->. (ecs !! 1)
>     m2 .->. (ecs !! 0)
>     m2 .->. (ecs !! 2)
>     ntm .->. (ecs !! 1)
>     ntm .->. (ecs !! 2)
>     _ <- sequence [ do evidence <- src "EE"
>     n .->. evidence
>     | n <- ecs
>     ]
>     edge refSpec tarSpec
> [("label","Engineering\nEffort"),("style","dotted")]
>     () <- scope $ do v1 <- box "Hello"
>     v2 <- box "World"
>     v1 .->. v2
>     (x,()) <- cluster $
>     do v1 <- box "Hello"
>     v2 <- box "World"
>     v1 .->. v2
>     -- x .->. m2
>     -- for hpc
>     () <- same [x,x]
>     v <- box "XYZ"
>     v .->. v
>     () <- attribute ("rankdir","LR")
>     let n1 = userNodeId 1
>     let n2 = userNodeId (-1)
>     () <- n1 `userNode` [ ("shape","box")]
>     n1 .->. n2
>     _ <- box "XYZ"
>     _ <- box "(\n\\n)\"(/\\)"
>     netlistGraph (\ a -> [("label","X" ++ show a)])
>     (\ a -> [succ a `mod` 10,pred a `mod` 10])
>     [ (n,n) | n <- [0..9] :: [Int] ]
>     return ()
>

My preference - and hence overall design with graphviz - is that you
would generate the graph first, and _then_ convert it to a Dot
representation en masse.

>
> Cf. graphviz with string ids:
>
> A short example of the monadic notation from [the
> documentation](http://hackage.haskell.org/package/graphviz-2999.16.0.0/docs/Data-GraphViz-Types-Monadic.html):

That version is a tad out of date, but shouldn't affect this.

>
>     digraph (Str "G") $ do
>
>         cluster (Int 0) $ do
>             graphAttrs [style filled, color LightGray]
>             nodeAttrs [style filled, color White]
>             "a0" --> "a1"
>             "a1" --> "a2"
>             "a2" --> "a3"
>             graphAttrs [textLabel "process #1"]
>
>         cluster (Int 1) $ do
>             nodeAttrs [style filled]
>             "b0" --> "b1"
>             "b1" --> "b2"
>             "b2" --> "b3"
>             graphAttrs [textLabel "process #2", color Blue]
>
>         "start" --> "a0"
>         "start" --> "b0"
>         "a1" --> "b3"
>         "b2" --> "a3"
>         "a3" --> "end"
>         "b3" --> "end"
>
>         node "start" [shape MDiamond]
>         node "end" [shape MSquare]
>
> Thanks for the packages, and best wishes,
> Ivan Z.



-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com


More information about the Haskell-Cafe mailing list