{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
{- |
   Module      : Data.GraphViz.Commands.Available
   Description : Available command-line programs
   Copyright   : (c) Ivan Lazar Miljenovic
   License     : 3-Clause BSD-style
   Maintainer  : Ivan.Miljenovic@gmail.com

   These are the known programs that read in Dot graphs.

 -}
module Data.GraphViz.Commands.Available where

import Data.GraphViz.Parsing
import Data.GraphViz.Printing

-- -----------------------------------------------------------------------------

-- | 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.
data GraphvizCommand = 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.
                     deriving (GraphvizCommand -> GraphvizCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GraphvizCommand -> GraphvizCommand -> Bool
$c/= :: GraphvizCommand -> GraphvizCommand -> Bool
== :: GraphvizCommand -> GraphvizCommand -> Bool
$c== :: GraphvizCommand -> GraphvizCommand -> Bool
Eq, Eq GraphvizCommand
GraphvizCommand -> GraphvizCommand -> Bool
GraphvizCommand -> GraphvizCommand -> Ordering
GraphvizCommand -> GraphvizCommand -> GraphvizCommand
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GraphvizCommand -> GraphvizCommand -> GraphvizCommand
$cmin :: GraphvizCommand -> GraphvizCommand -> GraphvizCommand
max :: GraphvizCommand -> GraphvizCommand -> GraphvizCommand
$cmax :: GraphvizCommand -> GraphvizCommand -> GraphvizCommand
>= :: GraphvizCommand -> GraphvizCommand -> Bool
$c>= :: GraphvizCommand -> GraphvizCommand -> Bool
> :: GraphvizCommand -> GraphvizCommand -> Bool
$c> :: GraphvizCommand -> GraphvizCommand -> Bool
<= :: GraphvizCommand -> GraphvizCommand -> Bool
$c<= :: GraphvizCommand -> GraphvizCommand -> Bool
< :: GraphvizCommand -> GraphvizCommand -> Bool
$c< :: GraphvizCommand -> GraphvizCommand -> Bool
compare :: GraphvizCommand -> GraphvizCommand -> Ordering
$ccompare :: GraphvizCommand -> GraphvizCommand -> Ordering
Ord, GraphvizCommand
forall a. a -> a -> Bounded a
maxBound :: GraphvizCommand
$cmaxBound :: GraphvizCommand
minBound :: GraphvizCommand
$cminBound :: GraphvizCommand
Bounded, Int -> GraphvizCommand
GraphvizCommand -> Int
GraphvizCommand -> [GraphvizCommand]
GraphvizCommand -> GraphvizCommand
GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
GraphvizCommand
-> GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: GraphvizCommand
-> GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
$cenumFromThenTo :: GraphvizCommand
-> GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
enumFromTo :: GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
$cenumFromTo :: GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
enumFromThen :: GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
$cenumFromThen :: GraphvizCommand -> GraphvizCommand -> [GraphvizCommand]
enumFrom :: GraphvizCommand -> [GraphvizCommand]
$cenumFrom :: GraphvizCommand -> [GraphvizCommand]
fromEnum :: GraphvizCommand -> Int
$cfromEnum :: GraphvizCommand -> Int
toEnum :: Int -> GraphvizCommand
$ctoEnum :: Int -> GraphvizCommand
pred :: GraphvizCommand -> GraphvizCommand
$cpred :: GraphvizCommand -> GraphvizCommand
succ :: GraphvizCommand -> GraphvizCommand
$csucc :: GraphvizCommand -> GraphvizCommand
Enum, Int -> GraphvizCommand -> ShowS
[GraphvizCommand] -> ShowS
GraphvizCommand -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [GraphvizCommand] -> ShowS
$cshowList :: [GraphvizCommand] -> ShowS
show :: GraphvizCommand -> [Char]
$cshow :: GraphvizCommand -> [Char]
showsPrec :: Int -> GraphvizCommand -> ShowS
$cshowsPrec :: Int -> GraphvizCommand -> ShowS
Show, ReadPrec [GraphvizCommand]
ReadPrec GraphvizCommand
Int -> ReadS GraphvizCommand
ReadS [GraphvizCommand]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GraphvizCommand]
$creadListPrec :: ReadPrec [GraphvizCommand]
readPrec :: ReadPrec GraphvizCommand
$creadPrec :: ReadPrec GraphvizCommand
readList :: ReadS [GraphvizCommand]
$creadList :: ReadS [GraphvizCommand]
readsPrec :: Int -> ReadS GraphvizCommand
$creadsPrec :: Int -> ReadS GraphvizCommand
Read)

instance PrintDot GraphvizCommand where
  unqtDot :: GraphvizCommand -> DotCode
unqtDot GraphvizCommand
Dot       = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"dot"
  unqtDot GraphvizCommand
Neato     = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"neato"
  unqtDot GraphvizCommand
TwoPi     = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"twopi"
  unqtDot GraphvizCommand
Circo     = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"circo"
  unqtDot GraphvizCommand
Fdp       = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"fdp"
  unqtDot GraphvizCommand
Sfdp      = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"sfdp"
  unqtDot GraphvizCommand
Osage     = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"osage"
  unqtDot GraphvizCommand
Patchwork = forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"patchwork"

instance ParseDot GraphvizCommand where
  parseUnqt :: Parse GraphvizCommand
parseUnqt = forall a. [([Char], a)] -> Parse a
stringValue [ ([Char]
"dot", GraphvizCommand
Dot)
                          , ([Char]
"neato", GraphvizCommand
Neato)
                          , ([Char]
"twopi", GraphvizCommand
TwoPi)
                          , ([Char]
"circo", GraphvizCommand
Circo)
                          , ([Char]
"fdp", GraphvizCommand
Fdp)
                          , ([Char]
"sfdp", GraphvizCommand
Sfdp)
                          , ([Char]
"osage", GraphvizCommand
Osage)
                          , ([Char]
"patchwork", GraphvizCommand
Patchwork)
                          ]