haphviz-0.2.0.1: Graphviz code generation with Haskell

Safe HaskellSafe
LanguageHaskell2010

Text.Dot

Contents

Description

Graphviz code-generation in Haskell

This can be used to generate graphviz code for large graph visualisations.

{-# LANGUAGE OverloadedStrings #-}
import Text.Dot

main :: IO ()
main = renderToStdOut $ graph directed "example" $ do
    a <- node "a"
    b <- node "b"
    a --> b
    b --> a
    b --> b
>>> runhaskell example.hs
> digraph example {
>   0 [label=<a>];
>   1 [label=<b>];
>   0 -> 1;
>   1 -> 0;
>   1 -> 1;
> }

Synopsis

Documentation

Graph rendering

renderGraph :: DotGraph -> Text Source #

Render a graph to graphviz code

renderToFile :: FilePath -> DotGraph -> IO () Source #

Render a given graph and write the result to the given file

renderToStdOut :: DotGraph -> IO () Source #

Render a given graph and print it to std out