graphviz-2999.9.0.0: Graphviz bindings for Haskell.

MaintainerIvan.Miljenovic@gmail.com

Data.GraphViz

Contents

Description

This is the top-level module for the graphviz library. It provides functions to convert Graphs into the Dot language used by the Graphviz suite of programs (as well as a limited ability to perform the reverse operation).

Information about Graphviz and the Dot language can be found at: http://graphviz.org/

Synopsis

Conversion from graphs to Dot format.

There are various functions available for converting Graphs to Graphviz's Dot format (represented using the DotGraph type). There are two main types: converting plain graphs and converting clustered graphs (where the graph cluster that a particular Node belongs to is determined by its label).

These functions have two versions: one in which the user specifies whether the graph is directed or undirected (with a Bool value of True indicating that the graph is directed), and a primed version which attempts to automatically infer if the graph is directed or not. Note that these conversion functions assume that undirected graphs have every edge being duplicated (or at least that if there exists an edge from n1 to n2, then n1 <= n2; if n1 > n2 then it is removed for an undirected graph).

graphToDot :: Graph gr => Bool -> gr a b -> [GlobalAttributes] -> (LNode a -> Attributes) -> (LEdge b -> Attributes) -> DotGraph NodeSource

Convert a graph to Graphviz's Dot format.

graphToDot' :: (Ord b, Graph gr) => gr a b -> [GlobalAttributes] -> (LNode a -> Attributes) -> (LEdge b -> Attributes) -> DotGraph NodeSource

Convert a graph to Graphviz's Dot format with automatic direction detection.

Conversion with support for clusters.

data NodeCluster c a Source

Define into which cluster a particular node belongs. Clusters can be nested to arbitrary depth.

Constructors

N (LNode a)

Indicates the actual Node in the Graph.

C c (NodeCluster c a)

Indicates that the NodeCluster is in the Cluster c.

Instances

(Show c, Show a) => Show (NodeCluster c a) 

clusterGraphToDot :: (Ord c, Graph gr) => Bool -> gr a b -> [GlobalAttributes] -> (LNode a -> NodeCluster c l) -> (c -> Maybe GraphID) -> (c -> [GlobalAttributes]) -> (LNode l -> Attributes) -> (LEdge b -> Attributes) -> DotGraph NodeSource

Convert a graph to Dot format, using the specified clustering function to group nodes into clusters. Clusters can be nested to arbitrary depth.

clusterGraphToDot' :: (Ord c, Ord b, Graph gr) => gr a b -> [GlobalAttributes] -> (LNode a -> NodeCluster c l) -> (c -> Maybe GraphID) -> (c -> [GlobalAttributes]) -> (LNode l -> Attributes) -> (LEdge b -> Attributes) -> DotGraph NodeSource

Convert a graph to Dot format, using the specified clustering function to group nodes into clusters. Clusters can be nested to arbitrary depth. Graph direction is automatically inferred.

Pseudo-inverse conversion.

dotToGraph :: (DotRepr dg Node, Graph gr) => dg Node -> gr Attributes AttributesSource

A pseudo-inverse to graphToDot and graphToDot'; "pseudo" in the sense that the original node and edge labels aren't able to be reconstructed.

Graph augmentation.

The following functions provide support for passing a Graph through the appropriate GraphvizCommand to augment the Graph by adding positional information, etc.

Please note that there are some restrictions on this: to enable support for multiple edges between two nodes, the Comment Attribute is used to provide a unique identifier for each edge. As such, you should not set this Attribute for any LEdge.

For unprimed functions, the Bool argument is True for directed graphs, False otherwise; for the primed versions of functions the directionality of the graph is automatically inferred. Directed graphs are passed through Dot, and undirected graphs through Neato. Note that the reason these functions do not have unsafePerformIO applied to them is because if you set a global Attribute of:

    Start (StartStyle RandomStyle)

