graphviz-2999.11.0.0: Graphviz bindings for Haskell.

MaintainerIvan.Miljenovic@gmail.com

Data.GraphViz.Attributes

Contents

Description

This module defines the various attributes that different parts of a Graphviz graph can have. These attributes are based on the documentation found at: http://graphviz.org/doc/info/attrs.html

For more information on usage, etc. please see that document.

A summary of known current constraints/limitations/differences:

  • There might still be a few cases where quotes are still not escaped/parsed correctly; if you find such a situation, please let me know; however, you should be able to use String values directly without having to worry about when quotes are required or extra escaping of quote characters as PrintDot and ParseDot instances for String should take care of that for you.
  • Note that for an edge, in Dot parlance if the edge goes from A to B, then A is the tail node and B is the head node (since A is at the tail end of the arrow).
  • ColorList, DoubleList and PointfList are defined as actual lists (LayerList needs a newtype for other reasons). All of these are assumed to be non-empty lists. Note that for the Color Attribute for node values, only a single Color is valid; edges are allowed multiple colors with one spline/arrow per color in the list (but you must have at least one Color in the list). This might be changed in future.
  • Style is implemented as a list of StyleItem values; note that empty lists are not allowed.
  • A lot of values have a possible value of none. These now have custom constructors. In fact, most constructors have been expanded upon to give an idea of what they represent rather than using generic terms.
  • PointF and Point have been combined. The optional ! and third value for Point are also available.
  • Rect uses two Point values to denote the lower-left and top-right corners.
  • The two LabelLoc attributes have been combined.
  • The defined LayerSep is not used to parse LayerRange or LayerList; the default ([' ', :, '\t']) is instead used.
  • SplineType has been replaced with [Spline].
  • Only polygon-based Shapes are available.
  • Not every Attribute is fully documented/described. However, all those which have specific allowed values should be covered.
  • Deprecated Overlap algorithms are not defined.
  • The global Orientation attribute is not defined, as it is difficult to distinguish from the node-based Orientation Attribute; also, its behaviour is duplicated by Rotate.

Synopsis

The actual Dot attributes.

data Attribute Source

These attributes have been implemented in a permissive manner: that is, rather than split them up based on which type of value they are allowed, they have all been included in the one data type, with functions to determine if they are indeed valid for what they're being applied to.

To interpret the Valid for listings:

G
Valid for Graphs.
C
Valid for Clusters.
S
Valid for Sub-Graphs (and also Clusters).
N
Valid for Nodes.
E
Valid for Edges.

The Default listings are those that the various Graphviz commands use if that Attribute isn't specified (in cases where this is none, this is equivalent to a Nothing value; that is, no value is used). The Parsing Default listings represent what value is used (i.e. corresponds to True) when the Attribute name is listed on its own in Dot source code.

Please note that the UnknownAttribute Attribute is defined for backwards-compatibility purposes only (specifically, to be able to parse old Dot code containing Attributes that are no longer valid). As such, this Attribute should not be used directly. The attribute name is assumed to match the first type of identifier listed in Data.GraphViz.Printing (i.e. a non-number that does not need to be quoted).

Constructors

Damping Double

Valid for: G; Default: 0.99; Minimum: 0.0; Notes: neato only

K Double

Valid for: GC; Default: 0.3; Minimum: 0; Notes: sfdp, fdp only

URL EscString

Valid for: ENGC; Default: none; Notes: svg, postscript, map only

ArrowHead ArrowType

Valid for: E; Default: normal

ArrowSize Double

Valid for: E; Default: 1.0; Minimum: 0.0

ArrowTail ArrowType

Valid for: E; Default: normal

Aspect AspectType

Valid for: G; Notes: dot only

Bb Rect

Valid for: G; Notes: write only

BgColor Color

Valid for: GC; Default: X11Color Transparent

Center Bool

Valid for: G; Default: False; Parsing Default: True

Charset String

Valid for: G; Default: "UTF-8"

ClusterRank ClusterMode

Valid for: G; Default: Local; Notes: dot only

ColorScheme ColorScheme

Valid for: ENCG; Default: X11

Color [Color]

Valid for: ENC; Default: X11Color Black

Comment String

Valid for: ENG; Default: ""

Compound Bool

Valid for: G; Default: False; Parsing Default: True; Notes: dot only

Concentrate Bool

Valid for: G; Default: False; Parsing Default: True

Constraint Bool

Valid for: E; Default: True; Parsing Default: True; Notes: dot only

