graphviz-2008.9.20: GraphViz wrapper for HaskellSource codeContentsIndex
Data.GraphViz
Synopsis
graphToDot :: (Ord b, Graph gr) => gr a b -> [Attribute] -> (LNode a -> [Attribute]) -> (LEdge b -> [Attribute]) -> DotGraph
clusterGraphToDot :: (Ord c, Ord b, Graph gr) => gr a b -> [Attribute] -> (LNode a -> NodeCluster c a) -> (c -> [Attribute]) -> (LNode a -> [Attribute]) -> (LEdge b -> [Attribute]) -> DotGraph
graphToGraph :: forall gr a b. (Ord b, Graph gr) => gr a b -> [Attribute] -> (LNode a -> [Attribute]) -> (LEdge b -> [Attribute]) -> IO (gr (AttributeNode a) (AttributeEdge b))
readDotGraph :: Parser Char DotGraph
commandFor :: DotGraph -> String
data DotGraph = DotGraph {
graphAttributes :: [Attribute]
graphNodes :: [DotNode]
graphEdges :: [DotEdge]
directedGraph :: Bool
}
data DotNode
= DotNode {
nodeID :: Int
nodeAttributes :: [Attribute]
}
| DotCluster {
clusterID :: String
clusterAttributes :: [Attribute]
clusterElems :: [DotNode]
}
data DotEdge = DotEdge {
edgeHeadNodeID :: Int
edgeTailNodeID :: Int
edgeAttributes :: [Attribute]
directedEdge :: Bool
}
data NodeCluster c a
= N (LNode a)
| C c (NodeCluster c a)
type AttributeNode a = ([Attribute], a)
type AttributeEdge b = ([Attribute], b)
module Data.GraphViz.Attributes
Documentation
graphToDot :: (Ord b, Graph gr) => gr a b -> [Attribute] -> (LNode a -> [Attribute]) -> (LEdge b -> [Attribute]) -> DotGraphSource
Convert a graph to dot format. You can then write this to a file and run the appropriate command on it (found using commandFor).
clusterGraphToDot :: (Ord c, Ord b, Graph gr) => gr a b -> [Attribute] -> (LNode a -> NodeCluster c a) -> (c -> [Attribute]) -> (LNode a -> [Attribute]) -> (LEdge b -> [Attribute]) -> DotGraphSource
Convert a graph to dot format, using the specified clustering function to group nodes into clusters. You can then write this to a file and run the appropriate command on it (found using commandFor). Clusters can be nested to arbitrary depth.
graphToGraph :: forall gr a b. (Ord b, Graph gr) => gr a b -> [Attribute] -> (LNode a -> [Attribute]) -> (LEdge b -> [Attribute]) -> IO (gr (AttributeNode a) (AttributeEdge b))Source
Run the graph via dot to get positional information and then combine that information back into the original graph. Note that this doesn't support graphs with clusters.
readDotGraph :: Parser Char DotGraphSource
commandFor :: DotGraph -> StringSource
The appropriate GraphViz command for the given graph.
data DotGraph Source
Constructors
DotGraph
graphAttributes :: [Attribute]
graphNodes :: [DotNode]
graphEdges :: [DotEdge]
directedGraph :: Bool
show/hide Instances
data DotNode Source
Constructors
DotNode
nodeID :: Int
nodeAttributes :: [Attribute]
DotCluster
clusterID :: String
clusterAttributes :: [Attribute]
clusterElems :: [DotNode]
show/hide Instances
data DotEdge Source
Constructors
DotEdge
edgeHeadNodeID :: Int
edgeTailNodeID :: Int
edgeAttributes :: [Attribute]
directedEdge :: Bool
show/hide Instances
data NodeCluster c a Source
Define into which cluster a particular node belongs. Nodes can be nested to arbitrary depth.
Constructors
N (LNode a)
C c (NodeCluster c a)
show/hide Instances
(Show c, Show a) => Show (NodeCluster c a)
type AttributeNode a = ([Attribute], a)Source
type AttributeEdge b = ([Attribute], b)Source
module Data.GraphViz.Attributes
Produced by Haddock version 2.3.0