then it will not necessarily be referentially transparent (ideally, no matter what the seed is, it will still eventually be drawn to the same optimum, but this can't be guaranteed). As such, if you are sure that you're not using such an Attribute, then you should be able to use unsafePerformIO directly in your own code.

Customisable augmentation.

graphToGraph :: Graph gr => Bool -> gr a b -> [GlobalAttributes] -> (LNode a -> Attributes) -> (LEdge b -> Attributes) -> IO (gr (AttributeNode a) (AttributeEdge b))Source

Run the appropriate Graphviz command on the graph to get positional information and then combine that information back into the original graph.

graphToGraph' :: (Ord b, Graph gr) => gr a b -> [GlobalAttributes] -> (LNode a -> Attributes) -> (LEdge b -> Attributes) -> IO (gr (AttributeNode a) (AttributeEdge b))Source

Run the appropriate Graphviz command on the graph to get positional information and then combine that information back into the original graph. Graph direction is automatically inferred.

clusterGraphToGraph :: (Ord c, Graph gr) => Bool -> gr a b -> [GlobalAttributes] -> (LNode a -> NodeCluster c l) -> (c -> Maybe GraphID) -> (c -> [GlobalAttributes]) -> (LNode l -> Attributes) -> (LEdge b -> Attributes) -> IO (gr (AttributeNode a) (AttributeEdge b))Source

Run the appropriate Graphviz command on the clustered graph to get positional information and then combine that information back into the original graph.

clusterGraphToGraph' :: (Ord b, Ord c, Graph gr) => gr a b -> [GlobalAttributes] -> (LNode a -> NodeCluster c l) -> (c -> Maybe GraphID) -> (c -> [GlobalAttributes]) -> (LNode l -> Attributes) -> (LEdge b -> Attributes) -> IO (gr (AttributeNode a) (AttributeEdge b))Source

Run the appropriate Graphviz command on the clustered graph to get positional information and then combine that information back into the original graph. Graph direction is automatically inferred.

Quick augmentation.

This section contains convenience functions for quick-and-dirty augmentation of graphs. No Attributes are applied, and unsafePerformIO is used to make these normal functions. Note that this should be safe since these should be referentially transparent.

dotizeGraph :: Graph gr => Bool -> gr a b -> gr (AttributeNode a) (AttributeEdge b)Source

Pass the graph through graphToGraph with no Attributes.

dotizeGraph' :: (Graph gr, Ord b) => gr a b -> gr (AttributeNode a) (AttributeEdge b)Source

Pass the graph through graphToGraph with no Attributes. The graph direction is automatically inferred.

dotizeClusterGraph :: (Ord c, Graph gr) => Bool -> gr a b -> (LNode a -> NodeCluster c l) -> gr (AttributeNode a) (AttributeEdge b)Source

Pass the clustered graph through clusterGraphToGraph with no Attributes.

dotizeClusterGraph' :: (Ord b, Ord c, Graph gr) => gr a b -> (LNode a -> NodeCluster c l) -> gr (AttributeNode a) (AttributeEdge b)Source

Pass the clustered graph through clusterGraphToGraph with no Attributes. The graph direction is automatically inferred.

Manual augmentation.

This section allows you to manually augment graphs by providing fine-grained control over the augmentation process (the standard augmentation functions compose these together). Possible reasons for manual augmentation are:

Note that whilst these functions provide you with more control, you must be careful how you use them: if you use the wrong DotRepr for a Graph, then the behaviour of augmentGraph (and all functions that use it) is undefined. The main point is to make sure that the defined DotNode and DotEdge values aren't removed (or their ID values - or the Comment Attribute for the DotEdges - altered) to ensure that it is possible to match up the nodes and edges in the Graph with those in the DotRepr.

data EdgeID b Source

Used to augment an edge label with a unique identifier.

Instances

Eq b => Eq (EdgeID b) 
Ord b => Ord (EdgeID b) 
Show b => Show (EdgeID b) 

addEdgeIDs :: Graph gr => gr a b -> gr a (EdgeID b)Source

Add unique edge identifiers to each label. This is useful for when multiple edges between two nodes need to be distinguished.

setEdgeComment :: (LEdge b -> Attributes) -> LEdge (EdgeID b) -> AttributesSource

Add the Comment to the list of attributes containing the value of the unique edge identifier.

dotAttributes :: (Graph gr, DotRepr dg Node) => Bool -> gr a (EdgeID b) -> dg Node -> IO (gr (AttributeNode a) (AttributeEdge b))Source

Pass the DotRepr through the relevant command and then augment the Graph that it came from.

augmentGraph :: (Graph gr, DotRepr dg Node) => gr a (EdgeID b) -> dg Node -> gr (AttributeNode a) (AttributeEdge b)Source

Use the Attributes in the provided DotGraph to augment the node and edge labels in the provided Graph. The unique identifiers on the edges are also stripped off.

Please note that the behaviour for this function is undefined if the DotGraph does not come from the original Graph (either by using a conversion function or by passing the result of a conversion function through a GraphvizCommand via the DotOutput or similar).

Utility functions

prettyPrint :: DotRepr dg n => dg n -> IO StringSource

Pretty-print the DotGraph by passing it through the Canon output type (which produces "canonical" output). This is required because the printDotGraph function (and all printing functions in Data.GraphViz.Types.Printing) no longer uses indentation (this is to ensure the Dot code is printed correctly due to the limitations of the Pretty Printer used).

This will call error if an error occurs when calling the relevant GraphvizCommand: likely causes are that Graphviz suite isn't installed, or it has an Image or HtmlImg Attribute that references an image that can't be found from the working directory.

prettyPrint' :: DotRepr dg n => dg n -> StringSource

The unsafePerformIOd version of prettyPrint. Graphviz should always produce the same pretty-printed output, so this should be safe. However, it is not recommended to use it in production code, just for testing purposes.

canonicalise :: (DotRepr dg n, DotRepr DotGraph n) => dg n -> IO (DotGraph n)Source

Convert the DotRepr into its canonical form. This should work as it appears that the prettyPrinted form is always in the format of a DotGraph, but the Graphviz code hasn't been examined to verify this.

preview :: (Ord b, Graph gr) => gr a b -> IO ()Source

Quickly visualise a graph using the Xlib GraphvizCanvas.

Re-exporting other modules.