Decorate Bool

Valid for: E; Default: False; Parsing Default: True

DefaultDist Double

Valid for: G; Default: 1+(avg. len)*sqrt(|V|); Minimum: epsilon; Notes: neato only

Dimen Int

Valid for: G; Default: 2; Minimum: 2; Notes: sfdp, fdp, neato only

Dim Int

Valid for: G; Default: 2; Minimum: 2; Notes: sfdp, fdp, neato only

Dir DirType

Valid for: E; Default: Forward (directed), NoDir (undirected)

DirEdgeConstraints DEConstraints

Valid for: G; Default: NoConstraints; Parsing Default: EdgeConstraints; Notes: neato only

Distortion Double

Valid for: N; Default: 0.0; Minimum: -100.0

DPI Double

Valid for: G; Default: 96.0, 0.0; Notes: svg, bitmap output only; "resolution" is a synonym

EdgeURL EscString

Valid for: E; Default: ""; Notes: svg, map only

EdgeTarget EscString

Valid for: E; Default: none; Notes: svg, map only

EdgeTooltip EscString

Valid for: E; Default: ""; Notes: svg, cmap only

Epsilon Double

Valid for: G; Default: .0001 * # nodes (mode == KK), .0001 (mode == Major); Notes: neato only

ESep DPoint

Valid for: G; Default: +3; Notes: not dot

FillColor Color

Valid for: NC; Default: X11Color LightGray (nodes), X11Color Black (clusters)

FixedSize Bool

Valid for: N; Default: False; Parsing Default: True

FontColor Color

Valid for: ENGC; Default: X11Color Black

FontName String

Valid for: ENGC; Default: "Times-Roman"

FontNames String

Valid for: G; Default: ""; Notes: svg only

FontPath String

Valid for: G; Default: system-dependent

FontSize Double

Valid for: ENGC; Default: 14.0; Minimum: 1.0

Group String

Valid for: N; Default: ""; Notes: dot only

HeadURL EscString

Valid for: E; Default: ""; Notes: svg, map only

HeadClip Bool

Valid for: E; Default: True; Parsing Default: True

HeadLabel Label

Valid for: E; Default: ""

HeadPort PortPos

Valid for: E; Default: PP CenterPoint

HeadTarget EscString

Valid for: E; Default: none; Notes: svg, map only

HeadTooltip EscString

Valid for: E; Default: ""; Notes: svg, cmap only

Height Double

Valid for: N; Default: 0.5; Minimum: 0.02

ID Label

Valid for: GNE; Default: ""; Notes: svg, postscript, map only

Image String

Valid for: N; Default: ""

ImageScale ScaleType

Valid for: N; Default: NoScale; Parsing Default: UniformScale

LabelURL EscString

Valid for: E; Default: ""; Notes: svg, map only

LabelAngle Double

Valid for: E; Default: -25.0; Minimum: -180.0

LabelDistance Double

Valid for: E; Default: 1.0; Minimum: 0.0

LabelFloat Bool

Valid for: E; Default: False; Parsing Default: True

LabelFontColor Color

Valid for: E; Default: X11Color Black

LabelFontName String

Valid for: E; Default: "Times-Roman"

LabelFontSize Double

Valid for: E; Default: 14.0; Minimum: 1.0

LabelJust Justification

Valid for: GC; Default: JCenter

LabelLoc VerticalPlacement

Valid for: GCN; Default: VTop (clusters), VBottom (root graphs), VCenter (nodes)

LabelTarget EscString

Valid for: E; Default: none; Notes: svg, map only

LabelTooltip EscString

Valid for: E; Default: ""; Notes: svg, cmap only

Label Label

Valid for: ENGC; Default: StrLabel "N" (nodes), StrLabel "" (otherwise)

Landscape Bool

Valid for: G; Default: False; Parsing Default: True

LayerSep String

Valid for: G; Default: " :t"

Layers LayerList

Valid for: G; Default: ""

Layer LayerRange

Valid for: EN; Default: ""

Layout String

Valid for: G; Default: ""

Len Double

Valid for: E; Default: 1.0 (neato), 0.3 (fdp); Notes: fdp, neato only

LevelsGap Double

Valid for: G; Default: 0.0; Notes: neato only

Levels Int

Valid for: G; Default: MAXINT; Minimum: 0; Notes: sfdp only

LHead String

Valid for: E; Default: ""; Notes: dot only

LPos Point

