Copyright | (c) Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
The generalised Dot representation most closely matches the implementation of actual Dot code, as it places no restrictions on ordering of elements, etc. As such it should be able to parse any existing Dot code (taking into account the parsing limitations/assumptions).
The sample graph could be implemented (this is actually a prettied version of parsing in the Dot code) as:
DotGraph { strictGraph = False , directedGraph = True , graphID = Just (Str "G") , graphStatements = Seq.fromList [ SG $ DotSG { isCluster = True , subGraphID = Just (Int 0) , subGraphStmts = Seq.fromList [ GA $ GraphAttrs [style filled] , GA $ GraphAttrs [color LightGray] , GA $ NodeAttrs [style filled, color White] , DE $ DotEdge "a0" "a1" [] , DE $ DotEdge "a1" "a2" [] , DE $ DotEdge "a2" "a3" [] , GA $ GraphAttrs [textLabel "process #1"]]} , SG $ DotSG { isCluster = True , subGraphID = Just (Int 1) , subGraphStmts = fromList [ GA $ NodeAttrs [style filled] , DE $ DotEdge "b0" "b1" [] , DE $ DotEdge "b1" "b2" [] , DE $ DotEdge "b2" "b3" [] , GA $ GraphAttrs [textLabel "process #2"] , GA $ GraphAttrs [color Blue]]} , DE $ DotEdge "start" "a0" [] , DE $ DotEdge "start" "b0" [] , DE $ DotEdge "a1" "b3" [] , DE $ DotEdge "b2" "a3" [] , DE $ DotEdge "a3" "a0" [] , DE $ DotEdge "a3" "end" [] , DE $ DotEdge "b3" "end" [] , DN $ DotNode "start" [shape MDiamond] , DN $ DotNode "end" [shape MSquare]]}
Synopsis
- data DotGraph n = DotGraph {}
- class DotRepr dg n => FromGeneralisedDot dg n where
- fromGeneralised :: DotGraph n -> dg n
- type DotStatements n = Seq (DotStatement n)
- data DotStatement n
- = GA GlobalAttributes
- | SG (DotSubGraph n)
- | DN (DotNode n)
- | DE (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
The internal representation of a generalised graph in Dot form.
DotGraph | |
|
Instances
class DotRepr dg n => FromGeneralisedDot dg n where Source #
This class is useful for being able to parse in a dot graph as a generalised one, and then convert it to your preferred representation.
This can be seen as a semi-inverse of fromCanonical
.
fromGeneralised :: DotGraph n -> dg n Source #
Instances
Ord n => FromGeneralisedDot DotGraph n Source # | |
Defined in Data.GraphViz.Types.Generalised fromGeneralised :: DotGraph0 n -> DotGraph n Source # | |
Ord n => FromGeneralisedDot DotGraph n Source # | |
Defined in Data.GraphViz.Types.Generalised fromGeneralised :: DotGraph n -> DotGraph n Source # | |
Ord n => FromGeneralisedDot DotGraph n Source # | |
Defined in Data.GraphViz.Types.Graph fromGeneralised :: DotGraph0 n -> DotGraph n Source # |
Sub-components of a DotGraph
.
type DotStatements n = Seq (DotStatement n) Source #
data DotStatement n Source #
GA GlobalAttributes | |
SG (DotSubGraph n) | |
DN (DotNode n) | |
DE (DotEdge n) |
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 # | |