Copyright | (c) Matthew Sackman Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
A canonical Dot graph requires that within each graph/sub-graph, the statements are in the following order:
- global attributes
- sub-graphs/clusters
- nodes
- edges
This Dot graph representation is ideally suited for converting
other data structures to Dot form (especially with the help of
graphElemsToDot
from Data.GraphViz).
If you require arbitrary ordering of statements, then use Data.GraphViz.Types.Generalised.
The sample graph could be implemented (this is actually the result
of calling canonicalise
from Data.GraphViz.Algorithms on the
generalised one) as:
DotGraph { strictGraph = False , directedGraph = True , graphID = Just (Str "G") , graphStatements = DotStmts { attrStmts = [] , subGraphs = [ DotSG { isCluster = True , subGraphID = Just (Num (Int 0)) , subGraphStmts = DotStmts { attrStmts = [ GraphAttrs [ style filled , color LightGray , textLabel "process #1"] , NodeAttrs [style filled, color White]] , subGraphs = [] , nodeStmts = [ DotNode "a0" [] , DotNode "a1" [] , DotNode "a2" [] , DotNode "a3" []] , edgeStmts = [ DotEdge "a0" "a1" [] , DotEdge "a1" "a2" [] , DotEdge "a2" "a3" [] , DotEdge "a3" "a0" []]}} , DotSG { isCluster = True , subGraphID = Just (Num (Int 1)) , subGraphStmts = DotStmts { attrStmts = [ GraphAttrs [textLabel "process #2", color Blue] , NodeAttrs [style filled]] , subGraphs = [] , nodeStmts = [ DotNode "b0" [] , DotNode "b1" [] , DotNode "b2" [] , DotNode "b3" []] , edgeStmts = [ DotEdge "b0" "b1" [] , DotEdge "b1" "b2" [] , DotEdge "b2" "b3" []]}}] , nodeStmts = [ DotNode "end" [shape MSquare] , DotNode "start" [shape MDiamond]] , edgeStmts = [ DotEdge "start" "a0" [] , DotEdge "start" "b0" [] , DotEdge "a1" "b3" [] , DotEdge "b2" "a3" [] , DotEdge "a3" "end" [] , DotEdge "b3" "end" []]}}
Note that whilst the above graph represents the same Dot graph as specified in Data.GraphViz.Types.Generalised, etc., it may be drawn slightly differently by the various Graphviz tools.
Synopsis
- data DotGraph n = DotGraph {}
- data DotStatements n = DotStmts {
- attrStmts :: [GlobalAttributes]
- subGraphs :: [DotSubGraph n]
- nodeStmts :: [DotNode n]
- edgeStmts :: [DotEdge n]
- data DotSubGraph n = DotSG {}
- data 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
Documentation
A Dot graph in canonical form.
DotGraph | |
|
Instances
Sub-components of a DotGraph
.
data DotStatements n Source #
DotStmts | |
|
Instances
data DotSubGraph n Source #
DotSG | |
|
Instances
Re-exported from Data.GraphViz.Types
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.
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.
Instances
A node in DotGraph
.
DotNode | |
|
Instances
Functor DotNode Source # | |
Eq n => Eq (DotNode n) Source # | |
Ord n => Ord (DotNode n) Source # | |
Defined in Data.GraphViz.Types.Internal.Common | |
Read n => Read (DotNode n) Source # | |
Show n => Show (DotNode n) Source # | |
ParseDot n => ParseDot (DotNode n) Source # | |
PrintDot n => PrintDot (DotNode n) Source # | |
An edge in DotGraph
.
DotEdge | |
|
Instances
Functor DotEdge Source # | |
Eq n => Eq (DotEdge n) Source # | |
Ord n => Ord (DotEdge n) Source # | |
Defined in Data.GraphViz.Types.Internal.Common | |
Read n => Read (DotEdge n) Source # | |
Show n => Show (DotEdge n) Source # | |
ParseDot n => ParseDot (DotEdge n) Source # | |
PrintDot n => PrintDot (DotEdge n) Source # | |