Copyright | (c) Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Four different representations of Dot graphs are available, all of
which are based loosely upon the specifications at:
http://graphviz.org/doc/info/lang.html. The DotRepr
class
provides a common interface for them (the PrintDotRepr
,
ParseDotRepr
and PPDotRepr
classes are used until class aliases
are implemented).
Every representation takes in a type parameter: this indicates the
node type (e.g. DotGraph Int
is a Dot graph with integer nodes).
Sum types are allowed, though care must be taken when specifying
their ParseDot
instances if there is the possibility of
overlapping definitions. The GraphID
type is an existing sum
type that allows textual and numeric values.
If you require using more than one Dot representation, you will most likely need to import at least one of them qualified, as they typically all use the same names.
As a comparison, all four representations provide how you would define the following Dot graph (or at least one isomorphic to it) (the original of which can be found at http://graphviz.org/content/cluster). Note that in all the examples, they are not necessarily done the best way (variables rather than repeated constants, etc.); they are just there to provide a comparison on the structure of each representation.
digraph G { subgraph cluster_0 { style=filled; color=lightgrey; node [style=filled,color=white]; a0 -> a1 -> a2 -> a3; label = "process #1"; } subgraph cluster_1 { node [style=filled]; b0 -> b1 -> b2 -> b3; label = "process #2"; color=blue } start -> a0; start -> b0; a1 -> b3; b2 -> a3; a3 -> a0; a3 -> end; b3 -> end; start [shape=Mdiamond]; end [shape=Msquare]; }
Each representation is suited for different things:
- Data.GraphViz.Types.Canonical
- is ideal for converting other graph-like data structures into Dot graphs (the Data.GraphViz module provides some functions for this). It is a structured representation of Dot code.
- Data.GraphViz.Types.Generalised
- matches the actual structure of Dot code. As such, it is suited for parsing in existing Dot code.
- Data.GraphViz.Types.Graph
- provides graph operations for manipulating Dot graphs; this is suited when you want to edit existing Dot code. It uses generalised Dot graphs for parsing and canonical Dot graphs for printing.
- Data.GraphViz.Types.Monadic
- is a much easier representation to use when defining relatively static Dot graphs in Haskell code, and looks vaguely like actual Dot code if you squint a bit.
Please also read the limitations section at the end for advice on how to properly use these Dot representations.
- class Ord n => DotRepr dg n where
- class PrintDot a where
- class ParseDot a where
- class (DotRepr dg n, PrintDot (dg n)) => PrintDotRepr dg n
- class (DotRepr dg n, ParseDot (dg n)) => ParseDotRepr dg n
- class (PrintDotRepr dg n, ParseDotRepr dg n) => PPDotRepr dg n
- data GraphID
- data Number
- class ToGraphID a where
- textGraphID :: Text -> GraphID
- data GlobalAttributes
- = GraphAttrs {
- attrs :: Attributes
- | NodeAttrs {
- attrs :: Attributes
- | EdgeAttrs {
- attrs :: Attributes
- = GraphAttrs {
- data DotNode n = DotNode {
- nodeID :: n
- nodeAttributes :: Attributes
- data DotEdge n = DotEdge {
- fromNode :: n
- toNode :: n
- edgeAttributes :: Attributes
- type ClusterLookup = Map (Maybe GraphID) ([Path], GlobalAttributes)
- type NodeLookup n = Map n (Path, Attributes)
- type Path = Seq (Maybe GraphID)
- graphStructureInformationClean :: DotRepr dg n => dg n -> (GlobalAttributes, ClusterLookup)
- nodeInformationClean :: DotRepr dg n => Bool -> dg n -> NodeLookup n
- edgeInformationClean :: DotRepr dg n => Bool -> dg n -> [DotEdge n]
- graphNodes :: DotRepr dg n => dg n -> [DotNode n]
- graphEdges :: DotRepr dg n => dg n -> [DotEdge n]
- printDotGraph :: PrintDotRepr dg n => dg n -> Text
- parseDotGraph :: ParseDotRepr dg n => Text -> dg n
- parseDotGraphLiberally :: ParseDotRepr dg n => Text -> dg n
Documentation
class Ord n => DotRepr dg n where Source #
This class is used to provide a common interface to different ways of representing a graph in Dot form.
You will most probably not need to create your own instances of this class.
The type variable represents the current node type of the Dot
graph, and the Ord
restriction is there because in practice
most implementations of some of these methods require it.
fromCanonical, getID, setID, graphIsDirected, setIsDirected, graphIsStrict, setStrictness, mapDotGraph, graphStructureInformation, nodeInformation, edgeInformation, unAnonymise
fromCanonical :: DotGraph n -> dg n Source #
Convert from a graph in canonical form. This is especially useful when using the functions from Data.GraphViz.Algorithms.
See FromGeneralisedDot
in Data.GraphViz.Types.Generalised
for a semi-inverse of this function.
getID :: dg n -> Maybe GraphID Source #
Return the ID of the graph.
setID :: GraphID -> dg n -> dg n Source #
Set the ID of the graph.
graphIsDirected :: dg n -> Bool Source #
Is this graph directed?
setIsDirected :: Bool -> dg n -> dg n Source #
Set whether a graph is directed or not.
graphIsStrict :: dg n -> Bool Source #
Is this graph strict? Strict graphs disallow multiple edges.
setStrictness :: Bool -> dg n -> dg n Source #
A strict graph disallows multiple edges.
mapDotGraph :: DotRepr dg n' => (n -> n') -> dg n -> dg n' Source #
Change the node values. This function is assumed to be injective, otherwise the resulting graph will not be identical to the original (modulo labels).
graphStructureInformation :: dg n -> (GlobalAttributes, ClusterLookup) Source #
Return information on all the clusters contained within this
DotRepr
, as well as the top-level GraphAttrs
for the
overall graph.
nodeInformation :: Bool -> dg n -> NodeLookup n Source #
Return information on the DotNode
s contained within this
DotRepr
. The Bool
parameter indicates if applicable
NodeAttrs
should be included.
edgeInformation :: Bool -> dg n -> [DotEdge n] Source #
Return information on the DotEdge
s contained within this
DotRepr
. The Bool
parameter indicates if applicable
EdgeAttrs
should be included.
unAnonymise :: dg n -> dg n Source #
Give any anonymous sub-graphs or clusters a unique identifier
(i.e. there will be no Nothing
key in the ClusterLookup
from graphStructureInformation
).
class PrintDot a where Source #
A class used to correctly print parts of the Graphviz Dot language.
Minimal implementation is unqtDot
.
unqtDot :: a -> DotCode Source #
The unquoted representation, for use when composing values to produce a larger printing value.
toDot :: a -> DotCode Source #
The actual quoted representation; this should be quoted if it
contains characters not permitted a plain ID String, a number
or it is not an HTML string. Defaults to unqtDot
.
unqtListToDot :: [a] -> DotCode Source #
The correct way of representing a list of this value when printed; not all Dot values require this to be implemented. Defaults to Haskell-like list representation.
listToDot :: [a] -> DotCode Source #
The quoted form of unqtListToDot
; defaults to wrapping double
quotes around the result of unqtListToDot
(since the default
implementation has characters that must be quoted).
class ParseDot a where Source #
parseUnqtList :: Parse [a] Source #
class (DotRepr dg n, PrintDot (dg n)) => PrintDotRepr dg n Source #
This class exists just to make type signatures nicer; all
instances of DotRepr
should also be an instance of
PrintDotRepr
.
class (DotRepr dg n, ParseDot (dg n)) => ParseDotRepr dg n Source #
This class exists just to make type signatures nicer; all
instances of DotRepr
should also be an instance of
ParseDotRepr
.
class (PrintDotRepr dg n, ParseDotRepr dg n) => PPDotRepr dg n Source #
Common sub-types
A numeric type with an explicit separation between integers and floating-point values.
textGraphID :: Text -> GraphID Source #
An alias for toGraphID
for use with the OverloadedStrings
extension.
data GlobalAttributes Source #
Represents a list of top-level list of Attribute
s for the
entire graph/sub-graph. Note that GraphAttrs
also applies to
DotSubGraph
s.
Note that Dot allows a single Attribute
to be listed on a line;
if this is the case then when parsing, the type of Attribute
it
is determined and that type of GlobalAttribute
is created.
A node in DotGraph
.
DotNode | |
|
An edge in DotGraph
.
DotEdge | |
|
Helper types for looking up information within a DotRepr
.
type ClusterLookup = Map (Maybe GraphID) ([Path], GlobalAttributes) Source #
The available information for each cluster; the [
denotes all locations where that particular cluster is located
(more than one location can indicate possible problems).Path
]
type NodeLookup n = Map n (Path, Attributes) Source #
The available information on each DotNode
(both explicit and implicit).
type Path = Seq (Maybe GraphID) Source #
The path of clusters that must be traversed to reach this spot.
graphStructureInformationClean :: DotRepr dg n => dg n -> (GlobalAttributes, ClusterLookup) Source #
A variant of graphStructureInformation
with default attributes
removed and only attributes usable by graph/cluster kept (where
applicable).
nodeInformationClean :: DotRepr dg n => Bool -> dg n -> NodeLookup n Source #
A variant of nodeInformation
with default attributes removed
and only attributes used by nodes kept.
edgeInformationClean :: DotRepr dg n => Bool -> dg n -> [DotEdge n] Source #
A variant of edgeInformation
with default attributes removed
and only attributes used by edges kept.
Obtaining the DotNode
s and DotEdges
.
graphNodes :: DotRepr dg n => dg n -> [DotNode n] Source #
graphEdges :: DotRepr dg n => dg n -> [DotEdge n] Source #
Printing and parsing a DotRepr
.
printDotGraph :: PrintDotRepr dg n => dg n -> Text Source #
The actual Dot code for an instance of DotRepr
. Note that it
is expected that
(this might not be true the other way around due to un-parseable
components).parseDotGraph
. printDotGraph
== id
parseDotGraph :: ParseDotRepr dg n => Text -> dg n Source #
Parse a limited subset of the Dot language to form an instance of
DotRepr
. Each instance may have its own limitations on what
may or may not be parseable Dot code.
Also removes any comments, etc. before parsing.
parseDotGraphLiberally :: ParseDotRepr dg n => Text -> dg n Source #
As with parseDotGraph
, but if an Attribute
cannot be parsed
strictly according to the known rules, let it fall back to being
parsed as an UnknownAttribute
. This is especially useful for
when using a version of Graphviz that is either newer (especially
for the XDot attributes) or older (when some attributes have
changed) but you'd still prefer it to parse rather than throwing
an error.
Limitations and documentation
Printing of Dot code is done as strictly as possible, whilst
parsing is as permissive as possible. For example, if the types
allow it then "2"
will be parsed as an Int
value. Note that
quoting and escaping of textual values is done automagically.
A summary of known limitations/differences:
- When creating
GraphID
values for graphs and sub-graphs, you should ensure that none of them have the same printed value as one of the node identifiers values to avoid any possible problems. - If you want any
GlobalAttributes
in a sub-graph and want them to only apply to that sub-graph, then you must ensure it does indeed have a validGraphID
. - All sub-graphs which represent clusters should have unique identifiers (well, only if you want them to be generated sensibly).
- If eventually outputting to a format such as SVG, then you should make sure to specify an identifier for the overall graph, as that is used as the title of the resulting image.
- Whilst the graphs, etc. are polymorphic in their node type, you should ensure that you use a relatively simple node type (that is, it only covers a single line, etc.).
- Also, whilst Graphviz allows you to mix the types used for nodes, this library requires/assumes that they are all the same type (but you can use a sum-type).
DotEdge
defines an edge(a, b)
(with an edge going froma
tob
); in Dot parlance the edge has a head ata
and a tail atb
. Care must be taken when using the relatedHead*
andTail*
Attribute
s. See the differences section in Data.GraphViz.Attributes for more information.- It is common to see multiple edges defined on the one line in Dot
(e.g.
n1 -> n2 -> n3
means to create a directed edge fromn1
ton2
and fromn2
ton3
). These types of edge definitions are parseable; however, they are converted to singleton edges. - It is not yet possible to create or parse edges with subgraphs/clusters as one of the end points.
- The parser will strip out comments and pre-processor lines, join together multiline statements and concatenate split strings together. However, pre-processing within HTML-like labels is currently not supported.
- Graphviz allows a node to be "defined" twice (e.g. the actual
node definition, and then in a subgraph with extra global attributes
applied to it). This actually represents the same node, but when
parsing they will be considered as separate
DotNode
s (such thatgraphNodes
will return both "definitions").canonicalise
from Data.GraphViz.Algorithms can be used to fix this.
See Data.GraphViz.Attributes.Complete for more limitations.