graphviz-2999.20.1.0: Bindings to Graphviz for graph visualisation.

Copyright(c) Ivan Lazar Miljenovic
License3-Clause BSD-style
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.GraphViz.Types

Contents

Description

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.

Synopsis

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.

Methods

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 DotNodes 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 DotEdges 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).

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

Defined in Data.GraphViz.Types

Ord n => DotRepr DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Generalised

Ord n => DotRepr DotGraph n Source # 
Instance details

Defined in Data.GraphViz.Types.Graph

class PrintDot a where Source #

A class used to correctly print parts of the Graphviz Dot language. Minimal implementation is unqtDot.

Minimal complete definition

unqtDot

Methods

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).

Instances
PrintDot Bool Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Char Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Double Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Int Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Integer Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Word8 Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Word16 Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Version Source #

Ignores versionTags and assumes 'not . null . versionBranch' (usually you want 'length . versionBranch == 2').

Instance details

Defined in Data.GraphViz.Printing

PrintDot Text Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot Text Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot BrewerName Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot BrewerScheme Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot ColorScheme Source # 
Instance details

Defined in Data.GraphViz.Printing

PrintDot GraphvizCommand Source # 
Instance details

Defined in Data.GraphViz.Commands.Available

PrintDot CompassPoint Source # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

PrintDot PortPos Source # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

PrintDot PortName Source # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

PrintDot X11Color Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors.X11

PrintDot SVGColor Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors.SVG

PrintDot WeightedColor Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors

PrintDot Color Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors

PrintDot Style Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Side Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Scale Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot CellFormat Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot VAlign Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Align Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Attribute Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Img Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Cell Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Row Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Table Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Format Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot TextItem Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot Label Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

PrintDot NodeSize Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Normalized Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Number Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Ratios Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Justification Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ScaleType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Paths Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot VerticalPlacement Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot FocusType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ViewPort Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot StyleName Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot StyleItem Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot STStyle Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot StartType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot SmoothType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Shape Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot RankDir Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot RankType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Root Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot QuadType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Spline Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot PageDir Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot EdgeType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Pos Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot PackMode Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Pack Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot OutputMode Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Order Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerList Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerID Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerRangeElem Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerListSep Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LayerSep Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Overlap Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Point Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot LabelScheme Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot RecordField Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Label Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Model Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ModeType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot GraphSize Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot SVGFontNames Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot DPoint Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot DEConstraints Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot DirType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ClusterMode Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot Rect Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

PrintDot ArrowSide Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowFill Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowModifier Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowShape Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot ArrowType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

PrintDot Attribute Source # 
Instance details

Defined in Data.GraphViz.Attributes.Complete

PrintDot GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot GraphID Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

PrintDot a => PrintDot [a] Source # 
Instance details

Defined in Data.GraphViz.Printing

Methods

unqtDot :: [a] -> DotCode Source #

toDot :: [a] -> DotCode Source #

unqtListToDot :: [[a]] -> DotCode Source #

listToDot :: [[a]] -> DotCode Source #

