graphviz-2999.1.0.2: GraphViz bindings for Haskell.

MaintainerIvan.Miljenovic@gmail.com

Data.GraphViz.Attributes

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:

  • Parsing of quoted strings might not always work if they are a sub-part of another Attribute (e.g. a quoted name in LayerList). In fact, parsing with quotes is iffy for everything; specifically when they are and aren't allowed.
  • ColorScheme is ignored when parsing Color values
  • ColorList and PointfList are defined as actual lists (but LayerList is not).
  • 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, and feature support for pure Int-based co-ordinates as well as Double ones (i.e. no floating point-only points for Point). The optional ! and third value for Point are not 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.
  • Device-dependent StyleName values are not available.
  • PortPos only has the CompassPoint option, not PortName[:CompassPoint] (since record shapes aren't allowed, and parsing HTML-like labels could be problematic).
  • Not every Attribute is fully documented/described. In particular, a lot of them are listed as having a String value, when actually only certain Strings are allowed.
  • Deprecated Overlap algorithms are not defined.

Synopsis

Documentation

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.

Note also that the default values are taken from the specification page listed above, and might not correspond fully with the names of the permitted values.

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 URL

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: <none>

Center Bool

Valid for: G; Default: false

Charset String

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

ClusterRank ClusterMode

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

Color [Color]

Valid for: ENC; Default: black

ColorScheme String

Valid for: ENCG; Default: ""

Comment String

Valid for: ENG; Default: ""

Compound Bool

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

Concentrate Bool

Valid for: G; Default: false

Constraint Bool

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

Decorate Bool

Valid for: E; Default: false

DefaultDist Double

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

Dim Int

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

Dimen Int

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

Dir DirType

Valid for: E; Default: forward(directed)/none(undirected)

DirEdgeConstraints DEConstraints

Valid for: G; Default: false; 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

EdgeURL URL

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

EdgeTarget String

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

EdgeTooltip String

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: lightgrey(nodes) | black(clusters)

FixedSize Bool

Valid for: N; Default: false

FontColor Color

Valid for: ENGC; Default: 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 URL

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

HeadClip Bool

Valid for: E; Default: true

HeadLabel Label

Valid for: E; Default: ""

HeadPort PortPos

Valid for: E; Default: center

HeadTarget QuotedString

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

HeadTooltip QuotedString

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: false

Label Label

Valid for: ENGC; Default: "N" (nodes) Nothing | "" (otherwise) Nothing

LabelURL URL

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

LabelFontColor Color

Valid for: E; Default: 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: "c"

LabelLoc VerticalPlacement

Valid for: GCN; Default: "t"(clusters) | "b"(root graphs) | "c"(clusters)

LabelTarget String

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

LabelTooltip String

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

Landscape Bool

Valid for: G; Default: false

Layer LayerRange

Valid for: EN; Default: ""

Layers LayerList

Valid for: G; Default: ""

LayerSep String

Valid for: G; Default: " :t"

Layout String

Valid for: G; Default: ""

Len Double

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

Levels Int

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

LevelsGap Double

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

LHead String

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

LP 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

Mode String

Valid for: G; Default: "major"; Notes: neato only

Model String

Valid for: G; Default: "shortpath"; Notes: neato only

Mosek Bool

Valid for: G; Default: false; 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

Normalize Bool

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

Nslimit Double

Valid for: G; Notes: dot only

Nslimit1 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

OrientationGraph String

Valid for: G; Default: ""; Notes: Landscape if "[lL]*" and rotate not defined

OutputOrder OutputMode

Valid for: G; Default: breadthfirst

Overlap Overlap

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

OverlapScaling Double

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

Pack Pack

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

PackMode PackMode

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

Pad DPoint

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

Page Point

Valid for: G

PageDir PageDir

Valid for: G; Default: BL

PenColor Color

Valid for: C; Default: 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; Notes: fdp, neato only

Pos Pos

Valid for: EN

QuadTree QuadType

Valid for: G; Default: "normal"; Notes: sfdp only

Quantum Double

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

Rank RankType

Valid for: S; Notes: dot only

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

Ratio Ratios

Valid for: G

Rects Rect

Valid for: N; Notes: write only

Regular Bool

Valid for: N; Default: false

ReMinCross Bool

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

RepulsiveForce Double

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

Resolution Double

Valid for: G; Default: 96.0 | 0.0; Notes: svg, bitmap output only

Root Root

Valid for: GN; Default: ""(graphs) | false(nodes); 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

Shape Shape

Valid for: N; Default: ellipse

ShapeFile String

Valid for: N; Default: ""

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: "none"; Notes: sfdp only

SortV Int

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

Splines EdgeType

Valid for: G

Start StartType

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

Style Style

Valid for: ENC

StyleSheet String

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

TailURL URL

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

TailClip Bool

Valid for: E; Default: true

TailLabel Label

Valid for: E; Default: ""

TailPort PortPos

Valid for: E; Default: center

TailTarget String

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

TailTooltip String

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

Target String

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

Tooltip String

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

TrueColor Bool

Valid for: G; Notes: bitmap output only

Vertices [Point]

Valid for: N; Notes: write only

ViewPort ViewPort

Valid for: G; Default: ""

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

usedByGraphs :: Attribute -> BoolSource

Determine if this Attribute is valid for use with Graphs.

usedByClusters :: Attribute -> BoolSource

Determine if this Attribute is valid for use with Clusters.

usedBySubGraphs :: Attribute -> BoolSource

Determine if this Attribute is valid for use with SubGraphs.

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.

newtype URL Source

Constructors

UStr 

Fields

urlString :: String
 

Instances

data Rect Source

Constructors

Rect Point Point 

data Color Source

Constructors

RGB 

Fields

red :: Word8
 
green :: Word8
 
blue :: Word8
 
RGBA 

Fields

red :: Word8
 
green :: Word8
 
blue :: Word8
 
alpha :: Word8
 
HSV 

Fields

hue :: Int
 
saturation :: Int
 
value :: Int
 
ColorName String 

data DPoint Source

Either a Double or a Point.

Constructors

DVal Double 
PVal Point 

data Overlap Source

Constructors

KeepOverlaps 
RemoveOverlaps 
ScaleOverlaps 
ScaleXYOverlaps 
PrismOverlap (Maybe Int)

Only when sfdp is available, Int is non-negative

CompressOverlap 
VpscOverlap 
IpsepOverlap

Only when mode=ipsep

data LayerList Source

The list represent (Separator, Name)

Constructors

LL String [(String, String)] 

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 Pos Source

Constructors

PointPos Point 
SplinePos [Spline] 

Instances

data EdgeType Source

Controls how (and if) edges are represented.

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 

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 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 StartType Source

It it assumed that at least one of these is Just{}.

Constructors

ST (Maybe STStyle) (Maybe Int) 

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

newtype QuotedString Source

Represents Strings that definitely have quotes around them.

Constructors

QS 

Fields

qStr :: String
 

bool :: a -> a -> Bool -> aSource

Fold over Bools.