haphviz-0.1.1.5: Graphviz code generation with Haskell

Safe HaskellSafe
LanguageHaskell2010

Text.Dot.Gen

Contents

Description

Generating graph contents

Synopsis

Documentation

graph Source

Arguments

:: GraphType 
-> GraphName

Internal graph name

-> DotGen a

Content

-> DotGraph 

Generate a haphviz graph with a given name and content

>>> graph directed "mygraph" $ do
        a <- node "a"
        b <- node "b"
        a --> b
> graph mygraph {
>   0 [label="a"];
>   1 [label="b"];
>   0 -- 1;
> }

graph_ Source

Arguments

:: GraphType 
-> DotGen a

Content

-> DotGraph 

Like graph but without an internal graph name

graph_ gt func = graph gt "haphviz" func

genDot :: DotGen a -> Dot Source

Generate Internal dot content AST

genSubDot :: Int -> DotGen a -> Dot Source

Utility function to generate a graph with nameless nodes starting from a given starting number.

Graph types

directed :: GraphType Source

Directed graph

>>> directed
> digraph

undirected :: GraphType Source

Undirected graph

>>> undirected
> graph

Nodes

genNode :: NodeId -> [Attribute] -> DotGen () Source

Most general node declaration

This allows you to specify a node identifier for the node.

In general it is more efficient to use nameless nodes and have the identifiers generated for you.

It also allows you to specify attributes. In general it is better to use namelessNode.

>>> n <- newNode
>>> genNode n [color =: green]
> 0 [color="green"];

namedNode Source

Arguments

:: Text

Name

-> [Attribute] 
-> DotGen NodeId 

Node with given (internal) name and attributes

Aside from human-readable output, there is no reason to use named nodes. Use node instead.

>>> void $ namedNode "woohoo" [color =: red]
> wohoo [color="red"];

namelessNode :: [Attribute] -> DotGen NodeId Source

Nameless node with attributes

This generates a nameless node for you but still allows you to specify its individual attributes. In general it is better to use nodeDec and then node.

>>> void $ namelessNode [color =: blue]
> 0 [color="blue"];

node Source

Arguments

:: Text

Label

-> DotGen NodeId 

Node with a label but no other attributes

A node with a given label and no other attributes. Usually used in conjunction with nodeDec.

>>> void $ node "server"
> 0 [label="server"];

node_ Source

Arguments

:: NodeId

given Node ID

-> Text

Label

-> DotGen () 

Node with given node Id and label

node_ ni l = genNode ni [label =: l]

newNode :: DotGen NodeId Source

Generate a new internally nameless node ID

It is not generally a good idea to use this directly but it can be used to define node identifiers before a subgraph to reference them both in- and outside of it.

Edges

genEdge :: NodeId -> NodeId -> [Attribute] -> DotGen () Source

Most general edge declaration

This allows you to specify attributes for a single edge.

Usually it is better to use edgeDec and then -->.

>>> genEdge a b [label =: "MyEdge"]
> a -> b [label="MyEdge"];

(-->) :: NodeId -> NodeId -> DotGen () Source

Infix edge constructor. (No attributes)

This takes care of using the right edge declaration for the given graph.

For undirected graphs, the output would be -- ...

>>> a --> b
> a -- b;

... and for directed graphs it would be ->.

>>> a --> b
> a -> b;

Attributes

(=:) :: AttributeName -> AttributeValue -> Attribute Source

Infix operator for an attribute pair

>>> [label =: "MyNode"]
> [label="MyNode"]

Declarations

genDec :: DecType -> [Attribute] -> DotGen () Source

General declaration of common attributes

graphDec :: [Attribute] -> DotGen () Source

Graph declaration

>>> graphDec [compound =: true]
> graph [compound=true];

nodeDec :: [Attribute] -> DotGen () Source

Node declaration

>>> nodeDec [shape =: none]
> node [shape=none];

edgeDec :: [Attribute] -> DotGen () Source

Edge declaration

>>> edgeDec [color =: "red:blue"]
> edge [color="red:blue"];

Subgraphs

cluster :: Text -> DotGen () -> DotGen GraphName Source

Cluster with a given name

The cluster_ prefix is taken care of.

cluster_ :: Text -> DotGen () -> DotGen () Source

Like cluster, discarding the graph name.

subgraph :: Text -> DotGen () -> DotGen GraphName Source

Subgraph declaration

This is rarely useful. Just use cluster.

Miscelaneous

Rankdir

rankdir :: RankdirType -> DotGen () Source

The rankdir declaration

This changes the default layout of nodes

>>> rankdir leftRight
> rankdir = LR;

leftRight :: RankdirType Source

>>> leftRight
> LR

rightLeft :: RankdirType Source

>>> rightLeft
> RL

topBottom :: RankdirType Source

>>> topBottom
> TB

bottomTop :: RankdirType Source

>>> bottomTop
> BT

Labels

labelDec :: Text -> DotGen () Source

Label declaration for graphs or subgraphs

Ports

(.:) Source

Arguments

:: NodeId 
-> Text

Port

-> NodeId 

Use a certain port on a given node's label as an endpoint for an edge

Internals

type DotGen = StateT State (WriterT Dot Identity) Source

Generation monad

type State = Int Source

The next id for a nameless node

data Dot Source

Haphviz internal graph content AST

Instances

Eq Dot Source 
Show Dot Source 
Monoid Dot Source

Dot is a monoid, duh, that's the point.

data DotGraph Source

A Haphviz Graph

data NodeId Source

A node identifier.

This is either a user supplied name or a generated numerical identifier.

type Attribute = (AttributeName, AttributeValue) Source

Attribute: a tuple of name and value.

type AttributeName = Text Source

Attribute name: just text

type AttributeValue = Text Source

Attribute value: just text

data DecType Source

Declaration type

Used to declare common attributes for nodes or edges.

data RankdirType Source

Rankdir Type

Used to specify the default node layout direction