Valid for: EGC; Notes: write only

LTail String

Valid for: E; Default: ""; Notes: dot only

Margin DPoint

Valid for: NG; Default: device-dependent

MaxIter Int

Valid for: G; Default: 100 * # nodes (mode == KK), 200 (mode == Major), 600 (fdp); Notes: fdp, neato only

MCLimit Double

Valid for: G; Default: 1.0; Notes: dot only

MinDist Double

Valid for: G; Default: 1.0; Minimum: 0.0; Notes: circo only

MinLen Int

Valid for: E; Default: 1; Minimum: 0; Notes: dot only

Model Model

Valid for: G; Default: ShortPath; Notes: neato only

Mode ModeType

Valid for: G; Default: Major; Notes: neato only

Mosek Bool

Valid for: G; Default: False; Parsing Default: True; Notes: neato only; requires the Mosek software

NodeSep Double

Valid for: G; Default: 0.25; Minimum: 0.02; Notes: dot only

NoJustify Bool

Valid for: GCNE; Default: False; Parsing Default: True

Normalize Bool

Valid for: G; Default: False; Parsing Default: True; Notes: not dot

Nslimit1 Double

Valid for: G; Notes: dot only

Nslimit Double

Valid for: G; Notes: dot only

Ordering String

Valid for: G; Default: ""; Notes: dot only

Orientation Double

Valid for: N; Default: 0.0; Minimum: 360.0

OutputOrder OutputMode

Valid for: G; Default: BreadthFirst

OverlapScaling Double

Valid for: G; Default: -4; Minimum: -1.0e10; Notes: prism only

Overlap Overlap

Valid for: G; Default: KeepOverlaps; Parsing Default: KeepOverlaps; Notes: not dot

PackMode PackMode

Valid for: G; Default: PackNode; Notes: not dot

Pack Pack

Valid for: G; Default: False; Parsing Default: DoPack; Notes: not dot

Pad DPoint

Valid for: G; Default: DVal 0.0555 (4 points)

PageDir PageDir

Valid for: G; Default: BL

Page Point

Valid for: G

PenColor Color

Valid for: C; Default: X11Color Black

PenWidth Double

Valid for: CNE; Default: 1.0; Minimum: 0.0

Peripheries Int

Valid for: NC; Default: shape default (nodes), 1 (clusters); Minimum: 0

Pin Bool

Valid for: N; Default: False; Parsing Default: True; Notes: fdp, neato only

Pos Pos

Valid for: EN

QuadTree QuadType

Valid for: G; Default: NormalQT; Parsing Default: NormalQT; Notes: sfdp only

Quantum Double

Valid for: G; Default: 0.0; Minimum: 0.0

RankDir RankDir

Valid for: G; Default: TB; Notes: dot only

RankSep [Double]

Valid for: G; Default: 0.5 (dot), 1.0 (twopi); Minimum: 0.02; Notes: twopi, dot only

Rank RankType

Valid for: S; Notes: dot only

Ratio Ratios

Valid for: G

Rects Rect

Valid for: N; Notes: write only

Regular Bool

Valid for: N; Default: False; Parsing Default: True

ReMinCross Bool

Valid for: G; Default: False; Parsing Default: True; Notes: dot only

RepulsiveForce Double

Valid for: G; Default: 1.0; Minimum: 0.0; Notes: sfdp only

Root Root

Valid for: GN; Default: NodeName "" (graphs), NotCentral (nodes); Parsing Default: IsCentral; Notes: circo, twopi only

Rotate Int

Valid for: G; Default: 0

SameHead String

Valid for: E; Default: ""; Notes: dot only

SameTail String

Valid for: E; Default: ""; Notes: dot only

SamplePoints Int

Valid for: N; Default: 8 (output), 20 (overlap and image maps)

SearchSize Int

Valid for: G; Default: 30; Notes: dot only

Sep DPoint

Valid for: G; Default: +4; Notes: not dot

ShapeFile String

Valid for: N; Default: ""

Shape Shape

Valid for: N; Default: Ellipse

ShowBoxes Int

Valid for: ENG; Default: 0; Minimum: 0; Notes: dot only

Sides Int

Valid for: N; Default: 4; Minimum: 0

Size Point

Valid for: G

Skew Double

Valid for: N; Default: 0.0; Minimum: -100.0

Smoothing SmoothType

Valid for: G; Default: NoSmooth; Notes: sfdp only

SortV Word16

Valid for: GCN; Default: 0; Minimum: 0

