graphviz-2999.20.2.0: Bindings to Graphviz for graph visualisation.
Copyright(c) Ivan Lazar Miljenovic
License3-Clause BSD-style
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.GraphViz.Types.Generalised

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

Instances

Instances details
Functor DotGraph Source #

Assumed to be an injective mapping function.

Instance details

Defined in Data.GraphViz.Types.Generalised

Methods

fmap :: (a -> b) -> DotGraph a -> DotGraph b #

(<$) :: a -> DotGraph b -> DotGraph a #

Ord n => DotRepr DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

(Ord n, PrintDot n, ParseDot n) => PPDotRepr DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

(Ord n, ParseDot n) => ParseDotRepr DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

(Ord n, PrintDot n) => PrintDotRepr DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Ord n => FromGeneralisedDot DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Read n => Read (DotGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Show n => Show (DotGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Methods

showsPrec :: Int -> DotGraph n -> ShowS #

show :: DotGraph n -> String #

showList :: [DotGraph n] -> ShowS #

Eq n => Eq (DotGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Methods

(==) :: DotGraph n -> DotGraph n -> Bool #

(/=) :: DotGraph n -> DotGraph n -> Bool #

Ord n => Ord (DotGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Methods

compare :: DotGraph n -> DotGraph n -> Ordering #

(<) :: DotGraph n -> DotGraph n -> Bool #

(<=) :: DotGraph n -> DotGraph n -> Bool #

(>) :: DotGraph n -> DotGraph n -> Bool #

(>=) :: DotGraph n -> DotGraph n -> Bool #

max :: DotGraph n -> DotGraph n -> DotGraph n #

min :: DotGraph n -> DotGraph n -> DotGraph n #

ParseDot n => ParseDot (DotGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

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.

Methods

fromGeneralised :: DotGraph n -> dg n Source #

Instances

Instances details
Ord n => FromGeneralisedDot DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Ord n => FromGeneralisedDot DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Ord n => FromGeneralisedDot DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Graph

Sub-components of a DotGraph.

data DotStatement n Source #

Constructors

GA GlobalAttributes 
SG (DotSubGraph n) 
DN (DotNode n) 
DE (DotEdge n) 

Instances

Instances details
Functor DotStatement Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Methods

fmap :: (a -> b) -> DotStatement a -> DotStatement b #

(<$) :: a -> DotStatement b -> DotStatement a #

Read n => Read (DotStatement n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Show n => Show (DotStatement n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Eq n => Eq (DotStatement n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Ord n => Ord (DotStatement n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

ParseDot n => ParseDot (DotStatement n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotStatement n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

data DotSubGraph n Source #

Instances

Instances details
Functor DotSubGraph Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Methods

fmap :: (a -> b) -> DotSubGraph a -> DotSubGraph b #

(<$) :: a -> DotSubGraph b -> DotSubGraph a #

Read n => Read (DotSubGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Show n => Show (DotSubGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Eq n => Eq (DotSubGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Ord n => Ord (DotSubGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

ParseDot n => ParseDot (DotSubGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotSubGraph n) Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

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 
Num Number 

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

NodeAttrs 

Fields

EdgeAttrs 

Fields

Instances

Instances details
Read GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Show GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Eq GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Ord GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

ParseDot GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

data DotNode n Source #

A node in DotGraph.

Constructors

DotNode 

Instances

Instances details
Functor DotNode Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

fmap :: (a -> b) -> DotNode a -> DotNode b #

(<$) :: a -> DotNode b -> DotNode a #

Read n => Read (DotNode n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Show n => Show (DotNode n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

showsPrec :: Int -> DotNode n -> ShowS #

show :: DotNode n -> String #

showList :: [DotNode n] -> ShowS #

Eq n => Eq (DotNode n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

(==) :: DotNode n -> DotNode n -> Bool #

(/=) :: DotNode n -> DotNode n -> Bool #

Ord n => Ord (DotNode n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

compare :: DotNode n -> DotNode n -> Ordering #

(<) :: DotNode n -> DotNode n -> Bool #

(<=) :: DotNode n -> DotNode n -> Bool #

(>) :: DotNode n -> DotNode n -> Bool #

(>=) :: DotNode n -> DotNode n -> Bool #

max :: DotNode n -> DotNode n -> DotNode n #

min :: DotNode n -> DotNode n -> DotNode n #

ParseDot n => ParseDot (DotNode n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot n => PrintDot (DotNode n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

data DotEdge n Source #

An edge in DotGraph.

Constructors

DotEdge 

Fields

Instances

Instances details
Functor DotEdge Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

fmap :: (a -> b) -> DotEdge a -> DotEdge b #

(<$) :: a -> DotEdge b -> DotEdge a #

Read n => Read (DotEdge n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Show n => Show (DotEdge n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

showsPrec :: Int -> DotEdge n -> ShowS #

show :: DotEdge n -> String #

showList :: [DotEdge n] -> ShowS #

Eq n => Eq (DotEdge n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

(==) :: DotEdge n -> DotEdge n -> Bool #

(/=) :: DotEdge n -> DotEdge n -> Bool #

Ord n => Ord (DotEdge n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Methods

compare :: DotEdge n -> DotEdge n -> Ordering #

(<) :: DotEdge n -> DotEdge n -> Bool #

(<=) :: DotEdge n -> DotEdge n -> Bool #

(>) :: DotEdge n -> DotEdge n -> Bool #

(>=) :: DotEdge n -> DotEdge n -> Bool #

max :: DotEdge n -> DotEdge n -> DotEdge n #

min :: DotEdge n -> DotEdge n -> DotEdge n #

ParseDot n => ParseDot (DotEdge n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot n => PrintDot (DotEdge n) Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common