graphviz-2999.7.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/

Commands for converting graphs to Dot format have two options: one in which the user specifies whether the graph is directed or undirected, 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).

Synopsis

Conversion from graphs to Dot format.

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

Convert a graph to Graphviz's Dot format. The Bool value is True for directed graphs, False otherwise.

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. The Bool argument is True for directed graphs, False otherwise.

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.

Utility functions

prettyPrint :: PrintDot a => DotGraph a -> IO StringSource

Pretty-print the DotGraph by passing it through the Canon output type (which produces "canonical" output). This is required because the printIt function in Data.GraphViz.Types.Printing no longer uses indentation to ensure the Dot code is printed correctly.

prettyPrint' :: PrintDot a => DotGraph a -> StringSource

The unsafePerformIOd version of prettyPrint. Graphviz should always produce the same pretty-printed output, so this should be safe.

Passing the graph through Graphviz.

Type aliases for Node and Edge labels.

For normal graphs.

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. Note that for the edge information to be parsed properly when using multiple edges, each edge between two nodes needs to have a unique label.

The Bool argument is True for directed graphs, False otherwise. Directed graphs are passed through dot, and undirected graphs through neato.

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.

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

Pass the graph through graphToGraph with no Attributes. This is an IO action, however since the state doesn't change it's safe to use unsafePerformIO to convert this to a normal function.

The Bool argument is True for directed graphs, False otherwise. Directed graphs are passed through dot, and undirected graphs through neato.

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

Pass the graph through graphToGraph with no Attributes. This is an IO action, however since the state doesn't change it's safe to use unsafePerformIO to convert this to a normal function.

The graph direction is automatically inferred.

For clustered graphs.

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. Note that for the edge information to be parsed properly when using multiple edges, each edge between two nodes needs to have a unique label.

The Bool argument is True for directed graphs, False otherwise. Directed graphs are passed through dot, and undirected graphs through neato.

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.

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. This is an IO action, however since the state doesn't change it's safe to use unsafePerformIO to convert this to a normal function.

The Bool argument is True for directed graphs, False otherwise. Directed graphs are passed through dot, and undirected graphs through neato.

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 graphToGraph with no Attributes. This is an IO action, however since the state doesn't change it's safe to use unsafePerformIO to convert this to a normal function.

The graph direction is automatically inferred.

Re-exporting other modules.