graphviz-2999.18.0.2: Bindings to Graphviz for graph visualisation.

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

Data.GraphViz.Types.Graph

Contents

Description

It is sometimes useful to be able to manipulate a Dot graph as an actual graph. This representation lets you do so, using an inductive approach based upon that from FGL (note that DotGraph is not an instance of the FGL classes due to having the wrong kind). Note, however, that the API is not as complete as proper graph implementations.

For purposes of manipulation, all edges are found in the root graph and not in a cluster; as such, having EdgeAttrs in a cluster's GlobalAttributes is redundant.

Printing is achieved via Data.GraphViz.Types.Canonical (using toCanonical) and parsing via Data.GraphViz.Types.Generalised (so any piece of Dot code can be parsed in).

This representation doesn't allow non-cluster sub-graphs. Also, all clusters must have a unique identifier. For those functions (with the exception of DotRepr methods) that take or return a "Maybe GraphID", a value of "Nothing" refers to the root graph; "Just clust" refers to the cluster with the identifier "clust".

You would not typically explicitly create these values, instead converting existing Dot graphs (via fromDotRepr). However, one way of constructing the sample graph would be:

setID (Str "G")
. setStrictness False
. setIsDirected True
. setClusterAttributes (Int 0) [GraphAttrs [style filled, color LightGray, textLabel "process #1"], NodeAttrs [style filled, color White]]
. setClusterAttributes (Int 1) [GraphAttrs [textLabel "process #2", color Blue], NodeAttrs [style filled]]
$ composeList [ Cntxt "a0"    (Just $ Int 0)   []               [("a3",[]),("start",[])] [("a1",[])]
              , Cntxt "a1"    (Just $ Int 0)   []               []                       [("a2",[]),("b3",[])]
              , Cntxt "a2"    (Just $ Int 0)   []               []                       [("a3",[])]
              , Cntxt "a3"    (Just $ Int 0)   []               [("b2",[])]              [("end",[])]
              , Cntxt "b0"    (Just $ Int 1)   []               [("start",[])]           [("b1",[])]
              , Cntxt "b1"    (Just $ Int 1)   []               []                       [("b2",[])]
              , Cntxt "b2"    (Just $ Int 1)   []               []                       [("b3",[])]
              , Cntxt "b3"    (Just $ Int 1)   []               []                       [("end",[])]
              , Cntxt "end"   Nothing          [shape MSquare]  []                       []
              , Cntxt "start" Nothing          [shape MDiamond] []                       []]

Synopsis

Documentation

data DotGraph n Source

A Dot graph that allows graph operations on it.

Instances

(Ord n, PrintDot n, ParseDot n) => PPDotRepr DotGraph n Source 
(Ord n, ParseDot n) => ParseDotRepr DotGraph n Source 
(Ord n, PrintDot n) => PrintDotRepr DotGraph n Source 
Ord n => DotRepr DotGraph n Source 
Ord n => FromGeneralisedDot DotGraph n Source 
Eq n => Eq (DotGraph n) Source 
Ord n => Ord (DotGraph n) Source 
(Ord n, Read n) => Read (DotGraph n) Source

If the graph is the output from show, then it should be safe to substitute unsafeFromCanonical for fromCanonical.

(Ord n, Show n) => Show (DotGraph n) Source

It should be safe to substitute unsafeFromCanonical for fromCanonical in the output of this.

(Ord n, ParseDot n) => ParseDot (DotGraph n) Source

Uses the ParseDot instance for generalised DotGraphs.

(Ord n, PrintDot n) => PrintDot (DotGraph n) Source

Uses the PrintDot instance for canonical DotGraphs.

data GraphID Source

A polymorphic type that covers all possible ID values allowed by Dot syntax. Note that whilst the ParseDot and PrintDot instances for String will properly take care of the special cases for numbers, they are treated differently here.

Constructors

Str Text 
Num Number 

data Context n Source

The decomposition of a node from a dot graph. Any loops should be found in successors rather than predecessors. Note also that these are created/consumed as if for directed graphs.

Constructors

Cntxt 

Fields

node :: !n
 
inCluster :: !(Maybe GraphID)

The cluster this node can be found in; Nothing indicates the node can be found in the root graph.

attributes :: !Attributes
 
predecessors :: ![(n, Attributes)]
 
successors :: ![(n, Attributes)]
 

Instances

Eq n => Eq (Context n) Source 
Ord n => Ord (Context n) Source 
Read n => Read (Context n) Source 
Show n => Show (Context n) Source 

Conversions

toCanonical :: Ord n => DotGraph n -> DotGraph n Source

Convert this DotGraph into canonical form. All edges are found in the outer graph rather than in clusters.

unsafeFromCanonical :: Ord n => DotGraph n -> DotGraph n Source

