| Maintainer | Ivan.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/
- data GraphvizParams nl el cl l = Params {
- isDirected :: Bool
- globalAttributes :: [GlobalAttributes]
- clusterBy :: LNode nl -> LNodeCluster cl l
- clusterID :: cl -> Maybe GraphID
- fmtCluster :: cl -> [GlobalAttributes]
- fmtNode :: LNode l -> Attributes
- fmtEdge :: LEdge el -> Attributes
- defaultParams :: GraphvizParams nl el cl nl
- nonClusteredParams :: GraphvizParams nl el () nl
- blankParams :: GraphvizParams nl el cl l
- setDirectedness :: (Ord el, Graph gr) => (GraphvizParams nl el cl l -> gr nl el -> a) -> GraphvizParams nl el cl l -> gr nl el -> a
- type LNodeCluster c a = NodeCluster c (LNode a)
- data NodeCluster c a
- = N a
- | C c (NodeCluster c a)
- graphToDot :: (Ord cl, Graph gr) => GraphvizParams nl el cl l -> gr nl el -> DotGraph Node
- dotToGraph :: (DotRepr dg Node, Graph gr) => dg Node -> gr Attributes Attributes
- type AttributeNode nl = (Attributes, nl)
- type AttributeEdge el = (Attributes, el)
- graphToGraph :: (Ord cl, Graph gr) => GraphvizParams nl el cl l -> gr nl el -> IO (gr (AttributeNode nl) (AttributeEdge el))
- dotizeGraph :: (Ord cl, Graph gr) => GraphvizParams nl el cl l -> gr nl el -> gr (AttributeNode nl) (AttributeEdge el)
- data EdgeID el
- addEdgeIDs :: Graph gr => gr nl el -> gr nl (EdgeID el)
- setEdgeComment :: (LEdge el -> Attributes) -> LEdge (EdgeID el) -> Attributes
- dotAttributes :: (Graph gr, DotRepr dg Node) => Bool -> gr nl (EdgeID el) -> dg Node -> IO (gr (AttributeNode nl) (AttributeEdge el))
- augmentGraph :: (Graph gr, DotRepr dg Node) => gr nl (EdgeID el) -> dg Node -> gr (AttributeNode nl) (AttributeEdge el)
- prettyPrint :: DotRepr dg n => dg n -> IO String
- prettyPrint' :: DotRepr dg n => dg n -> String
- canonicalise :: (DotRepr dg n, DotRepr DotGraph n) => dg n -> IO (DotGraph n)
- preview :: (Ord el, Graph gr, Labellable nl, Labellable el) => gr nl el -> IO ()
- module Data.GraphViz.Types
- module Data.GraphViz.Attributes
- module Data.GraphViz.Commands
Conversion from graphs to Dot format.
Specifying parameters.
A GraphvizParams value contains all the information necessary to
manipulate Graphs with this library. As such, its components deal
with:
- Whether to treat graphs as being directed or not;
- Which top-level
GlobalAttributesvalues should be applied; - How to define (and name) clusters;
- How to format clusters, nodes and edges.
Apart from not having to pass multiple values around, another
advantage of using GraphvizParams over the previous approach is that
there is no distinction between clustering and non-clustering variants
of the same functions.
Example usages of GraphvizParams follow:
- Quickly visualise a graph using the default parameters. Note the
usage of
overnonClusteredParamsto avoid type-checking problems with the cluster type.defaultParams
defaultVis :: (Graph gr) => gr nl el -> DotGraph Node defaultVis = graphToDot nonClusteredParams
- As with
defaultVis, but determine whether or not the graph is directed or undirected.
checkDirectednessVis :: (Graph gr, Ord el) => gr nl el -> DotGraph Node checkDirectednessVis = setDirectedness graphToDot nonClusteredParams
- Clustering nodes based upon whether they are even or odd. We have
the option of either constructing a
GraphvizParamsdirectly, or using. Going with the latter to avoid settingblankParams.isDirected
evenOdd :: (Graph gr, Ord el) => gr Int el -> DotGraph Node
evenOdd = setDirectedness graphToDot params
where
params = blankParams { globalAttributes = []
, clusterBy = clustBy
, clusterID = Just . Int
, fmtCluster = clFmt
, fmtNode = const []
, fmtEdge = const []
}
clustBy (n,l) = C (n `mod` 2) $ N (n,l)
clFmt m = [GraphAttrs [toLabel $ "n == " ++ show m ++ " (mod 2)"]]
For more examples, see the source of dotizeGraph and preview.
data GraphvizParams nl el cl l Source
Defines the parameters used to convert a Graph into a DotRepr.
A value of type indicates that the
GraphvizParams nl el cl lGraph has node labels of type nl, edge labels of type el,
corresponding clusters of type cl and after clustering the
nodes have a label of type l (which may or may not be the same
as nl).
The clustering in clusterBy can be to arbitrary depth.
Constructors
| Params | |
Fields
| |
defaultParams :: GraphvizParams nl el cl nlSource
A default GraphvizParams value which assumes the graph is
directed, contains no clusters and has no Attributes set.
If you wish to have the labels of the nodes to have a different
type after applying clusterBy from before clustering, then you
will have to specify your own GraphvizParams value from
scratch (or use blankParams).
nonClusteredParams :: GraphvizParams nl el () nlSource
A variant of defaultParams that enforces that the clustering
type is '()' (i.e.: no clustering); this avoids problems when
using defaultParams internally within a function without any
constraint on what the clustering type is.
blankParams :: GraphvizParams nl el cl lSource
A GraphvizParams value where every field is set to
. This is useful when you have a function that will
set some of the values for you (e.g. undefinedsetDirectedness) but you
don't want to bother thinking of default values to set in the
meantime. This is especially useful when you are
programmatically setting the clustering function (and as such do
not know what the types might be).
setDirectedness :: (Ord el, Graph gr) => (GraphvizParams nl el cl l -> gr nl el -> a) -> GraphvizParams nl el cl l -> gr nl el -> aSource
Determine if the provided Graph is directed or not and set the
value of isDirected appropriately.
Specifying clusters.
type LNodeCluster c a = NodeCluster c (LNode a)Source
A type alias for NodeCluster that specifies that the node value
is an LNode.
data NodeCluster c a Source
Define into which cluster a particular node belongs. Clusters can be nested to arbitrary depth.
Constructors
| N a | Indicates the actual Node in the Graph. |
| C c (NodeCluster c a) | Indicates that the
|
Instances
| (Show c, Show a) => Show (NodeCluster c a) |
Converting graphs.
graphToDot :: (Ord cl, Graph gr) => GraphvizParams nl el cl l -> gr nl el -> DotGraph NodeSource
Convert a graph to Dot format, using the specified parameters to cluster the graph, etc.
Pseudo-inverse conversion.
dotToGraph :: (DotRepr dg Node, Graph gr) => dg Node -> gr Attributes AttributesSource
A pseudo-inverse to 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.
Note that the reason that most of 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.
type AttributeNode nl = (Attributes, nl)Source
Augment the current node label type with the Attributes applied
to that node.
type AttributeEdge el = (Attributes, el)Source
Augment the current edge label type with the Attributes applied
to that edge.
Customisable augmentation.
graphToGraph :: (Ord cl, Graph gr) => GraphvizParams nl el cl l -> gr nl el -> IO (gr (AttributeNode nl) (AttributeEdge el))Source
Run the appropriate Graphviz command on the graph to get positional information and then combine that information back into the original graph.
Quick augmentation.
dotizeGraph :: (Ord cl, Graph gr) => GraphvizParams nl el cl l -> gr nl el -> gr (AttributeNode nl) (AttributeEdge el)Source
This is a "quick-and-dirty" graph augmentation function that
sets no Attributes and thus should be referentially transparent
and is wrapped in unsafePerformIO.
Note that the provided GraphvizParams is only used for
isDirected, clusterBy and clusterID.
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:
- Gain access to the intermediary
DotReprused. - Convert the default
DotGraphto aGDotGraph(found in Data.GraphViz.Types.Generalised) so as to have greater control over the generated Dot code. - Use a specific
GraphvizCommandrather than the default.
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.
Used to augment an edge label with a unique identifier.
addEdgeIDs :: Graph gr => gr nl el -> gr nl (EdgeID el)Source
Add unique edge identifiers to each label. This is useful for when multiple edges between two nodes need to be distinguished.
setEdgeComment :: (LEdge el -> Attributes) -> LEdge (EdgeID el) -> 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 nl (EdgeID el) -> dg Node -> IO (gr (AttributeNode nl) (AttributeEdge el))Source
augmentGraph :: (Graph gr, DotRepr dg Node) => gr nl (EdgeID el) -> dg Node -> gr (AttributeNode nl) (AttributeEdge el)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 el, Graph gr, Labellable nl, Labellable el) => gr nl el -> IO ()Source
Quickly visualise a graph using the Xlib GraphvizCanvas. If
your label types are not (and cannot) be instances of Labellable,
you may wish to use gmap, nmap or emap to set them to a value
such as "".
Re-exporting other modules.
module Data.GraphViz.Types
module Data.GraphViz.Attributes
module Data.GraphViz.Commands