Splines EdgeType

Valid for: G; Parsing Default: SplineEdges

Start StartType

Valid for: G; Default: ""; Notes: fdp, neato only

StyleSheet String

Valid for: G; Default: ""; Notes: svg only

Style [StyleItem]

Valid for: ENC

TailURL EscString

Valid for: E; Default: ""; Notes: svg, map only

TailClip Bool

Valid for: E; Default: True; Parsing Default: True

TailLabel Label

Valid for: E; Default: ""

TailPort PortPos

Valid for: E; Default: center

TailTarget EscString

Valid for: E; Default: none; Notes: svg, map only

TailTooltip EscString

Valid for: E; Default: ""; Notes: svg, cmap only

Target EscString

Valid for: ENGC; Default: none; Notes: svg, map only

Tooltip EscString

Valid for: NEC; Default: ""; Notes: svg, cmap only

TrueColor Bool

Valid for: G; Parsing Default: True; Notes: bitmap output only

Vertices [Point]

Valid for: N; Notes: write only

ViewPort ViewPort

Valid for: G; Default: none

VoroMargin Double

Valid for: G; Default: 0.05; Minimum: 0.0; Notes: not dot

Weight Double

Valid for: E; Default: 1.0; Minimum: 0 (dot), 1 (neato,fdp,sfdp)

Width Double

Valid for: N; Default: 0.75; Minimum: 0.01

Z Double

Valid for: N; Default: 0.0; Minimum: -MAXFLOAT, -1000

UnknownAttribute String String

Valid for: Assumed valid for all; the fields are Attribute name and value respectively.

sameAttribute :: Attribute -> Attribute -> BoolSource

Determine if two Attributes are the same type of Attribute.

Validity functions on Attribute values.

usedByGraphs :: Attribute -> BoolSource

Determine if this Attribute is valid for use with Graphs.

usedBySubGraphs :: Attribute -> BoolSource

Determine if this Attribute is valid for use with SubGraphs.

usedByClusters :: Attribute -> BoolSource

Determine if this Attribute is valid for use with Clusters.

usedByNodes :: Attribute -> BoolSource

Determine if this Attribute is valid for use with Nodes.

usedByEdges :: Attribute -> BoolSource

Determine if this Attribute is valid for use with Edges.

Value types for Attributes.

Labels

type EscString = StringSource

Some Attributes (mainly label-like ones) take a String argument that allows for extra escape codes. This library doesn't do any extra checks or special parsing for these escape codes, but usage of EscString rather than String indicates that the Graphviz tools will recognise these extra escape codes for these Attributes.

The extra escape codes include (note that these are all Strings):

\N
Replace with the name of the node (for Node Attributes).
\G
Replace with the name of the graph (for Node Attributes) or the name of the graph or cluster, whichever is applicable (for Graph, Cluster and Edge Attributes).
\E
Replace with the name of the edge, formed by the two adjoining nodes and the edge type (for Edge Attributes).
\T
Replace with the name of the tail node (for Edge Attributes).
\H
Replace with the name of the head node (for Edge Attributes).
\L
Replace with the object's label (for all Attributes).

Also, if the Attribute in question is Label, HeadLabel or TailLabel, then \n, \l and \r split the label into lines centered, left-justified and right-justified respectively.

data Label Source

Constructors

StrLabel EscString 
HtmlLabel HtmlLabel

If PlainText is used, the HtmlLabel value is the entire "shape"; if anything else except PointShape is used then the HtmlLabel is embedded within the shape.

RecordLabel RecordFields

For nodes only; requires either Record or MRecord as the shape.

class Labellable a whereSource

A convenience class to make it easier to create labels. It is highly recommended that you make any other types that you wish to create labels from an instance of this class, preferably via the String instance.

Methods

toLabel :: a -> AttributeSource

Types representing the Dot grammar for records.

type RecordFields = [RecordField]Source

A RecordFields value should never be empty.

data RecordField Source

Specifies the sub-values of a record-based label. By default, the cells are laid out horizontally; use FlipFields to change the orientation of the fields (can be applied recursively). To change the default orientation, use RankDir.

Constructors

LabelledTarget PortName EscString 
PortName PortName

Will result in no label for that cell.

FieldLabel EscString 
FlipFields RecordFields 

data Rect Source

Should only have 2D points (i.e. created with createPoint).

Constructors

Rect Point Point 

Nodes

data Shape Source

Constructors

BoxShape