Convert a canonical Dot graph to a graph-based one. This assumes that the canonical graph is the same format as returned by toCanonical. The "unsafeness" is that:

  • All clusters must have a unique identifier (unAnonymise can be used to make sure all clusters have an identifier, but it doesn't ensure uniqueness).
  • All nodes are assumed to be explicitly listed precisely once.
  • Only edges found in the root graph are considered.

If this isn't the case, use fromCanonical instead.

The graphToDot function from Data.GraphViz produces output suitable for this function (assuming all clusters are provided with a unique identifier); graphElemsToDot is suitable if all nodes are specified in the input list (rather than just the edges).

fromDotRepr :: DotRepr dg n => dg n -> DotGraph n Source

Convert any existing DotRepr instance to a DotGraph.

Graph information

isEmpty :: DotGraph n -> Bool Source

Does this graph have any nodes?

hasClusters :: DotGraph n -> Bool Source

Does this graph have any clusters?

isEmptyGraph :: DotGraph n -> Bool Source

Determine if this graph has nodes or clusters.

parentOf :: DotGraph n -> GraphID -> Maybe GraphID Source

Which cluster (or the root graph) is this cluster in?

foundInCluster :: Ord n => DotGraph n -> n -> Maybe GraphID Source

Return the ID for the cluster the node is in.

attributesOf :: Ord n => DotGraph n -> n -> Attributes Source

Return the attributes for the node.

predecessorsOf :: Ord n => DotGraph n -> n -> [DotEdge n] Source

Predecessor edges for the specified node. For undirected graphs equivalent to adjacentTo.

successorsOf :: Ord n => DotGraph n -> n -> [DotEdge n] Source

Successor edges for the specified node. For undirected graphs equivalent to adjacentTo.

adjacentTo :: Ord n => DotGraph n -> n -> [DotEdge n] Source

All edges involving this node.

Graph construction

mkGraph :: Ord n => [DotNode n] -> [DotEdge n] -> DotGraph n Source

Create a graph with no clusters.

(&) :: Ord n => Context n -> DotGraph n -> DotGraph n infixr 5 Source

Merge the Context into the graph. Assumes that the specified node is not in the graph but that all endpoints in the successors and predecessors (with the exception of loops) are. If the cluster is not present in the graph, then it will be added with no attributes with a parent of the root graph.

Note that & and decompose are not quite inverses, as this function will add in the cluster if it does not yet exist in the graph, but decompose will not delete it.

composeList :: Ord n => [Context n] -> DotGraph n Source

Recursively merge the list of contexts.

composeList = foldr (&) emptyGraph

addNode Source

Arguments

:: Ord n 
=> n 
-> Maybe GraphID

The cluster the node can be found in (Nothing refers to the root graph).

-> Attributes 
-> DotGraph n 
-> DotGraph n 

Add a node to the current graph. Throws an error if the node already exists in the graph.

If the specified cluster does not yet exist in the graph, then it will be added (as a sub-graph of the overall graph and no attributes).

data DotNode n Source

A node in DotGraph.

Constructors

DotNode 

addDotNode :: Ord n => DotNode n -> DotGraph n -> DotGraph n Source

A variant of addNode that takes in a DotNode (not in a cluster).

addEdge :: Ord n => n -> n -> Attributes -> DotGraph n -> DotGraph n Source

Add the specified edge to the graph; assumes both node values are already present in the graph. If the graph is undirected then the order of nodes doesn't matter.

data DotEdge n Source

An edge in DotGraph.

Constructors

DotEdge 

Fields

fromNode :: n
 
toNode :: n
 
edgeAttributes :: Attributes
 

addDotEdge :: Ord n => DotEdge n -> DotGraph n -> DotGraph n Source

A variant of addEdge that takes a DotEdge value.

addCluster Source

Arguments

:: GraphID

The identifier for this cluster.

-> Maybe GraphID

The parent of this cluster (Nothing refers to the root graph)

-> [GlobalAttributes] 
-> DotGraph n 
-> DotGraph n 

Add a new cluster to the graph; throws an error if the cluster already exists. Assumes that it doesn't match the identifier of the overall graph. If the parent cluster doesn't already exist in the graph then it will be added.

setClusterParent :: GraphID -> Maybe GraphID -> DotGraph n -> DotGraph n Source

Specify the parent of the cluster; adds both in if not already present.

setClusterAttributes :: GraphID -> [GlobalAttributes] -> DotGraph n -> DotGraph n Source

Specify the attributes of the cluster; adds it if not already present.

Graph deconstruction

decompose :: Ord n => n -> DotGraph n -> Maybe (Context n, DotGraph n) Source

A partial inverse of &, in that if a node exists in a graph then it will be decomposed, but will not remove the cluster that it was in even if it was the only node in that cluster.

decomposeAny :: Ord n => DotGraph n -> Maybe (Context n, DotGraph n) Source

As with decompose, but do not specify which node to decompose.

decomposeList :: Ord n => DotGraph n -> [Context n] Source

Recursively decompose the Dot graph into a list of contexts such that if (c:cs) = decomposeList dg, then dg = c & composeList cs.

Note that all global attributes are lost, so this is not suitable for representing a Dot graph on its own.

deleteNode :: Ord n => n -> DotGraph n -> DotGraph n Source

Delete the specified node from the graph; returns the original graph if that node isn't present.

deleteAllEdges :: Ord n => n -> n -> DotGraph n -> DotGraph n Source

Delete all edges between the two nodes; returns the original graph if there are no edges.

deleteEdge :: Ord n => n -> n -> Attributes -> DotGraph n -> DotGraph n Source

Deletes the specified edge from the DotGraph (note: for unordered graphs both orientations are considered).

deleteDotEdge :: Ord n => DotEdge n -> DotGraph n -> DotGraph n Source

As with deleteEdge but takes a DotEdge rather than individual values.

deleteCluster :: Ord n => GraphID -> DotGraph n -> DotGraph n Source

Delete the specified cluster, and makes any clusters or nodes within it be in its root cluster (or the overall graph if required).

removeEmptyClusters :: Ord n => DotGraph n -> DotGraph n Source

Remove clusters with no sub-clusters and no nodes within them.