| Copyright | (c) Matthew Sackman Ivan Lazar Miljenovic | 
|---|---|
| License | 3-Clause BSD-style | 
| Maintainer | Ivan.Miljenovic@gmail.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.GraphViz.Commands
Contents
Description
This module defines functions to call the various Graphviz commands.
Whilst various output formats are supported (see GraphvizOutput
   for a complete list), it is not yet possible to choose a desired
   renderer and formatter.  Being able to determine which renderers
   and formatters are applicable for a specific GraphvizOutput is
   not easy (there is no listing of available renderers or formatters
   on the Graphviz website), and for the most part the default ones do
   the job well.
Please note that for GraphvizOutput and GraphvizCanvas, you
   will see that they are instances of a GraphvizResult class; this is
   an internal class that should not be visible outside this module, but
   Haddock is being too helpful for its own good.
Synopsis
- data GraphvizCommand
- dirCommand :: GraphvizCommand
- undirCommand :: GraphvizCommand
- commandFor :: DotRepr dg n => dg n -> GraphvizCommand
- data GraphvizOutput
- data GraphvizCanvas
- runGraphviz :: PrintDotRepr dg n => dg n -> GraphvizOutput -> FilePath -> IO FilePath
- runGraphvizCommand :: PrintDotRepr dg n => GraphvizCommand -> dg n -> GraphvizOutput -> FilePath -> IO FilePath
- addExtension :: (GraphvizOutput -> FilePath -> a) -> GraphvizOutput -> FilePath -> a
- runGraphvizCanvas :: PrintDotRepr dg n => GraphvizCommand -> dg n -> GraphvizCanvas -> IO ()
- runGraphvizCanvas' :: PrintDotRepr dg n => dg n -> GraphvizCanvas -> IO ()
- graphvizWithHandle :: PrintDotRepr dg n => GraphvizCommand -> dg n -> GraphvizOutput -> (Handle -> IO a) -> IO a
- isGraphvizInstalled :: IO Bool
- quitWithoutGraphviz :: String -> IO ()
The different Graphviz tools available.
data GraphvizCommand Source #
The available Graphviz commands.  The following directions are
   based upon those in the Graphviz man page (available online at
   http://graphviz.org/pdf/dot.1.pdf, or if installed on your
   system man graphviz).  Note that any command can be used on
   both directed and undirected graphs.
When used with the Layout attribute, it overrides any actual
   command called on the dot graph.
Constructors
| Dot | For hierachical graphs (ideal for directed graphs). | 
| Neato | For symmetric layouts of graphs (ideal for undirected graphs). | 
| TwoPi | For radial layout of graphs. | 
| Circo | For circular layout of graphs. | 
| Fdp | Spring-model approach for undirected graphs. | 
| Sfdp | As with Fdp, but ideal for large graphs. | 
| Osage | Filter for drawing clustered graphs, requires Graphviz >= 2.28.0. | 
| Patchwork | Draw clustered graphs as treemaps, requires Graphviz >= 2.28.0. | 
Instances
dirCommand :: GraphvizCommand Source #
The default command for directed graphs.
undirCommand :: GraphvizCommand Source #
The default command for undirected graphs.
commandFor :: DotRepr dg n => dg n -> GraphvizCommand Source #
The appropriate (default) Graphviz command for the given graph.
The possible outputs that Graphviz supports.
The list of output types supported by Graphviz is dependent upon
   how it is built on your system.  To determine which actual formats
   are available on your system, run dot -T?.  Trying to use an
   output type that is not supported by your installation of Graphviz
   will result in an error.
The outputs defined here in GraphvizOutput and GraphvizCanvas
   are those from the default list of available outputs.  For more
   information, see:
     http://graphviz.org/doc/info/output.html
