graphviz-2999.18.1.2: Bindings to Graphviz for graph visualisation.

Copyright(c) Matthew Sackman, Ivan Lazar Miljenovic
License3-Clause BSD-style
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

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).

If you wish to construct a Haskell representation of a Dot graph yourself rather than using the conversion functions here, please see the Data.GraphViz.Types module as a starting point for how to do so.

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

Synopsis

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 GlobalAttributes values 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 nonClusteredParams over defaultParams to avoid type-checking problems with the cluster type.
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 GraphvizParams directly, or using blankParams. Using the latter to avoid setting isDirected:
evenOdd :: (Graph gr, Ord el) => gr Int el -> DotGraph Node
evenOdd = setDirectedness graphToDot params
  where
    params = blankParams { globalAttributes = []
                         , clusterBy        = clustBy
                         , clusterID        = Num . 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 n nl el cl l Source #

Defines the parameters used to convert a Graph into a DotRepr.

A value of type GraphvizParams n nl el cl l indicates that the Graph has a node type of n, 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 tuples in the function types represent labelled nodes (for (n,nl) and (n,l)) and labelled edges ((n,n,el); the value (f,t,ftl) is an edge from f to l with a label of ftl). These correspond to LNode and LEdge in FGL graphs.

The clustering in clusterBy can be to arbitrary depth.

Note that the term "cluster" is slightly conflated here: in terms of GraphvizParams values, a cluster is a grouping of nodes; the isDotCluster function lets you specify whether it is a cluster in the Dot sense or just a sub-graph.

Constructors

Params 

Fields

defaultParams :: GraphvizParams n nl el cl nl Source #

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).

If you use a custom clusterBy function (which if you actually want clusters you should) then you should also override the (nonsensical) default clusterID.

nonClusteredParams :: GraphvizParams n nl el () nl Source #

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 n nl el cl l Source #

A GraphvizParams value where every field is set to undefined. This is useful when you have a function that will set some of the values for you (e.g. setDirectedness) 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 Node nl el cl l -> gr nl el -> a) -> GraphvizParams Node nl el cl l -> gr nl el -> a Source #

Determine if the provided Graph is directed or not and set the value of isDirected appropriately.

Specifying clusters.

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 NodeCluster is in the Cluster c.

Instances

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

Methods

showsPrec :: Int -> NodeCluster c a -> ShowS #

show :: NodeCluster c a -> String #

showList :: [NodeCluster c a] -> ShowS #

type LNodeCluster cl l = NodeCluster cl (Node, l) Source #

An alias for NodeCluster when dealing with FGL graphs.

Converting graphs.

graphToDot :: (Ord cl, Graph gr) => GraphvizParams Node nl el cl l -> gr nl el -> DotGraph Node Source #

Convert a graph to Dot format, using the specified parameters to cluster the graph, etc.

graphElemsToDot :: (Ord cl, Ord n) => GraphvizParams n nl el cl l -> [(n, nl)] -> [(n, n, el)] -> DotGraph n Source #

As with graphToDot, but this allows you to easily convert other graph-like formats to a Dot graph as long as you can get a list of nodes and edges from it.

Pseudo-inverse conversion.

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

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.

A CustomAttribute is used to distinguish multiple edges between two nodes from each other.

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 Node 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 Node 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:

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 Attributes 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 el Source #

Used to augment an edge label with a unique identifier.

Instances

Eq el => Eq (EdgeID el) Source # 

Methods

(==) :: EdgeID el -> EdgeID el -> Bool #

(/=) :: EdgeID el -> EdgeID el -> Bool #

Ord el => Ord (EdgeID el) Source # 

Methods

compare :: EdgeID el -> EdgeID el -> Ordering #

(<) :: EdgeID el -> EdgeID el -> Bool #

(<=) :: EdgeID el -> EdgeID el -> Bool #

(>) :: EdgeID el -> EdgeID el -> Bool #

(>=) :: EdgeID el -> EdgeID el -> Bool #

max :: EdgeID el -> EdgeID el -> EdgeID el #

min :: EdgeID el -> EdgeID el -> EdgeID el #

Show el => Show (EdgeID el) Source # 

Methods

showsPrec :: Int -> EdgeID el -> ShowS #

show :: EdgeID el -> String #

showList :: [EdgeID el] -> ShowS #

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.

setEdgeIDAttribute :: (LEdge el -> Attributes) -> LEdge (EdgeID el) -> Attributes Source #

Add a custom attribute to the list of attributes containing the value of the unique edge identifier.

dotAttributes :: (Graph gr, PPDotRepr dg Node, FromGeneralisedDot dg Node) => Bool -> gr nl (EdgeID el) -> dg Node -> IO (gr (AttributeNode nl) (AttributeEdge el)) Source #

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

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

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.