PrintDot n => PrintDot (DotEdge 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

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

Defined in Data.GraphViz.Types.Canonical

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

Defined in Data.GraphViz.Types.Canonical

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

Defined in Data.GraphViz.Types.Canonical

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

Defined in Data.GraphViz.Types.Generalised

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

Defined in Data.GraphViz.Types.Generalised

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

Defined in Data.GraphViz.Types.Generalised

PrintDot n => PrintDot (DotGraph n) Source #

Uses the PrintDot instance for canonical DotGraphs.

Instance details

Defined in Data.GraphViz.Types.Graph

class ParseDot a where Source #

Minimal complete definition

parseUnqt

Instances
ParseDot Bool Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Char Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Double Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Int Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Integer Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Word8 Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Word16 Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Version Source #

Ignores versionTags and assumes 'not . null . versionBranch' (usually you want 'length . versionBranch == 2') and that all such values are non-negative.

Instance details

Defined in Data.GraphViz.Parsing

ParseDot Text Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot Text Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot BrewerName Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot BrewerScheme Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot ColorScheme Source # 
Instance details

Defined in Data.GraphViz.Parsing

ParseDot GraphvizCommand Source # 
Instance details

Defined in Data.GraphViz.Commands.Available

ParseDot CompassPoint Source # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

ParseDot PortPos Source # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

ParseDot PortName Source # 
Instance details

Defined in Data.GraphViz.Attributes.Internal

ParseDot X11Color Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors.X11

ParseDot SVGColor Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors.SVG

ParseDot WeightedColor Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors

ParseDot Color Source # 
Instance details

Defined in Data.GraphViz.Attributes.Colors

ParseDot Style Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Side Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Scale Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot CellFormat Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot VAlign Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Align Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Attribute Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Img Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Cell Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Row Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Table Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Format Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot TextItem Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot Label Source # 
Instance details

Defined in Data.GraphViz.Attributes.HTML

ParseDot NodeSize Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Normalized Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Number Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Ratios Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Justification Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot ScaleType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Paths Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot VerticalPlacement Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot FocusType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot ViewPort Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot StyleName Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot StyleItem Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot STStyle Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot StartType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot SmoothType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Shape Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot RankDir Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot RankType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Root Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot QuadType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Spline Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot PageDir Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot EdgeType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Pos Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot PackMode Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Pack Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot OutputMode Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Order Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot LayerList Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot LayerID Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot LayerRangeElem Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot LayerListSep Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot LayerSep Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Overlap Source #

Note that overlap=false defaults to PrismOverlap Nothing, but if the Prism library isn't available then it is equivalent to VoronoiOverlap.

Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Point Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot LabelScheme Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot RecordField Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Label Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Model Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot ModeType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot GraphSize Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot SVGFontNames Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot DPoint Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot DEConstraints Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot DirType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot ClusterMode Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot Rect Source # 
Instance details

Defined in Data.GraphViz.Attributes.Values

ParseDot ArrowSide Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

ParseDot ArrowFill Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

ParseDot ArrowModifier Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

ParseDot ArrowShape Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

ParseDot ArrowType Source # 
Instance details

Defined in Data.GraphViz.Attributes.Arrows

ParseDot Attribute Source # 
Instance details

Defined in Data.GraphViz.Attributes.Complete

ParseDot GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

ParseDot GraphID Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

ParseDot a => ParseDot [a] Source # 
Instance details

Defined in Data.GraphViz.Parsing

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

Defined in Data.GraphViz.Types.Internal.Common

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

Defined in Data.GraphViz.Types.Internal.Common

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

Defined in Data.GraphViz.Types.Canonical

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

Defined in Data.GraphViz.Types.Canonical

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

Defined in Data.GraphViz.Types.Canonical

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

Defined in Data.GraphViz.Types.Generalised

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

Defined in Data.GraphViz.Types.Generalised

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

Defined in Data.GraphViz.Types.Generalised

(Ord n, ParseDot n) => ParseDot (DotGraph n) Source #

Uses the ParseDot instance for generalised DotGraphs.

Instance details

Defined in Data.GraphViz.Types.Graph

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.

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

Defined in Data.GraphViz.Types

(Ord n, PrintDot n) => PrintDotRepr 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.Graph

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.

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

Defined in Data.GraphViz.Types

(Ord n, ParseDot n) => ParseDotRepr 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.Graph

class (PrintDotRepr dg n, ParseDotRepr dg n) => PPDotRepr dg n Source #

This class exists just to make type signatures nicer; all instances of DotRepr should also be an instance of PPDotRepr.

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

Defined in Data.GraphViz.Types

(Ord n, PrintDot n, ParseDot n) => PPDotRepr 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.Graph

Common sub-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 Number Source #

A numeric type with an explicit separation between integers and floating-point values.

Constructors

Int Int 
Dbl Double 

class ToGraphID a where Source #

A convenience class to make it easier to convert data types to GraphID values, e.g. for cluster identifiers.

In most cases, conversion would be via the Text or String instances (e.g. using show).

Methods

toGraphID :: a -> GraphID Source #

Instances
ToGraphID Char Source # 
Instance details

Defined in Data.GraphViz.Types

ToGraphID Double Source # 
Instance details

Defined in Data.GraphViz.Types

ToGraphID Int Source # 
Instance details

Defined in Data.GraphViz.Types

ToGraphID Integer Source #

This instance loses precision by going via Number.

Instance details

Defined in Data.GraphViz.Types

ToGraphID String Source # 
Instance details

Defined in Data.GraphViz.Types

ToGraphID Text Source # 
Instance details

Defined in Data.GraphViz.Types

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 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
Eq GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Ord GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Read GlobalAttributes Source # 
Instance details

Defined in Data.GraphViz.Types.Internal.Common

Show 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
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 #

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 #

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 #

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
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 #

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 #

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 #

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

Helper types for looking up information within a DotRepr.

type ClusterLookup = Map (Maybe GraphID) ([Path], GlobalAttributes) Source #

The available information for each cluster; the [Path] denotes all locations where that particular cluster is located (more than one location can indicate possible problems).

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 DotNodes and DotEdges.

graphNodes :: DotRepr dg n => dg n -> [DotNode n] Source #

Returns all resultant DotNodes in the DotRepr (not including NodeAttrs).

graphEdges :: DotRepr dg n => dg n -> [DotEdge n] Source #

Returns all resultant DotEdges in the DotRepr (not including EdgeAttrs).

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 parseDotGraph . printDotGraph == id (this might not be true the other way around due to un-parseable components).

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 Number 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 valid GraphID.
  • 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 from a to b); in Dot parlance the edge has a head at a and a tail at b. Care must be taken when using the related Head* and Tail* Attributes. 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 from n1 to n2 and from n2 to n3). 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 DotNodes (such that graphNodes will return both "definitions"). canonicalise from Data.GraphViz.Algorithms can be used to fix this.

See Data.GraphViz.Attributes.Complete for more limitations.