graphviz-2999.13.0.3: Bindings to Graphviz for graph visualisation.

MaintainerIvan.Miljenovic@gmail.com
Safe HaskellSafe-Infered

Data.GraphViz.Types.Generalised

Contents

Description

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

Documentation

data DotGraph n Source

The internal representation of a generalised graph in Dot form.

Constructors

DotGraph 

Fields

strictGraph :: Bool

If True, no multiple edges are drawn.

directedGraph :: Bool
 
graphID :: Maybe GraphID
 
graphStatements :: DotStatements n
 

Instances

Functor DotGraph

Assumed to be an injective mapping function.

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

Sub-components of a DotGraph.

Re-exported from Data.GraphViz.Types.

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 
Int Int 
Dbl Double 

data GlobalAttributes Source

Represents a list of top-level list of Attributes for the entire graph/sub-graph. Note that GraphAttrs also applies to DotSubGraphs.

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.

Constructors

GraphAttrs 

Fields

attrs :: Attributes
 
NodeAttrs 

Fields

attrs :: Attributes
 
EdgeAttrs 

Fields

attrs :: Attributes
 

data DotNode n Source

A node in DotGraph.

Constructors

DotNode 

Instances

Functor DotNode 
Eq n => Eq (DotNode n) 
Ord n => Ord (DotNode n) 
Read n => Read (DotNode n) 
Show n => Show (DotNode n) 
ParseDot n => ParseDot (DotNode n) 
PrintDot n => PrintDot (DotNode n) 

data DotEdge n Source

An edge in DotGraph.

Constructors

DotEdge 

Fields

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

Instances

Functor DotEdge 
Eq n => Eq (DotEdge n) 
Ord n => Ord (DotEdge n) 
Read n => Read (DotEdge n) 
Show n => Show (DotEdge n) 
ParseDot n => ParseDot (DotEdge n) 
PrintDot n => PrintDot (DotEdge n)