Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Generating graph contents
- graph :: GraphType -> GraphName -> DotGen a -> DotGraph
- graph_ :: GraphType -> DotGen a -> DotGraph
- genDot :: DotGen a -> Dot
- genSubDot :: Int -> DotGen a -> Dot
- genSubDot' :: Int -> DotGen a -> ((a, State), Dot)
- directed :: GraphType
- undirected :: GraphType
- genNode :: NodeId -> [Attribute] -> DotGen ()
- namedNode :: Text -> [Attribute] -> DotGen NodeId
- namelessNode :: [Attribute] -> DotGen NodeId
- node :: Text -> DotGen NodeId
- node_ :: NodeId -> Text -> DotGen ()
- newNode :: DotGen NodeId
- genEdge :: NodeId -> NodeId -> [Attribute] -> DotGen ()
- (-->) :: NodeId -> NodeId -> DotGen ()
- (=:) :: AttributeName -> AttributeValue -> Attribute
- genDec :: DecType -> [Attribute] -> DotGen ()
- graphDec :: [Attribute] -> DotGen ()
- nodeDec :: [Attribute] -> DotGen ()
- edgeDec :: [Attribute] -> DotGen ()
- cluster :: Text -> DotGen a -> DotGen (GraphName, a)
- cluster_ :: Text -> DotGen a -> DotGen a
- subgraph :: Text -> DotGen a -> DotGen (GraphName, a)
- rankdir :: RankdirType -> DotGen ()
- leftRight :: RankdirType
- rightLeft :: RankdirType
- topBottom :: RankdirType
- bottomTop :: RankdirType
- labelDec :: Text -> DotGen ()
- (.:) :: NodeId -> Text -> NodeId
- ranksame :: DotGen a -> DotGen a
- type DotGen = StateT State (WriterT Dot Identity)
- type State = Int
- module Text.Dot.Attributes
- data Dot
- data DotGraph
- data NodeId
- type Attribute = (AttributeName, AttributeValue)
- type AttributeName = Text
- type AttributeValue = Text
- data DecType
- data RankdirType
Documentation
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; > }
Like graph
but without an internal graph name
graph_ gt func = graph gt "haphviz" func
genSubDot :: Int -> DotGen a -> Dot Source #
Utility function to generate a graph with nameless nodes starting from a given starting number.
Graph types
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"];
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"];
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 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
(-->) :: 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
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 a -> DotGen (GraphName, a) Source #
Cluster with a given name
The cluster_
prefix is taken care of.
subgraph :: Text -> DotGen a -> DotGen (GraphName, a) 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
Ports
Use a certain port on a given node's label as an endpoint for an edge
Ranks
ranksame :: DotGen a -> DotGen a Source #
{rank=same ... } declaration
>>>
ranksame $ node [shape =: none]
> node [shape=none];
Internals
module Text.Dot.Attributes
Haphviz internal graph content AST
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
Declaration type
Used to declare common attributes for nodes or edges.
data RankdirType Source #
Rankdir Type
Used to specify the default node layout direction