Has synonyms of rect and rectangle.

Polygon 
Ellipse 
Circle 
PointShape 
Egg 
Triangle 
PlainText

Has synonym of none.

DiamondShape 
Trapezium 
Parallelogram 
House 
Pentagon 
Hexagon 
Septagon 
Octagon 
DoubleCircle 
DoubleOctagon 
TripleOctagon 
InvTriangle 
InvTrapezium 
InvHouse 
MDiamond 
MSquare 
MCircle 
Note 
Tab 
Folder 
Box3D 
Component 
Record

Must specify the record shape with a Label.

MRecord

Must specify the record shape with a Label.

Edges

data EdgeType Source

Controls how (and if) edges are represented.

Modifying where edges point

newtype PortName Source

Specifies a name for ports (used also in record-based and HTML-like labels). Note that it is not valid for a PortName value to contain a colon (:) character; it is assumed that it doesn't.

Constructors

PN 

Fields

portName :: String
 

Instances

Eq PortName 
Ord PortName 
Read PortName 
Show PortName 
ParseDot PortName 
PrintDot PortName 
Labellable PortName

A shorter variant than using PortName from RecordField.

Labellable (PortName, EscString)

A shorter variant than using LabelledTarget.

Arrows

newtype ArrowType Source

Dot has a basic grammar of arrow shapes which allows usage of up to 1,544,761 different shapes from 9 different basic ArrowShapes. Note that whilst an explicit list is used in the definition of ArrowType, there must be at least one tuple and a maximum of 4 (since that is what is required by Dot). For more information, see: http://graphviz.org/doc/info/arrows.html

The 19 basic arrows shown on the overall attributes page have been defined below as a convenience. Parsing of the 5 backward-compatible special cases is also supported.

Constructors

AType [(ArrowModifier, ArrowShape)] 

data ArrowSide Source

Represents which side (when looking towards the node the arrow is pointing to) is drawn.

Constructors

LeftSide 
RightSide 
BothSides 

Default ArrowType aliases.

The 9 primitive ArrowShapes.

5 derived Arrows.

5 supported cases for backwards compatibility

ArrowModifier instances

noMods :: ArrowModifierSource

Apply no modifications to an ArrowShape.

Positioning

data Point Source

Constructors

Point 

Fields

xCoord :: Double
 
yCoord :: Double
 
zCoord :: Maybe Double

Can only be Just for Dim 3 or greater.

forcePos :: Bool

Input to Graphviz only: specify that the node position should not change.

createPoint :: Double -> Double -> PointSource

Create a point with only x and y values.

data Spline Source

The number of points in the list must be equivalent to 1 mod 3; note that this is not checked.

Constructors

Spline (Maybe Point) (Maybe Point) [Point] 

data DPoint Source

Either a Double or a (2D) Point (i.e. created with createPoint).

Constructors

DVal Double 
PVal Point 

Layout

data Root Source

Specify the root node either as a Node attribute or a Graph attribute.

Constructors

IsCentral

For Nodes only

NotCentral

For Nodes only

NodeName String

For Graphs only

data Pack Source

Constructors

DoPack 
DontPack 
PackMargin Int

If non-negative, then packs; otherwise doesn't.

data PackMode Source

Constructors

PackNode 
PackClust 
PackGraph 
PackArray Bool Bool (Maybe Int)

Sort by cols, sort by user, number of rows/cols

data PageDir Source

Upper-case first character is major order; lower-case second character is minor order.

Constructors

Bl 
Br 
Tl 
Tr 
Rb 
Rt 
Lb 
Lt 

Modes

Layers

data LayerID Source

You should not have any layer separator characters for the LRName option, as they won't be parseable.

Constructors

AllLayers 
LRInt Int 
LRName String

Should not be a number of all.

newtype LayerList Source

A non-empty list of layer names. The names should all be LRName values, and when printed will use an arbitrary character from defLayerSep.

Constructors

LL [LayerID] 

defLayerSep :: [Char]Source

The default separators for LayerSep.

Stylistic

data StyleItem Source

An individual style item. Except for DD, the [String] should be empty.

Constructors

SItem StyleName [String] 

data StyleName Source

Constructors

Dashed

Nodes and Edges

Dotted

Nodes and Edges

Solid

Nodes and Edges

Bold

Nodes and Edges

Invisible

Nodes and Edges

Filled

Nodes and Clusters

Diagonals

Nodes only

Rounded

Nodes and Clusters

DD String

Device Dependent