data GraphvizOutput Source #
The possible Graphviz output formats (that is, those that actually produce a file).
Constructors
| Bmp | Windows Bitmap Format. | 
| Canon | Pretty-printed Dot output with no layout performed. | 
| DotOutput | Reproduces the input along with layout information. | 
| XDot (Maybe Version) | As with  | 
| Eps | Encapsulated PostScript. | 
| Fig | FIG graphics language. | 
| Gd | Internal GD library format. | 
| Gd2 | Compressed version of  | 
| Gif | Graphics Interchange Format. | 
| Ico | Icon image file format. | 
| Imap | Server-side imagemap. | 
| Cmapx | Client-side imagemap. | 
| ImapNP | As for  | 
| CmapxNP | As for  | 
| Jpeg | The JPEG image format. | 
| Portable Document Format. | |
| Plain | Simple text format. | 
| PlainExt | As for  | 
| Png | Portable Network Graphics format. | 
| Ps | PostScript. | 
| Ps2 | PostScript for PDF. | 
| Svg | Scalable Vector Graphics format. | 
| SvgZ | Compressed SVG format. | 
| Tiff | Tagged Image File Format. | 
| Vml | Vector Markup Language;  | 
| VmlZ | Compressed VML format;  | 
| Vrml | Virtual Reality Modeling Language
   format; requires nodes to have a
   third dimension set via the  | 
| WBmp | Wireless BitMap format; monochrome format usually used for mobile computing devices. | 
| WebP | Google's WebP format; requires Graphviz >= 2.29.0. | 
Instances
| Eq GraphvizOutput Source # | |
| Defined in Data.GraphViz.Commands Methods (==) :: GraphvizOutput -> GraphvizOutput -> Bool # (/=) :: GraphvizOutput -> GraphvizOutput -> Bool # | |
| Ord GraphvizOutput Source # | |
| Defined in Data.GraphViz.Commands Methods compare :: GraphvizOutput -> GraphvizOutput -> Ordering # (<) :: GraphvizOutput -> GraphvizOutput -> Bool # (<=) :: GraphvizOutput -> GraphvizOutput -> Bool # (>) :: GraphvizOutput -> GraphvizOutput -> Bool # (>=) :: GraphvizOutput -> GraphvizOutput -> Bool # max :: GraphvizOutput -> GraphvizOutput -> GraphvizOutput # min :: GraphvizOutput -> GraphvizOutput -> GraphvizOutput # | |
| Read GraphvizOutput Source # | |
| Defined in Data.GraphViz.Commands Methods readsPrec :: Int -> ReadS GraphvizOutput # readList :: ReadS [GraphvizOutput] # | |
| Show GraphvizOutput Source # | |
| Defined in Data.GraphViz.Commands Methods showsPrec :: Int -> GraphvizOutput -> ShowS # show :: GraphvizOutput -> String # showList :: [GraphvizOutput] -> ShowS # | |
data GraphvizCanvas Source #
Unlike GraphvizOutput, these items do not produce an output
   file; instead, they directly draw a canvas (i.e. a window) with
   the resulting image.
Instances
Running Graphviz.
runGraphviz :: PrintDotRepr dg n => dg n -> GraphvizOutput -> FilePath -> IO FilePath Source #
Run the recommended Graphviz command on this graph, saving the result to the file provided (note: file extensions are not checked).
runGraphvizCommand :: PrintDotRepr dg n => GraphvizCommand -> dg n -> GraphvizOutput -> FilePath -> IO FilePath Source #
Run the chosen Graphviz command on this graph, saving the result to the file provided (note: file extensions are not checked).
addExtension :: (GraphvizOutput -> FilePath -> a) -> GraphvizOutput -> FilePath -> a Source #
Append the default extension for the provided GraphvizOutput to
   the provided FilePath for the output file.
runGraphvizCanvas :: PrintDotRepr dg n => GraphvizCommand -> dg n -> GraphvizCanvas -> IO () Source #
Run the chosen Graphviz command on this graph and render it using the given canvas type.
runGraphvizCanvas' :: PrintDotRepr dg n => dg n -> GraphvizCanvas -> IO () Source #
Run the recommended Graphviz command on this graph and render it using the given canvas type.
Arguments
| :: PrintDotRepr dg n | |
| => GraphvizCommand | Which command to run | 
| -> dg n | The  | 
| -> GraphvizOutput | The  | 
| -> (Handle -> IO a) | Extract the output | 
| -> IO a | The error or the result. | 
Run the chosen Graphviz command on this graph, but send the result to the given handle rather than to a file.
Note that the Handle -> IO aHandle; e.g. use strict ByteStrings rather
   than lazy ones.
If the command was unsuccessful, then a GraphvizException is
   thrown.
Testing if Graphviz is installed
isGraphvizInstalled :: IO Bool Source #
Is the Graphviz suite of tools installed?  This is determined by
   whether dot is available in the PATH.
quitWithoutGraphviz :: String -> IO () Source #
If Graphviz does not seem to be available, print the provided error message and then exit fatally.