{-# LANGUAGE CPP, OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
module Data.GraphViz.Attributes.Values where
import qualified Data.GraphViz.Attributes.HTML as Html
import Data.GraphViz.Attributes.Internal
import Data.GraphViz.Internal.State (getLayerListSep,
getLayerSep,
setLayerListSep,
setLayerSep)
import Data.GraphViz.Internal.Util (bool, stringToInt)
import Data.GraphViz.Parsing
import Data.GraphViz.Printing
import Data.List (intercalate)
import Data.Maybe (isJust)
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import Data.Word (Word16)
import System.FilePath (searchPathSeparator, splitSearchPath)
#if !MIN_VERSION_base (4,13,0)
import Data.Monoid ((<>))
#endif
type EscString = Text
data Rect = Rect Point Point
deriving (Rect -> Rect -> Bool
(Rect -> Rect -> Bool) -> (Rect -> Rect -> Bool) -> Eq Rect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rect -> Rect -> Bool
== :: Rect -> Rect -> Bool
$c/= :: Rect -> Rect -> Bool
/= :: Rect -> Rect -> Bool
Eq, Eq Rect
Eq Rect =>
(Rect -> Rect -> Ordering)
-> (Rect -> Rect -> Bool)
-> (Rect -> Rect -> Bool)
-> (Rect -> Rect -> Bool)
-> (Rect -> Rect -> Bool)
-> (Rect -> Rect -> Rect)
-> (Rect -> Rect -> Rect)
-> Ord Rect
Rect -> Rect -> Bool
Rect -> Rect -> Ordering
Rect -> Rect -> Rect
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
$ccompare :: Rect -> Rect -> Ordering
compare :: Rect -> Rect -> Ordering
$c< :: Rect -> Rect -> Bool
< :: Rect -> Rect -> Bool
$c<= :: Rect -> Rect -> Bool
<= :: Rect -> Rect -> Bool
$c> :: Rect -> Rect -> Bool
> :: Rect -> Rect -> Bool
$c>= :: Rect -> Rect -> Bool
>= :: Rect -> Rect -> Bool
$cmax :: Rect -> Rect -> Rect
max :: Rect -> Rect -> Rect
$cmin :: Rect -> Rect -> Rect
min :: Rect -> Rect -> Rect
Ord, Int -> Rect -> ShowS
[Rect] -> ShowS
Rect -> String
(Int -> Rect -> ShowS)
-> (Rect -> String) -> ([Rect] -> ShowS) -> Show Rect
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rect -> ShowS
showsPrec :: Int -> Rect -> ShowS
$cshow :: Rect -> String
show :: Rect -> String
$cshowList :: [Rect] -> ShowS
showList :: [Rect] -> ShowS
Show, ReadPrec [Rect]
ReadPrec Rect
Int -> ReadS Rect
ReadS [Rect]
(Int -> ReadS Rect)
-> ReadS [Rect] -> ReadPrec Rect -> ReadPrec [Rect] -> Read Rect
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Rect
readsPrec :: Int -> ReadS Rect
$creadList :: ReadS [Rect]
readList :: ReadS [Rect]
$creadPrec :: ReadPrec Rect
readPrec :: ReadPrec Rect
$creadListPrec :: ReadPrec [Rect]
readListPrec :: ReadPrec [Rect]
Read)
instance PrintDot Rect where
unqtDot :: Rect -> DotCode
unqtDot (Rect Point
p1 Point
p2) = Point -> DotCode
printPoint2DUnqt Point
p1 DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode
forall (m :: * -> *). Applicative m => m Doc
comma DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Point -> DotCode
printPoint2DUnqt Point
p2
toDot :: Rect -> DotCode
toDot = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> (Rect -> DotCode) -> Rect -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rect -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
unqtListToDot :: [Rect] -> DotCode
unqtListToDot = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hsep (DotCodeM [Doc] -> DotCode)
-> ([Rect] -> DotCodeM [Doc]) -> [Rect] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rect -> DotCode) -> [Rect] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Rect -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
instance ParseDot Rect where
parseUnqt :: Parse Rect
parseUnqt = (Point -> Point -> Rect) -> (Point, Point) -> Rect
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Point -> Point -> Rect
Rect ((Point, Point) -> Rect)
-> Parser GraphvizState (Point, Point) -> Parse Rect
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parse Point -> Parse Point -> Parser GraphvizState (Point, Point)
forall a b. Parse a -> Parse b -> Parse (a, b)
commaSep' Parse Point
parsePoint2D Parse Point
parsePoint2D
parse :: Parse Rect
parse = Parse Rect -> Parse Rect
forall a. Parse a -> Parse a
quotedParse Parse Rect
forall a. ParseDot a => Parse a
parseUnqt
parseUnqtList :: Parse [Rect]
parseUnqtList = Parse Rect -> Parser GraphvizState () -> Parse [Rect]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse Rect
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
whitespace1
data ClusterMode = Local
| Global
| NoCluster
deriving (ClusterMode -> ClusterMode -> Bool
(ClusterMode -> ClusterMode -> Bool)
-> (ClusterMode -> ClusterMode -> Bool) -> Eq ClusterMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClusterMode -> ClusterMode -> Bool
== :: ClusterMode -> ClusterMode -> Bool
$c/= :: ClusterMode -> ClusterMode -> Bool
/= :: ClusterMode -> ClusterMode -> Bool
Eq, Eq ClusterMode
Eq ClusterMode =>
(ClusterMode -> ClusterMode -> Ordering)
-> (ClusterMode -> ClusterMode -> Bool)
-> (ClusterMode -> ClusterMode -> Bool)
-> (ClusterMode -> ClusterMode -> Bool)
-> (ClusterMode -> ClusterMode -> Bool)
-> (ClusterMode -> ClusterMode -> ClusterMode)
-> (ClusterMode -> ClusterMode -> ClusterMode)
-> Ord ClusterMode
ClusterMode -> ClusterMode -> Bool
ClusterMode -> ClusterMode -> Ordering
ClusterMode -> ClusterMode -> ClusterMode
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
$ccompare :: ClusterMode -> ClusterMode -> Ordering
compare :: ClusterMode -> ClusterMode -> Ordering
$c< :: ClusterMode -> ClusterMode -> Bool
< :: ClusterMode -> ClusterMode -> Bool
$c<= :: ClusterMode -> ClusterMode -> Bool
<= :: ClusterMode -> ClusterMode -> Bool
$c> :: ClusterMode -> ClusterMode -> Bool
> :: ClusterMode -> ClusterMode -> Bool
$c>= :: ClusterMode -> ClusterMode -> Bool
>= :: ClusterMode -> ClusterMode -> Bool
$cmax :: ClusterMode -> ClusterMode -> ClusterMode
max :: ClusterMode -> ClusterMode -> ClusterMode
$cmin :: ClusterMode -> ClusterMode -> ClusterMode
min :: ClusterMode -> ClusterMode -> ClusterMode
Ord, ClusterMode
ClusterMode -> ClusterMode -> Bounded ClusterMode
forall a. a -> a -> Bounded a
$cminBound :: ClusterMode
minBound :: ClusterMode
$cmaxBound :: ClusterMode
maxBound :: ClusterMode
Bounded, Int -> ClusterMode
ClusterMode -> Int
ClusterMode -> [ClusterMode]
ClusterMode -> ClusterMode
ClusterMode -> ClusterMode -> [ClusterMode]
ClusterMode -> ClusterMode -> ClusterMode -> [ClusterMode]
(ClusterMode -> ClusterMode)
-> (ClusterMode -> ClusterMode)
-> (Int -> ClusterMode)
-> (ClusterMode -> Int)
-> (ClusterMode -> [ClusterMode])
-> (ClusterMode -> ClusterMode -> [ClusterMode])
-> (ClusterMode -> ClusterMode -> [ClusterMode])
-> (ClusterMode -> ClusterMode -> ClusterMode -> [ClusterMode])
-> Enum ClusterMode
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ClusterMode -> ClusterMode
succ :: ClusterMode -> ClusterMode
$cpred :: ClusterMode -> ClusterMode
pred :: ClusterMode -> ClusterMode
$ctoEnum :: Int -> ClusterMode
toEnum :: Int -> ClusterMode
$cfromEnum :: ClusterMode -> Int
fromEnum :: ClusterMode -> Int
$cenumFrom :: ClusterMode -> [ClusterMode]
enumFrom :: ClusterMode -> [ClusterMode]
$cenumFromThen :: ClusterMode -> ClusterMode -> [ClusterMode]
enumFromThen :: ClusterMode -> ClusterMode -> [ClusterMode]
$cenumFromTo :: ClusterMode -> ClusterMode -> [ClusterMode]
enumFromTo :: ClusterMode -> ClusterMode -> [ClusterMode]
$cenumFromThenTo :: ClusterMode -> ClusterMode -> ClusterMode -> [ClusterMode]
enumFromThenTo :: ClusterMode -> ClusterMode -> ClusterMode -> [ClusterMode]
Enum, Int -> ClusterMode -> ShowS
[ClusterMode] -> ShowS
ClusterMode -> String
(Int -> ClusterMode -> ShowS)
-> (ClusterMode -> String)
-> ([ClusterMode] -> ShowS)
-> Show ClusterMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClusterMode -> ShowS
showsPrec :: Int -> ClusterMode -> ShowS
$cshow :: ClusterMode -> String
show :: ClusterMode -> String
$cshowList :: [ClusterMode] -> ShowS
showList :: [ClusterMode] -> ShowS
Show, ReadPrec [ClusterMode]
ReadPrec ClusterMode
Int -> ReadS ClusterMode
ReadS [ClusterMode]
(Int -> ReadS ClusterMode)
-> ReadS [ClusterMode]
-> ReadPrec ClusterMode
-> ReadPrec [ClusterMode]
-> Read ClusterMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ClusterMode
readsPrec :: Int -> ReadS ClusterMode
$creadList :: ReadS [ClusterMode]
readList :: ReadS [ClusterMode]
$creadPrec :: ReadPrec ClusterMode
readPrec :: ReadPrec ClusterMode
$creadListPrec :: ReadPrec [ClusterMode]
readListPrec :: ReadPrec [ClusterMode]
Read)
instance PrintDot ClusterMode where
unqtDot :: ClusterMode -> DotCode
unqtDot ClusterMode
Local = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"local"
unqtDot ClusterMode
Global = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"global"
unqtDot ClusterMode
NoCluster = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"none"
instance ParseDot ClusterMode where
parseUnqt :: Parse ClusterMode
parseUnqt = [Parse ClusterMode] -> Parse ClusterMode
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ ClusterMode -> String -> Parse ClusterMode
forall a. a -> String -> Parse a
stringRep ClusterMode
Local String
"local"
, ClusterMode -> String -> Parse ClusterMode
forall a. a -> String -> Parse a
stringRep ClusterMode
Global String
"global"
, ClusterMode -> String -> Parse ClusterMode
forall a. a -> String -> Parse a
stringRep ClusterMode
NoCluster String
"none"
]
data DirType = Forward
| Back
| Both
| NoDir
deriving (DirType -> DirType -> Bool
(DirType -> DirType -> Bool)
-> (DirType -> DirType -> Bool) -> Eq DirType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirType -> DirType -> Bool
== :: DirType -> DirType -> Bool
$c/= :: DirType -> DirType -> Bool
/= :: DirType -> DirType -> Bool
Eq, Eq DirType
Eq DirType =>
(DirType -> DirType -> Ordering)
-> (DirType -> DirType -> Bool)
-> (DirType -> DirType -> Bool)
-> (DirType -> DirType -> Bool)
-> (DirType -> DirType -> Bool)
-> (DirType -> DirType -> DirType)
-> (DirType -> DirType -> DirType)
-> Ord DirType
DirType -> DirType -> Bool
DirType -> DirType -> Ordering
DirType -> DirType -> DirType
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
$ccompare :: DirType -> DirType -> Ordering
compare :: DirType -> DirType -> Ordering
$c< :: DirType -> DirType -> Bool
< :: DirType -> DirType -> Bool
$c<= :: DirType -> DirType -> Bool
<= :: DirType -> DirType -> Bool
$c> :: DirType -> DirType -> Bool
> :: DirType -> DirType -> Bool
$c>= :: DirType -> DirType -> Bool
>= :: DirType -> DirType -> Bool
$cmax :: DirType -> DirType -> DirType
max :: DirType -> DirType -> DirType
$cmin :: DirType -> DirType -> DirType
min :: DirType -> DirType -> DirType
Ord, DirType
DirType -> DirType -> Bounded DirType
forall a. a -> a -> Bounded a
$cminBound :: DirType
minBound :: DirType
$cmaxBound :: DirType
maxBound :: DirType
Bounded, Int -> DirType
DirType -> Int
DirType -> [DirType]
DirType -> DirType
DirType -> DirType -> [DirType]
DirType -> DirType -> DirType -> [DirType]
(DirType -> DirType)
-> (DirType -> DirType)
-> (Int -> DirType)
-> (DirType -> Int)
-> (DirType -> [DirType])
-> (DirType -> DirType -> [DirType])
-> (DirType -> DirType -> [DirType])
-> (DirType -> DirType -> DirType -> [DirType])
-> Enum DirType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: DirType -> DirType
succ :: DirType -> DirType
$cpred :: DirType -> DirType
pred :: DirType -> DirType
$ctoEnum :: Int -> DirType
toEnum :: Int -> DirType
$cfromEnum :: DirType -> Int
fromEnum :: DirType -> Int
$cenumFrom :: DirType -> [DirType]
enumFrom :: DirType -> [DirType]
$cenumFromThen :: DirType -> DirType -> [DirType]
enumFromThen :: DirType -> DirType -> [DirType]
$cenumFromTo :: DirType -> DirType -> [DirType]
enumFromTo :: DirType -> DirType -> [DirType]
$cenumFromThenTo :: DirType -> DirType -> DirType -> [DirType]
enumFromThenTo :: DirType -> DirType -> DirType -> [DirType]
Enum, Int -> DirType -> ShowS
[DirType] -> ShowS
DirType -> String
(Int -> DirType -> ShowS)
-> (DirType -> String) -> ([DirType] -> ShowS) -> Show DirType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DirType -> ShowS
showsPrec :: Int -> DirType -> ShowS
$cshow :: DirType -> String
show :: DirType -> String
$cshowList :: [DirType] -> ShowS
showList :: [DirType] -> ShowS
Show, ReadPrec [DirType]
ReadPrec DirType
Int -> ReadS DirType
ReadS [DirType]
(Int -> ReadS DirType)
-> ReadS [DirType]
-> ReadPrec DirType
-> ReadPrec [DirType]
-> Read DirType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DirType
readsPrec :: Int -> ReadS DirType
$creadList :: ReadS [DirType]
readList :: ReadS [DirType]
$creadPrec :: ReadPrec DirType
readPrec :: ReadPrec DirType
$creadListPrec :: ReadPrec [DirType]
readListPrec :: ReadPrec [DirType]
Read)
instance PrintDot DirType where
unqtDot :: DirType -> DotCode
unqtDot DirType
Forward = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"forward"
unqtDot DirType
Back = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"back"
unqtDot DirType
Both = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"both"
unqtDot DirType
NoDir = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"none"
instance ParseDot DirType where
parseUnqt :: Parse DirType
parseUnqt = [Parse DirType] -> Parse DirType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ DirType -> String -> Parse DirType
forall a. a -> String -> Parse a
stringRep DirType
Forward String
"forward"
, DirType -> String -> Parse DirType
forall a. a -> String -> Parse a
stringRep DirType
Back String
"back"
, DirType -> String -> Parse DirType
forall a. a -> String -> Parse a
stringRep DirType
Both String
"both"
, DirType -> String -> Parse DirType
forall a. a -> String -> Parse a
stringRep DirType
NoDir String
"none"
]
data DEConstraints = EdgeConstraints
| NoConstraints
| HierConstraints
deriving (DEConstraints -> DEConstraints -> Bool
(DEConstraints -> DEConstraints -> Bool)
-> (DEConstraints -> DEConstraints -> Bool) -> Eq DEConstraints
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DEConstraints -> DEConstraints -> Bool
== :: DEConstraints -> DEConstraints -> Bool
$c/= :: DEConstraints -> DEConstraints -> Bool
/= :: DEConstraints -> DEConstraints -> Bool
Eq, Eq DEConstraints
Eq DEConstraints =>
(DEConstraints -> DEConstraints -> Ordering)
-> (DEConstraints -> DEConstraints -> Bool)
-> (DEConstraints -> DEConstraints -> Bool)
-> (DEConstraints -> DEConstraints -> Bool)
-> (DEConstraints -> DEConstraints -> Bool)
-> (DEConstraints -> DEConstraints -> DEConstraints)
-> (DEConstraints -> DEConstraints -> DEConstraints)
-> Ord DEConstraints
DEConstraints -> DEConstraints -> Bool
DEConstraints -> DEConstraints -> Ordering
DEConstraints -> DEConstraints -> DEConstraints
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
$ccompare :: DEConstraints -> DEConstraints -> Ordering
compare :: DEConstraints -> DEConstraints -> Ordering
$c< :: DEConstraints -> DEConstraints -> Bool
< :: DEConstraints -> DEConstraints -> Bool
$c<= :: DEConstraints -> DEConstraints -> Bool
<= :: DEConstraints -> DEConstraints -> Bool
$c> :: DEConstraints -> DEConstraints -> Bool
> :: DEConstraints -> DEConstraints -> Bool
$c>= :: DEConstraints -> DEConstraints -> Bool
>= :: DEConstraints -> DEConstraints -> Bool
$cmax :: DEConstraints -> DEConstraints -> DEConstraints
max :: DEConstraints -> DEConstraints -> DEConstraints
$cmin :: DEConstraints -> DEConstraints -> DEConstraints
min :: DEConstraints -> DEConstraints -> DEConstraints
Ord, DEConstraints
DEConstraints -> DEConstraints -> Bounded DEConstraints
forall a. a -> a -> Bounded a
$cminBound :: DEConstraints
minBound :: DEConstraints
$cmaxBound :: DEConstraints
maxBound :: DEConstraints
Bounded, Int -> DEConstraints
DEConstraints -> Int
DEConstraints -> [DEConstraints]
DEConstraints -> DEConstraints
DEConstraints -> DEConstraints -> [DEConstraints]
DEConstraints -> DEConstraints -> DEConstraints -> [DEConstraints]
(DEConstraints -> DEConstraints)
-> (DEConstraints -> DEConstraints)
-> (Int -> DEConstraints)
-> (DEConstraints -> Int)
-> (DEConstraints -> [DEConstraints])
-> (DEConstraints -> DEConstraints -> [DEConstraints])
-> (DEConstraints -> DEConstraints -> [DEConstraints])
-> (DEConstraints
-> DEConstraints -> DEConstraints -> [DEConstraints])
-> Enum DEConstraints
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: DEConstraints -> DEConstraints
succ :: DEConstraints -> DEConstraints
$cpred :: DEConstraints -> DEConstraints
pred :: DEConstraints -> DEConstraints
$ctoEnum :: Int -> DEConstraints
toEnum :: Int -> DEConstraints
$cfromEnum :: DEConstraints -> Int
fromEnum :: DEConstraints -> Int
$cenumFrom :: DEConstraints -> [DEConstraints]
enumFrom :: DEConstraints -> [DEConstraints]
$cenumFromThen :: DEConstraints -> DEConstraints -> [DEConstraints]
enumFromThen :: DEConstraints -> DEConstraints -> [DEConstraints]
$cenumFromTo :: DEConstraints -> DEConstraints -> [DEConstraints]
enumFromTo :: DEConstraints -> DEConstraints -> [DEConstraints]
$cenumFromThenTo :: DEConstraints -> DEConstraints -> DEConstraints -> [DEConstraints]
enumFromThenTo :: DEConstraints -> DEConstraints -> DEConstraints -> [DEConstraints]
Enum, Int -> DEConstraints -> ShowS
[DEConstraints] -> ShowS
DEConstraints -> String
(Int -> DEConstraints -> ShowS)
-> (DEConstraints -> String)
-> ([DEConstraints] -> ShowS)
-> Show DEConstraints
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DEConstraints -> ShowS
showsPrec :: Int -> DEConstraints -> ShowS
$cshow :: DEConstraints -> String
show :: DEConstraints -> String
$cshowList :: [DEConstraints] -> ShowS
showList :: [DEConstraints] -> ShowS
Show, ReadPrec [DEConstraints]
ReadPrec DEConstraints
Int -> ReadS DEConstraints
ReadS [DEConstraints]
(Int -> ReadS DEConstraints)
-> ReadS [DEConstraints]
-> ReadPrec DEConstraints
-> ReadPrec [DEConstraints]
-> Read DEConstraints
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DEConstraints
readsPrec :: Int -> ReadS DEConstraints
$creadList :: ReadS [DEConstraints]
readList :: ReadS [DEConstraints]
$creadPrec :: ReadPrec DEConstraints
readPrec :: ReadPrec DEConstraints
$creadListPrec :: ReadPrec [DEConstraints]
readListPrec :: ReadPrec [DEConstraints]
Read)
instance PrintDot DEConstraints where
unqtDot :: DEConstraints -> DotCode
unqtDot DEConstraints
EdgeConstraints = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot DEConstraints
NoConstraints = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
False
unqtDot DEConstraints
HierConstraints = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"hier"
instance ParseDot DEConstraints where
parseUnqt :: Parse DEConstraints
parseUnqt = (Bool -> DEConstraints)
-> Parser GraphvizState Bool -> Parse DEConstraints
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DEConstraints -> DEConstraints -> Bool -> DEConstraints
forall a. a -> a -> Bool -> a
bool DEConstraints
NoConstraints DEConstraints
EdgeConstraints) Parser GraphvizState Bool
forall a. ParseDot a => Parse a
parse
Parse DEConstraints -> Parse DEConstraints -> Parse DEConstraints
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
DEConstraints -> String -> Parse DEConstraints
forall a. a -> String -> Parse a
stringRep DEConstraints
HierConstraints String
"hier"
data DPoint = DVal Double
| PVal Point
deriving (DPoint -> DPoint -> Bool
(DPoint -> DPoint -> Bool)
-> (DPoint -> DPoint -> Bool) -> Eq DPoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DPoint -> DPoint -> Bool
== :: DPoint -> DPoint -> Bool
$c/= :: DPoint -> DPoint -> Bool
/= :: DPoint -> DPoint -> Bool
Eq, Eq DPoint
Eq DPoint =>
(DPoint -> DPoint -> Ordering)
-> (DPoint -> DPoint -> Bool)
-> (DPoint -> DPoint -> Bool)
-> (DPoint -> DPoint -> Bool)
-> (DPoint -> DPoint -> Bool)
-> (DPoint -> DPoint -> DPoint)
-> (DPoint -> DPoint -> DPoint)
-> Ord DPoint
DPoint -> DPoint -> Bool
DPoint -> DPoint -> Ordering
DPoint -> DPoint -> DPoint
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
$ccompare :: DPoint -> DPoint -> Ordering
compare :: DPoint -> DPoint -> Ordering
$c< :: DPoint -> DPoint -> Bool
< :: DPoint -> DPoint -> Bool
$c<= :: DPoint -> DPoint -> Bool
<= :: DPoint -> DPoint -> Bool
$c> :: DPoint -> DPoint -> Bool
> :: DPoint -> DPoint -> Bool
$c>= :: DPoint -> DPoint -> Bool
>= :: DPoint -> DPoint -> Bool
$cmax :: DPoint -> DPoint -> DPoint
max :: DPoint -> DPoint -> DPoint
$cmin :: DPoint -> DPoint -> DPoint
min :: DPoint -> DPoint -> DPoint
Ord, Int -> DPoint -> ShowS
[DPoint] -> ShowS
DPoint -> String
(Int -> DPoint -> ShowS)
-> (DPoint -> String) -> ([DPoint] -> ShowS) -> Show DPoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DPoint -> ShowS
showsPrec :: Int -> DPoint -> ShowS
$cshow :: DPoint -> String
show :: DPoint -> String
$cshowList :: [DPoint] -> ShowS
showList :: [DPoint] -> ShowS
Show, ReadPrec [DPoint]
ReadPrec DPoint
Int -> ReadS DPoint
ReadS [DPoint]
(Int -> ReadS DPoint)
-> ReadS [DPoint]
-> ReadPrec DPoint
-> ReadPrec [DPoint]
-> Read DPoint
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DPoint
readsPrec :: Int -> ReadS DPoint
$creadList :: ReadS [DPoint]
readList :: ReadS [DPoint]
$creadPrec :: ReadPrec DPoint
readPrec :: ReadPrec DPoint
$creadListPrec :: ReadPrec [DPoint]
readListPrec :: ReadPrec [DPoint]
Read)
instance PrintDot DPoint where
unqtDot :: DPoint -> DotCode
unqtDot (DVal Double
d) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
d
unqtDot (PVal Point
p) = Point -> DotCode
printPoint2DUnqt Point
p
toDot :: DPoint -> DotCode
toDot (DVal Double
d) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Double
d
toDot (PVal Point
p) = Point -> DotCode
printPoint2D Point
p
instance ParseDot DPoint where
parseUnqt :: Parse DPoint
parseUnqt = Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Char -> Parser GraphvizState Char
character Char
'+')
Parser GraphvizState (Maybe Char) -> Parse DPoint -> Parse DPoint
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [Parse DPoint] -> Parse DPoint
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Point -> DPoint
PVal (Point -> DPoint) -> Parse Point -> Parse DPoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parse Point
parsePoint2D
, Double -> DPoint
DVal (Double -> DPoint) -> Parser GraphvizState Double -> Parse DPoint
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt
]
parse :: Parse DPoint
parse = Parse DPoint -> Parse DPoint
forall a. Parse a -> Parse a
quotedParse Parse DPoint
forall a. ParseDot a => Parse a
parseUnqt
Parse DPoint -> Parse DPoint -> Parse DPoint
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Double -> DPoint) -> Parser GraphvizState Double -> Parse DPoint
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> DPoint
DVal (Bool -> Parser GraphvizState Double
parseSignedFloat Bool
False)
data SVGFontNames = SvgNames
| PostScriptNames
| FontConfigNames
deriving (SVGFontNames -> SVGFontNames -> Bool
(SVGFontNames -> SVGFontNames -> Bool)
-> (SVGFontNames -> SVGFontNames -> Bool) -> Eq SVGFontNames
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SVGFontNames -> SVGFontNames -> Bool
== :: SVGFontNames -> SVGFontNames -> Bool
$c/= :: SVGFontNames -> SVGFontNames -> Bool
/= :: SVGFontNames -> SVGFontNames -> Bool
Eq, Eq SVGFontNames
Eq SVGFontNames =>
(SVGFontNames -> SVGFontNames -> Ordering)
-> (SVGFontNames -> SVGFontNames -> Bool)
-> (SVGFontNames -> SVGFontNames -> Bool)
-> (SVGFontNames -> SVGFontNames -> Bool)
-> (SVGFontNames -> SVGFontNames -> Bool)
-> (SVGFontNames -> SVGFontNames -> SVGFontNames)
-> (SVGFontNames -> SVGFontNames -> SVGFontNames)
-> Ord SVGFontNames
SVGFontNames -> SVGFontNames -> Bool
SVGFontNames -> SVGFontNames -> Ordering
SVGFontNames -> SVGFontNames -> SVGFontNames
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
$ccompare :: SVGFontNames -> SVGFontNames -> Ordering
compare :: SVGFontNames -> SVGFontNames -> Ordering
$c< :: SVGFontNames -> SVGFontNames -> Bool
< :: SVGFontNames -> SVGFontNames -> Bool
$c<= :: SVGFontNames -> SVGFontNames -> Bool
<= :: SVGFontNames -> SVGFontNames -> Bool
$c> :: SVGFontNames -> SVGFontNames -> Bool
> :: SVGFontNames -> SVGFontNames -> Bool
$c>= :: SVGFontNames -> SVGFontNames -> Bool
>= :: SVGFontNames -> SVGFontNames -> Bool
$cmax :: SVGFontNames -> SVGFontNames -> SVGFontNames
max :: SVGFontNames -> SVGFontNames -> SVGFontNames
$cmin :: SVGFontNames -> SVGFontNames -> SVGFontNames
min :: SVGFontNames -> SVGFontNames -> SVGFontNames
Ord, SVGFontNames
SVGFontNames -> SVGFontNames -> Bounded SVGFontNames
forall a. a -> a -> Bounded a
$cminBound :: SVGFontNames
minBound :: SVGFontNames
$cmaxBound :: SVGFontNames
maxBound :: SVGFontNames
Bounded, Int -> SVGFontNames
SVGFontNames -> Int
SVGFontNames -> [SVGFontNames]
SVGFontNames -> SVGFontNames
SVGFontNames -> SVGFontNames -> [SVGFontNames]
SVGFontNames -> SVGFontNames -> SVGFontNames -> [SVGFontNames]
(SVGFontNames -> SVGFontNames)
-> (SVGFontNames -> SVGFontNames)
-> (Int -> SVGFontNames)
-> (SVGFontNames -> Int)
-> (SVGFontNames -> [SVGFontNames])
-> (SVGFontNames -> SVGFontNames -> [SVGFontNames])
-> (SVGFontNames -> SVGFontNames -> [SVGFontNames])
-> (SVGFontNames -> SVGFontNames -> SVGFontNames -> [SVGFontNames])
-> Enum SVGFontNames
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SVGFontNames -> SVGFontNames
succ :: SVGFontNames -> SVGFontNames
$cpred :: SVGFontNames -> SVGFontNames
pred :: SVGFontNames -> SVGFontNames
$ctoEnum :: Int -> SVGFontNames
toEnum :: Int -> SVGFontNames
$cfromEnum :: SVGFontNames -> Int
fromEnum :: SVGFontNames -> Int
$cenumFrom :: SVGFontNames -> [SVGFontNames]
enumFrom :: SVGFontNames -> [SVGFontNames]
$cenumFromThen :: SVGFontNames -> SVGFontNames -> [SVGFontNames]
enumFromThen :: SVGFontNames -> SVGFontNames -> [SVGFontNames]
$cenumFromTo :: SVGFontNames -> SVGFontNames -> [SVGFontNames]
enumFromTo :: SVGFontNames -> SVGFontNames -> [SVGFontNames]
$cenumFromThenTo :: SVGFontNames -> SVGFontNames -> SVGFontNames -> [SVGFontNames]
enumFromThenTo :: SVGFontNames -> SVGFontNames -> SVGFontNames -> [SVGFontNames]
Enum, Int -> SVGFontNames -> ShowS
[SVGFontNames] -> ShowS
SVGFontNames -> String
(Int -> SVGFontNames -> ShowS)
-> (SVGFontNames -> String)
-> ([SVGFontNames] -> ShowS)
-> Show SVGFontNames
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SVGFontNames -> ShowS
showsPrec :: Int -> SVGFontNames -> ShowS
$cshow :: SVGFontNames -> String
show :: SVGFontNames -> String
$cshowList :: [SVGFontNames] -> ShowS
showList :: [SVGFontNames] -> ShowS
Show, ReadPrec [SVGFontNames]
ReadPrec SVGFontNames
Int -> ReadS SVGFontNames
ReadS [SVGFontNames]
(Int -> ReadS SVGFontNames)
-> ReadS [SVGFontNames]
-> ReadPrec SVGFontNames
-> ReadPrec [SVGFontNames]
-> Read SVGFontNames
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SVGFontNames
readsPrec :: Int -> ReadS SVGFontNames
$creadList :: ReadS [SVGFontNames]
readList :: ReadS [SVGFontNames]
$creadPrec :: ReadPrec SVGFontNames
readPrec :: ReadPrec SVGFontNames
$creadListPrec :: ReadPrec [SVGFontNames]
readListPrec :: ReadPrec [SVGFontNames]
Read)
instance PrintDot SVGFontNames where
unqtDot :: SVGFontNames -> DotCode
unqtDot SVGFontNames
SvgNames = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"svg"
unqtDot SVGFontNames
PostScriptNames = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"ps"
unqtDot SVGFontNames
FontConfigNames = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"gd"
instance ParseDot SVGFontNames where
parseUnqt :: Parse SVGFontNames
parseUnqt = [Parse SVGFontNames] -> Parse SVGFontNames
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ SVGFontNames -> String -> Parse SVGFontNames
forall a. a -> String -> Parse a
stringRep SVGFontNames
SvgNames String
"svg"
, SVGFontNames -> String -> Parse SVGFontNames
forall a. a -> String -> Parse a
stringRep SVGFontNames
PostScriptNames String
"ps"
, SVGFontNames -> String -> Parse SVGFontNames
forall a. a -> String -> Parse a
stringRep SVGFontNames
FontConfigNames String
"gd"
]
parse :: Parse SVGFontNames
parse = SVGFontNames -> String -> Parse SVGFontNames
forall a. a -> String -> Parse a
stringRep SVGFontNames
SvgNames String
"\"\""
Parse SVGFontNames -> Parse SVGFontNames -> Parse SVGFontNames
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
Parse SVGFontNames -> Parse SVGFontNames
forall a. Parse a -> Parse a
optionalQuoted Parse SVGFontNames
forall a. ParseDot a => Parse a
parseUnqt
data GraphSize = GSize { GraphSize -> Double
width :: Double
, GraphSize -> Maybe Double
height :: Maybe Double
, GraphSize -> Bool
desiredSize :: Bool
}
deriving (GraphSize -> GraphSize -> Bool
(GraphSize -> GraphSize -> Bool)
-> (GraphSize -> GraphSize -> Bool) -> Eq GraphSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GraphSize -> GraphSize -> Bool
== :: GraphSize -> GraphSize -> Bool
$c/= :: GraphSize -> GraphSize -> Bool
/= :: GraphSize -> GraphSize -> Bool
Eq, Eq GraphSize
Eq GraphSize =>
(GraphSize -> GraphSize -> Ordering)
-> (GraphSize -> GraphSize -> Bool)
-> (GraphSize -> GraphSize -> Bool)
-> (GraphSize -> GraphSize -> Bool)
-> (GraphSize -> GraphSize -> Bool)
-> (GraphSize -> GraphSize -> GraphSize)
-> (GraphSize -> GraphSize -> GraphSize)
-> Ord GraphSize
GraphSize -> GraphSize -> Bool
GraphSize -> GraphSize -> Ordering
GraphSize -> GraphSize -> GraphSize
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
$ccompare :: GraphSize -> GraphSize -> Ordering
compare :: GraphSize -> GraphSize -> Ordering
$c< :: GraphSize -> GraphSize -> Bool
< :: GraphSize -> GraphSize -> Bool
$c<= :: GraphSize -> GraphSize -> Bool
<= :: GraphSize -> GraphSize -> Bool
$c> :: GraphSize -> GraphSize -> Bool
> :: GraphSize -> GraphSize -> Bool
$c>= :: GraphSize -> GraphSize -> Bool
>= :: GraphSize -> GraphSize -> Bool
$cmax :: GraphSize -> GraphSize -> GraphSize
max :: GraphSize -> GraphSize -> GraphSize
$cmin :: GraphSize -> GraphSize -> GraphSize
min :: GraphSize -> GraphSize -> GraphSize
Ord, Int -> GraphSize -> ShowS
[GraphSize] -> ShowS
GraphSize -> String
(Int -> GraphSize -> ShowS)
-> (GraphSize -> String)
-> ([GraphSize] -> ShowS)
-> Show GraphSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GraphSize -> ShowS
showsPrec :: Int -> GraphSize -> ShowS
$cshow :: GraphSize -> String
show :: GraphSize -> String
$cshowList :: [GraphSize] -> ShowS
showList :: [GraphSize] -> ShowS
Show, ReadPrec [GraphSize]
ReadPrec GraphSize
Int -> ReadS GraphSize
ReadS [GraphSize]
(Int -> ReadS GraphSize)
-> ReadS [GraphSize]
-> ReadPrec GraphSize
-> ReadPrec [GraphSize]
-> Read GraphSize
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GraphSize
readsPrec :: Int -> ReadS GraphSize
$creadList :: ReadS [GraphSize]
readList :: ReadS [GraphSize]
$creadPrec :: ReadPrec GraphSize
readPrec :: ReadPrec GraphSize
$creadListPrec :: ReadPrec [GraphSize]
readListPrec :: ReadPrec [GraphSize]
Read)
instance PrintDot GraphSize where
unqtDot :: GraphSize -> DotCode
unqtDot (GSize Double
w Maybe Double
mh Bool
ds) = (DotCode -> DotCode)
-> (DotCode -> DotCode) -> Bool -> DotCode -> DotCode
forall a. a -> a -> Bool -> a
bool DotCode -> DotCode
forall a. a -> a
id (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'!') Bool
ds
(DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotCode -> DotCode)
-> (Double -> DotCode -> DotCode)
-> Maybe Double
-> DotCode
-> DotCode
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DotCode -> DotCode
forall a. a -> a
id (\Double
h -> (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
h) (DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode
forall (m :: * -> *). Applicative m => m Doc
comma)) Maybe Double
mh
(DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
w
toDot :: GraphSize -> DotCode
toDot (GSize Double
w Maybe Double
Nothing Bool
False) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Double
w
toDot GraphSize
gs = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ GraphSize -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot GraphSize
gs
instance ParseDot GraphSize where
parseUnqt :: Parse GraphSize
parseUnqt = Double -> Maybe Double -> Bool -> GraphSize
GSize (Double -> Maybe Double -> Bool -> GraphSize)
-> Parser GraphvizState Double
-> Parser GraphvizState (Maybe Double -> Bool -> GraphSize)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt
Parser GraphvizState (Maybe Double -> Bool -> GraphSize)
-> Parser GraphvizState (Maybe Double)
-> Parser GraphvizState (Bool -> GraphSize)
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GraphvizState Double -> Parser GraphvizState (Maybe Double)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState ()
parseComma Parser GraphvizState ()
-> Parser GraphvizState () -> Parser GraphvizState ()
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState ()
whitespace Parser GraphvizState ()
-> Parser GraphvizState Double -> Parser GraphvizState Double
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt)
Parser GraphvizState (Bool -> GraphSize)
-> Parser GraphvizState Bool -> Parse GraphSize
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe Char -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Char -> Bool)
-> Parser GraphvizState (Maybe Char) -> Parser GraphvizState Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Char -> Parser GraphvizState Char
character Char
'!'))
parse :: Parse GraphSize
parse = Parse GraphSize -> Parse GraphSize
forall a. Parse a -> Parse a
quotedParse Parse GraphSize
forall a. ParseDot a => Parse a
parseUnqt
Parse GraphSize -> Parse GraphSize -> Parse GraphSize
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Double -> GraphSize)
-> Parser GraphvizState Double -> Parse GraphSize
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ Double
w -> Double -> Maybe Double -> Bool -> GraphSize
GSize Double
w Maybe Double
forall a. Maybe a
Nothing Bool
False) (Bool -> Parser GraphvizState Double
parseSignedFloat Bool
False)
data ModeType = Major
| KK
| Hier
| IpSep
| SpringMode
| MaxEnt
deriving (ModeType -> ModeType -> Bool
(ModeType -> ModeType -> Bool)
-> (ModeType -> ModeType -> Bool) -> Eq ModeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModeType -> ModeType -> Bool
== :: ModeType -> ModeType -> Bool
$c/= :: ModeType -> ModeType -> Bool
/= :: ModeType -> ModeType -> Bool
Eq, Eq ModeType
Eq ModeType =>
(ModeType -> ModeType -> Ordering)
-> (ModeType -> ModeType -> Bool)
-> (ModeType -> ModeType -> Bool)
-> (ModeType -> ModeType -> Bool)
-> (ModeType -> ModeType -> Bool)
-> (ModeType -> ModeType -> ModeType)
-> (ModeType -> ModeType -> ModeType)
-> Ord ModeType
ModeType -> ModeType -> Bool
ModeType -> ModeType -> Ordering
ModeType -> ModeType -> ModeType
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
$ccompare :: ModeType -> ModeType -> Ordering
compare :: ModeType -> ModeType -> Ordering
$c< :: ModeType -> ModeType -> Bool
< :: ModeType -> ModeType -> Bool
$c<= :: ModeType -> ModeType -> Bool
<= :: ModeType -> ModeType -> Bool
$c> :: ModeType -> ModeType -> Bool
> :: ModeType -> ModeType -> Bool
$c>= :: ModeType -> ModeType -> Bool
>= :: ModeType -> ModeType -> Bool
$cmax :: ModeType -> ModeType -> ModeType
max :: ModeType -> ModeType -> ModeType
$cmin :: ModeType -> ModeType -> ModeType
min :: ModeType -> ModeType -> ModeType
Ord, ModeType
ModeType -> ModeType -> Bounded ModeType
forall a. a -> a -> Bounded a
$cminBound :: ModeType
minBound :: ModeType
$cmaxBound :: ModeType
maxBound :: ModeType
Bounded, Int -> ModeType
ModeType -> Int
ModeType -> [ModeType]
ModeType -> ModeType
ModeType -> ModeType -> [ModeType]
ModeType -> ModeType -> ModeType -> [ModeType]
(ModeType -> ModeType)
-> (ModeType -> ModeType)
-> (Int -> ModeType)
-> (ModeType -> Int)
-> (ModeType -> [ModeType])
-> (ModeType -> ModeType -> [ModeType])
-> (ModeType -> ModeType -> [ModeType])
-> (ModeType -> ModeType -> ModeType -> [ModeType])
-> Enum ModeType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ModeType -> ModeType
succ :: ModeType -> ModeType
$cpred :: ModeType -> ModeType
pred :: ModeType -> ModeType
$ctoEnum :: Int -> ModeType
toEnum :: Int -> ModeType
$cfromEnum :: ModeType -> Int
fromEnum :: ModeType -> Int
$cenumFrom :: ModeType -> [ModeType]
enumFrom :: ModeType -> [ModeType]
$cenumFromThen :: ModeType -> ModeType -> [ModeType]
enumFromThen :: ModeType -> ModeType -> [ModeType]
$cenumFromTo :: ModeType -> ModeType -> [ModeType]
enumFromTo :: ModeType -> ModeType -> [ModeType]
$cenumFromThenTo :: ModeType -> ModeType -> ModeType -> [ModeType]
enumFromThenTo :: ModeType -> ModeType -> ModeType -> [ModeType]
Enum, Int -> ModeType -> ShowS
[ModeType] -> ShowS
ModeType -> String
(Int -> ModeType -> ShowS)
-> (ModeType -> String) -> ([ModeType] -> ShowS) -> Show ModeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModeType -> ShowS
showsPrec :: Int -> ModeType -> ShowS
$cshow :: ModeType -> String
show :: ModeType -> String
$cshowList :: [ModeType] -> ShowS
showList :: [ModeType] -> ShowS
Show, ReadPrec [ModeType]
ReadPrec ModeType
Int -> ReadS ModeType
ReadS [ModeType]
(Int -> ReadS ModeType)
-> ReadS [ModeType]
-> ReadPrec ModeType
-> ReadPrec [ModeType]
-> Read ModeType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ModeType
readsPrec :: Int -> ReadS ModeType
$creadList :: ReadS [ModeType]
readList :: ReadS [ModeType]
$creadPrec :: ReadPrec ModeType
readPrec :: ReadPrec ModeType
$creadListPrec :: ReadPrec [ModeType]
readListPrec :: ReadPrec [ModeType]
Read)
instance PrintDot ModeType where
unqtDot :: ModeType -> DotCode
unqtDot ModeType
Major = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"major"
unqtDot ModeType
KK = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"KK"
unqtDot ModeType
Hier = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"hier"
unqtDot ModeType
IpSep = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"ipsep"
unqtDot ModeType
SpringMode = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"spring"
unqtDot ModeType
MaxEnt = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"maxent"
instance ParseDot ModeType where
parseUnqt :: Parse ModeType
parseUnqt = [Parse ModeType] -> Parse ModeType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ ModeType -> String -> Parse ModeType
forall a. a -> String -> Parse a
stringRep ModeType
Major String
"major"
, ModeType -> String -> Parse ModeType
forall a. a -> String -> Parse a
stringRep ModeType
KK String
"KK"
, ModeType -> String -> Parse ModeType
forall a. a -> String -> Parse a
stringRep ModeType
Hier String
"hier"
, ModeType -> String -> Parse ModeType
forall a. a -> String -> Parse a
stringRep ModeType
IpSep String
"ipsep"
, ModeType -> String -> Parse ModeType
forall a. a -> String -> Parse a
stringRep ModeType
SpringMode String
"spring"
, ModeType -> String -> Parse ModeType
forall a. a -> String -> Parse a
stringRep ModeType
MaxEnt String
"maxent"
]
data Model = ShortPath
| SubSet
| Circuit
| MDS
deriving (Model -> Model -> Bool
(Model -> Model -> Bool) -> (Model -> Model -> Bool) -> Eq Model
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Model -> Model -> Bool
== :: Model -> Model -> Bool
$c/= :: Model -> Model -> Bool
/= :: Model -> Model -> Bool
Eq, Eq Model
Eq Model =>
(Model -> Model -> Ordering)
-> (Model -> Model -> Bool)
-> (Model -> Model -> Bool)
-> (Model -> Model -> Bool)
-> (Model -> Model -> Bool)
-> (Model -> Model -> Model)
-> (Model -> Model -> Model)
-> Ord Model
Model -> Model -> Bool
Model -> Model -> Ordering
Model -> Model -> Model
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
$ccompare :: Model -> Model -> Ordering
compare :: Model -> Model -> Ordering
$c< :: Model -> Model -> Bool
< :: Model -> Model -> Bool
$c<= :: Model -> Model -> Bool
<= :: Model -> Model -> Bool
$c> :: Model -> Model -> Bool
> :: Model -> Model -> Bool
$c>= :: Model -> Model -> Bool
>= :: Model -> Model -> Bool
$cmax :: Model -> Model -> Model
max :: Model -> Model -> Model
$cmin :: Model -> Model -> Model
min :: Model -> Model -> Model
Ord, Model
Model -> Model -> Bounded Model
forall a. a -> a -> Bounded a
$cminBound :: Model
minBound :: Model
$cmaxBound :: Model
maxBound :: Model
Bounded, Int -> Model
Model -> Int
Model -> [Model]
Model -> Model
Model -> Model -> [Model]
Model -> Model -> Model -> [Model]
(Model -> Model)
-> (Model -> Model)
-> (Int -> Model)
-> (Model -> Int)
-> (Model -> [Model])
-> (Model -> Model -> [Model])
-> (Model -> Model -> [Model])
-> (Model -> Model -> Model -> [Model])
-> Enum Model
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Model -> Model
succ :: Model -> Model
$cpred :: Model -> Model
pred :: Model -> Model
$ctoEnum :: Int -> Model
toEnum :: Int -> Model
$cfromEnum :: Model -> Int
fromEnum :: Model -> Int
$cenumFrom :: Model -> [Model]
enumFrom :: Model -> [Model]
$cenumFromThen :: Model -> Model -> [Model]
enumFromThen :: Model -> Model -> [Model]
$cenumFromTo :: Model -> Model -> [Model]
enumFromTo :: Model -> Model -> [Model]
$cenumFromThenTo :: Model -> Model -> Model -> [Model]
enumFromThenTo :: Model -> Model -> Model -> [Model]
Enum, Int -> Model -> ShowS
[Model] -> ShowS
Model -> String
(Int -> Model -> ShowS)
-> (Model -> String) -> ([Model] -> ShowS) -> Show Model
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Model -> ShowS
showsPrec :: Int -> Model -> ShowS
$cshow :: Model -> String
show :: Model -> String
$cshowList :: [Model] -> ShowS
showList :: [Model] -> ShowS
Show, ReadPrec [Model]
ReadPrec Model
Int -> ReadS Model
ReadS [Model]
(Int -> ReadS Model)
-> ReadS [Model]
-> ReadPrec Model
-> ReadPrec [Model]
-> Read Model
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Model
readsPrec :: Int -> ReadS Model
$creadList :: ReadS [Model]
readList :: ReadS [Model]
$creadPrec :: ReadPrec Model
readPrec :: ReadPrec Model
$creadListPrec :: ReadPrec [Model]
readListPrec :: ReadPrec [Model]
Read)
instance PrintDot Model where
unqtDot :: Model -> DotCode
unqtDot Model
ShortPath = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"shortpath"
unqtDot Model
SubSet = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"subset"
unqtDot Model
Circuit = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"circuit"
unqtDot Model
MDS = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"mds"
instance ParseDot Model where
parseUnqt :: Parse Model
parseUnqt = [Parse Model] -> Parse Model
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Model -> String -> Parse Model
forall a. a -> String -> Parse a
stringRep Model
ShortPath String
"shortpath"
, Model -> String -> Parse Model
forall a. a -> String -> Parse a
stringRep Model
SubSet String
"subset"
, Model -> String -> Parse Model
forall a. a -> String -> Parse a
stringRep Model
Circuit String
"circuit"
, Model -> String -> Parse Model
forall a. a -> String -> Parse a
stringRep Model
MDS String
"mds"
]
data Label = StrLabel EscString
| HtmlLabel Html.Label
| RecordLabel RecordFields
deriving (Label -> Label -> Bool
(Label -> Label -> Bool) -> (Label -> Label -> Bool) -> Eq Label
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Label -> Label -> Bool
== :: Label -> Label -> Bool
$c/= :: Label -> Label -> Bool
/= :: Label -> Label -> Bool
Eq, Eq Label
Eq Label =>
(Label -> Label -> Ordering)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Bool)
-> (Label -> Label -> Label)
-> (Label -> Label -> Label)
-> Ord Label
Label -> Label -> Bool
Label -> Label -> Ordering
Label -> Label -> Label
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
$ccompare :: Label -> Label -> Ordering
compare :: Label -> Label -> Ordering
$c< :: Label -> Label -> Bool
< :: Label -> Label -> Bool
$c<= :: Label -> Label -> Bool
<= :: Label -> Label -> Bool
$c> :: Label -> Label -> Bool
> :: Label -> Label -> Bool
$c>= :: Label -> Label -> Bool
>= :: Label -> Label -> Bool
$cmax :: Label -> Label -> Label
max :: Label -> Label -> Label
$cmin :: Label -> Label -> Label
min :: Label -> Label -> Label
Ord, Int -> Label -> ShowS
[Label] -> ShowS
Label -> String
(Int -> Label -> ShowS)
-> (Label -> String) -> ([Label] -> ShowS) -> Show Label
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Label -> ShowS
showsPrec :: Int -> Label -> ShowS
$cshow :: Label -> String
show :: Label -> String
$cshowList :: [Label] -> ShowS
showList :: [Label] -> ShowS
Show, ReadPrec [Label]
ReadPrec Label
Int -> ReadS Label
ReadS [Label]
(Int -> ReadS Label)
-> ReadS [Label]
-> ReadPrec Label
-> ReadPrec [Label]
-> Read Label
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Label
readsPrec :: Int -> ReadS Label
$creadList :: ReadS [Label]
readList :: ReadS [Label]
$creadPrec :: ReadPrec Label
readPrec :: ReadPrec Label
$creadListPrec :: ReadPrec [Label]
readListPrec :: ReadPrec [Label]
Read)
instance PrintDot Label where
unqtDot :: Label -> DotCode
unqtDot (StrLabel Text
s) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
s
unqtDot (HtmlLabel Label
h) = DotCode -> DotCode
angled (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ Label -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Label
h
unqtDot (RecordLabel RecordFields
fs) = RecordFields -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot RecordFields
fs
toDot :: Label -> DotCode
toDot (StrLabel Text
s) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
s
toDot h :: Label
h@HtmlLabel{} = Label -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Label
h
toDot (RecordLabel RecordFields
fs) = RecordFields -> DotCode
forall a. PrintDot a => a -> DotCode
toDot RecordFields
fs
instance ParseDot Label where
parseUnqt :: Parse Label
parseUnqt = [Parse Label] -> Parse Label
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Label -> Label
HtmlLabel (Label -> Label) -> Parser GraphvizState Label -> Parse Label
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Label -> Parser GraphvizState Label
forall a. Parse a -> Parse a
parseAngled Parser GraphvizState Label
forall a. ParseDot a => Parse a
parseUnqt
, RecordFields -> Label
RecordLabel (RecordFields -> Label)
-> Parser GraphvizState RecordFields -> Parse Label
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState RecordFields
forall a. ParseDot a => Parse a
parseUnqt
, Text -> Label
StrLabel (Text -> Label) -> Parser GraphvizState Text -> Parse Label
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Text
forall a. ParseDot a => Parse a
parseUnqt
]
parse :: Parse Label
parse = [Parse Label] -> Parse Label
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Label -> Label
HtmlLabel (Label -> Label) -> Parser GraphvizState Label -> Parse Label
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Label -> Parser GraphvizState Label
forall a. Parse a -> Parse a
parseAngled Parser GraphvizState Label
forall a. ParseDot a => Parse a
parse
, RecordFields -> Label
RecordLabel (RecordFields -> Label)
-> Parser GraphvizState RecordFields -> Parse Label
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState RecordFields
forall a. ParseDot a => Parse a
parse
, Text -> Label
StrLabel (Text -> Label) -> Parser GraphvizState Text -> Parse Label
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Text
forall a. ParseDot a => Parse a
parse
]
type RecordFields = [RecordField]
data RecordField = LabelledTarget PortName EscString
| PortName PortName
| FieldLabel EscString
| FlipFields RecordFields
deriving (RecordField -> RecordField -> Bool
(RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool) -> Eq RecordField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecordField -> RecordField -> Bool
== :: RecordField -> RecordField -> Bool
$c/= :: RecordField -> RecordField -> Bool
/= :: RecordField -> RecordField -> Bool
Eq, Eq RecordField
Eq RecordField =>
(RecordField -> RecordField -> Ordering)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> RecordField)
-> (RecordField -> RecordField -> RecordField)
-> Ord RecordField
RecordField -> RecordField -> Bool
RecordField -> RecordField -> Ordering
RecordField -> RecordField -> RecordField
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
$ccompare :: RecordField -> RecordField -> Ordering
compare :: RecordField -> RecordField -> Ordering
$c< :: RecordField -> RecordField -> Bool
< :: RecordField -> RecordField -> Bool
$c<= :: RecordField -> RecordField -> Bool
<= :: RecordField -> RecordField -> Bool
$c> :: RecordField -> RecordField -> Bool
> :: RecordField -> RecordField -> Bool
$c>= :: RecordField -> RecordField -> Bool
>= :: RecordField -> RecordField -> Bool
$cmax :: RecordField -> RecordField -> RecordField
max :: RecordField -> RecordField -> RecordField
$cmin :: RecordField -> RecordField -> RecordField
min :: RecordField -> RecordField -> RecordField
Ord, Int -> RecordField -> ShowS
RecordFields -> ShowS
RecordField -> String
(Int -> RecordField -> ShowS)
-> (RecordField -> String)
-> (RecordFields -> ShowS)
-> Show RecordField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RecordField -> ShowS
showsPrec :: Int -> RecordField -> ShowS
$cshow :: RecordField -> String
show :: RecordField -> String
$cshowList :: RecordFields -> ShowS
showList :: RecordFields -> ShowS
Show, ReadPrec RecordFields
ReadPrec RecordField
Int -> ReadS RecordField
ReadS RecordFields
(Int -> ReadS RecordField)
-> ReadS RecordFields
-> ReadPrec RecordField
-> ReadPrec RecordFields
-> Read RecordField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RecordField
readsPrec :: Int -> ReadS RecordField
$creadList :: ReadS RecordFields
readList :: ReadS RecordFields
$creadPrec :: ReadPrec RecordField
readPrec :: ReadPrec RecordField
$creadListPrec :: ReadPrec RecordFields
readListPrec :: ReadPrec RecordFields
Read)
instance PrintDot RecordField where
unqtDot :: RecordField -> DotCode
unqtDot (LabelledTarget PortName
t Text
s) = PortName -> DotCode
printPortName PortName
t DotCode -> DotCode -> DotCode
forall (m :: * -> *). Applicative m => m Doc -> m Doc -> m Doc
<+> Text -> DotCode
unqtRecordString Text
s
unqtDot (PortName PortName
t) = PortName -> DotCode
printPortName PortName
t
unqtDot (FieldLabel Text
s) = Text -> DotCode
unqtRecordString Text
s
unqtDot (FlipFields RecordFields
rs) = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
braces (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ RecordFields -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot RecordFields
rs
toDot :: RecordField -> DotCode
toDot (FieldLabel Text
s) = String -> Text -> DotCode
printEscaped String
recordEscChars Text
s
toDot RecordField
rf = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ RecordField -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot RecordField
rf
unqtListToDot :: RecordFields -> DotCode
unqtListToDot [RecordField
f] = RecordField -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot RecordField
f
unqtListToDot RecordFields
fs = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> (DotCodeM [Doc] -> DotCodeM [Doc]) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate (Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'|') (DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall a b. (a -> b) -> a -> b
$ (RecordField -> DotCode) -> RecordFields -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM RecordField -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot RecordFields
fs
listToDot :: RecordFields -> DotCode
listToDot [RecordField
f] = RecordField -> DotCode
forall a. PrintDot a => a -> DotCode
toDot RecordField
f
listToDot RecordFields
fs = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ RecordFields -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot RecordFields
fs
instance ParseDot RecordField where
parseUnqt :: Parse RecordField
parseUnqt = ((RecordField -> (Text -> RecordField) -> Maybe Text -> RecordField)
-> (PortName -> RecordField)
-> (PortName -> Text -> RecordField)
-> PortName
-> Maybe Text
-> RecordField
forall a b c.
(a -> b -> c)
-> (PortName -> a) -> (PortName -> b) -> PortName -> c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 RecordField -> (Text -> RecordField) -> Maybe Text -> RecordField
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PortName -> RecordField
PortName PortName -> Text -> RecordField
LabelledTarget
(PortName -> Maybe Text -> RecordField)
-> Parser GraphvizState PortName
-> Parser GraphvizState (Maybe Text -> RecordField)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> PortName
PN (Text -> PortName)
-> Parser GraphvizState Text -> Parser GraphvizState PortName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Text -> Parser GraphvizState Text
forall a. Parse a -> Parse a
parseAngled Parser GraphvizState Text
parseRecord)
Parser GraphvizState (Maybe Text -> RecordField)
-> Parser GraphvizState (Maybe Text) -> Parse RecordField
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GraphvizState Text -> Parser GraphvizState (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState ()
whitespace1 Parser GraphvizState ()
-> Parser GraphvizState Text -> Parser GraphvizState Text
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState Text
parseRecord)
)
Parse RecordField -> Parse RecordField -> Parse RecordField
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> RecordField)
-> Parser GraphvizState Text -> Parse RecordField
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> RecordField
FieldLabel Parser GraphvizState Text
parseRecord
Parse RecordField -> Parse RecordField -> Parse RecordField
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(RecordFields -> RecordField)
-> Parser GraphvizState RecordFields -> Parse RecordField
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RecordFields -> RecordField
FlipFields (Parser GraphvizState RecordFields
-> Parser GraphvizState RecordFields
forall a. Parse a -> Parse a
parseBraced Parser GraphvizState RecordFields
forall a. ParseDot a => Parse a
parseUnqt)
Parse RecordField -> Parse RecordField -> Parse RecordField
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
String -> Parse RecordField
forall a. String -> Parser GraphvizState a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unable to parse RecordField"
parse :: Parse RecordField
parse = Parse RecordField -> Parse RecordField
forall a. Parse a -> Parse a
quotedParse Parse RecordField
forall a. ParseDot a => Parse a
parseUnqt
parseUnqtList :: Parser GraphvizState RecordFields
parseUnqtList = Parser GraphvizState RecordFields
-> Parser GraphvizState RecordFields
forall a. Parse a -> Parse a
wrapWhitespace (Parser GraphvizState RecordFields
-> Parser GraphvizState RecordFields)
-> Parser GraphvizState RecordFields
-> Parser GraphvizState RecordFields
forall a b. (a -> b) -> a -> b
$ Parse RecordField
-> Parser GraphvizState Char -> Parser GraphvizState RecordFields
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse RecordField
forall a. ParseDot a => Parse a
parseUnqt (Parser GraphvizState Char -> Parser GraphvizState Char
forall a. Parse a -> Parse a
wrapWhitespace (Parser GraphvizState Char -> Parser GraphvizState Char)
-> Parser GraphvizState Char -> Parser GraphvizState Char
forall a b. (a -> b) -> a -> b
$ Char -> Parser GraphvizState Char
character Char
'|')
parseList :: Parser GraphvizState RecordFields
parseList = do RecordFields
rfs <- Parser GraphvizState RecordFields
-> Parser GraphvizState RecordFields
forall a. Parse a -> Parse a
quotedParse Parser GraphvizState RecordFields
forall a. ParseDot a => Parse [a]
parseUnqtList
if RecordFields -> Bool
validRFs RecordFields
rfs
then RecordFields -> Parser GraphvizState RecordFields
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return RecordFields
rfs
else String -> Parser GraphvizState RecordFields
forall a. String -> Parser GraphvizState a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"This is a StrLabel, not a RecordLabel"
where
validRFs :: RecordFields -> Bool
validRFs [FieldLabel Text
str] = (Char -> Bool) -> Text -> Bool
T.any (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
recordEscChars) Text
str
validRFs RecordFields
_ = Bool
True
printPortName :: PortName -> DotCode
printPortName :: PortName -> DotCode
printPortName = DotCode -> DotCode
angled (DotCode -> DotCode)
-> (PortName -> DotCode) -> PortName -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> DotCode
unqtRecordString (Text -> DotCode) -> (PortName -> Text) -> PortName -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PortName -> Text
portName
parseRecord :: Parse Text
parseRecord :: Parser GraphvizState Text
parseRecord = Bool -> String -> String -> Parser GraphvizState Text
parseEscaped Bool
False String
recordEscChars []
unqtRecordString :: Text -> DotCode
unqtRecordString :: Text -> DotCode
unqtRecordString = String -> Text -> DotCode
unqtEscaped String
recordEscChars
recordEscChars :: [Char]
recordEscChars :: String
recordEscChars = [Char
'{', Char
'}', Char
'|', Char
' ', Char
'<', Char
'>']
data LabelScheme = NotEdgeLabel
| CloseToCenter
| CloseToOldCenter
| RemoveAndStraighten
deriving (LabelScheme -> LabelScheme -> Bool
(LabelScheme -> LabelScheme -> Bool)
-> (LabelScheme -> LabelScheme -> Bool) -> Eq LabelScheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LabelScheme -> LabelScheme -> Bool
== :: LabelScheme -> LabelScheme -> Bool
$c/= :: LabelScheme -> LabelScheme -> Bool
/= :: LabelScheme -> LabelScheme -> Bool
Eq, Eq LabelScheme
Eq LabelScheme =>
(LabelScheme -> LabelScheme -> Ordering)
-> (LabelScheme -> LabelScheme -> Bool)
-> (LabelScheme -> LabelScheme -> Bool)
-> (LabelScheme -> LabelScheme -> Bool)
-> (LabelScheme -> LabelScheme -> Bool)
-> (LabelScheme -> LabelScheme -> LabelScheme)
-> (LabelScheme -> LabelScheme -> LabelScheme)
-> Ord LabelScheme
LabelScheme -> LabelScheme -> Bool
LabelScheme -> LabelScheme -> Ordering
LabelScheme -> LabelScheme -> LabelScheme
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
$ccompare :: LabelScheme -> LabelScheme -> Ordering
compare :: LabelScheme -> LabelScheme -> Ordering
$c< :: LabelScheme -> LabelScheme -> Bool
< :: LabelScheme -> LabelScheme -> Bool
$c<= :: LabelScheme -> LabelScheme -> Bool
<= :: LabelScheme -> LabelScheme -> Bool
$c> :: LabelScheme -> LabelScheme -> Bool
> :: LabelScheme -> LabelScheme -> Bool
$c>= :: LabelScheme -> LabelScheme -> Bool
>= :: LabelScheme -> LabelScheme -> Bool
$cmax :: LabelScheme -> LabelScheme -> LabelScheme
max :: LabelScheme -> LabelScheme -> LabelScheme
$cmin :: LabelScheme -> LabelScheme -> LabelScheme
min :: LabelScheme -> LabelScheme -> LabelScheme
Ord, LabelScheme
LabelScheme -> LabelScheme -> Bounded LabelScheme
forall a. a -> a -> Bounded a
$cminBound :: LabelScheme
minBound :: LabelScheme
$cmaxBound :: LabelScheme
maxBound :: LabelScheme
Bounded, Int -> LabelScheme
LabelScheme -> Int
LabelScheme -> [LabelScheme]
LabelScheme -> LabelScheme
LabelScheme -> LabelScheme -> [LabelScheme]
LabelScheme -> LabelScheme -> LabelScheme -> [LabelScheme]
(LabelScheme -> LabelScheme)
-> (LabelScheme -> LabelScheme)
-> (Int -> LabelScheme)
-> (LabelScheme -> Int)
-> (LabelScheme -> [LabelScheme])
-> (LabelScheme -> LabelScheme -> [LabelScheme])
-> (LabelScheme -> LabelScheme -> [LabelScheme])
-> (LabelScheme -> LabelScheme -> LabelScheme -> [LabelScheme])
-> Enum LabelScheme
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: LabelScheme -> LabelScheme
succ :: LabelScheme -> LabelScheme
$cpred :: LabelScheme -> LabelScheme
pred :: LabelScheme -> LabelScheme
$ctoEnum :: Int -> LabelScheme
toEnum :: Int -> LabelScheme
$cfromEnum :: LabelScheme -> Int
fromEnum :: LabelScheme -> Int
$cenumFrom :: LabelScheme -> [LabelScheme]
enumFrom :: LabelScheme -> [LabelScheme]
$cenumFromThen :: LabelScheme -> LabelScheme -> [LabelScheme]
enumFromThen :: LabelScheme -> LabelScheme -> [LabelScheme]
$cenumFromTo :: LabelScheme -> LabelScheme -> [LabelScheme]
enumFromTo :: LabelScheme -> LabelScheme -> [LabelScheme]
$cenumFromThenTo :: LabelScheme -> LabelScheme -> LabelScheme -> [LabelScheme]
enumFromThenTo :: LabelScheme -> LabelScheme -> LabelScheme -> [LabelScheme]
Enum, Int -> LabelScheme -> ShowS
[LabelScheme] -> ShowS
LabelScheme -> String
(Int -> LabelScheme -> ShowS)
-> (LabelScheme -> String)
-> ([LabelScheme] -> ShowS)
-> Show LabelScheme
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LabelScheme -> ShowS
showsPrec :: Int -> LabelScheme -> ShowS
$cshow :: LabelScheme -> String
show :: LabelScheme -> String
$cshowList :: [LabelScheme] -> ShowS
showList :: [LabelScheme] -> ShowS
Show, ReadPrec [LabelScheme]
ReadPrec LabelScheme
Int -> ReadS LabelScheme
ReadS [LabelScheme]
(Int -> ReadS LabelScheme)
-> ReadS [LabelScheme]
-> ReadPrec LabelScheme
-> ReadPrec [LabelScheme]
-> Read LabelScheme
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LabelScheme
readsPrec :: Int -> ReadS LabelScheme
$creadList :: ReadS [LabelScheme]
readList :: ReadS [LabelScheme]
$creadPrec :: ReadPrec LabelScheme
readPrec :: ReadPrec LabelScheme
$creadListPrec :: ReadPrec [LabelScheme]
readListPrec :: ReadPrec [LabelScheme]
Read)
instance PrintDot LabelScheme where
unqtDot :: LabelScheme -> DotCode
unqtDot LabelScheme
NotEdgeLabel = Int -> DotCode
forall (m :: * -> *). Applicative m => Int -> m Doc
int Int
0
unqtDot LabelScheme
CloseToCenter = Int -> DotCode
forall (m :: * -> *). Applicative m => Int -> m Doc
int Int
1
unqtDot LabelScheme
CloseToOldCenter = Int -> DotCode
forall (m :: * -> *). Applicative m => Int -> m Doc
int Int
2
unqtDot LabelScheme
RemoveAndStraighten = Int -> DotCode
forall (m :: * -> *). Applicative m => Int -> m Doc
int Int
3
instance ParseDot LabelScheme where
parseUnqt :: Parse LabelScheme
parseUnqt = [(String, LabelScheme)] -> Parse LabelScheme
forall a. [(String, a)] -> Parse a
stringValue [ (String
"0", LabelScheme
NotEdgeLabel)
, (String
"1", LabelScheme
CloseToCenter)
, (String
"2", LabelScheme
CloseToOldCenter)
, (String
"3", LabelScheme
RemoveAndStraighten)
]
data Point = Point { Point -> Double
xCoord :: Double
, Point -> Double
yCoord :: Double
, Point -> Maybe Double
zCoord :: Maybe Double
, Point -> Bool
forcePos :: Bool
}
deriving (Point -> Point -> Bool
(Point -> Point -> Bool) -> (Point -> Point -> Bool) -> Eq Point
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Point -> Point -> Bool
== :: Point -> Point -> Bool
$c/= :: Point -> Point -> Bool
/= :: Point -> Point -> Bool
Eq, Eq Point
Eq Point =>
(Point -> Point -> Ordering)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> Ord Point
Point -> Point -> Bool
Point -> Point -> Ordering
Point -> Point -> Point
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
$ccompare :: Point -> Point -> Ordering
compare :: Point -> Point -> Ordering
$c< :: Point -> Point -> Bool
< :: Point -> Point -> Bool
$c<= :: Point -> Point -> Bool
<= :: Point -> Point -> Bool
$c> :: Point -> Point -> Bool
> :: Point -> Point -> Bool
$c>= :: Point -> Point -> Bool
>= :: Point -> Point -> Bool
$cmax :: Point -> Point -> Point
max :: Point -> Point -> Point
$cmin :: Point -> Point -> Point
min :: Point -> Point -> Point
Ord, Int -> Point -> ShowS
[Point] -> ShowS
Point -> String
(Int -> Point -> ShowS)
-> (Point -> String) -> ([Point] -> ShowS) -> Show Point
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Point -> ShowS
showsPrec :: Int -> Point -> ShowS
$cshow :: Point -> String
show :: Point -> String
$cshowList :: [Point] -> ShowS
showList :: [Point] -> ShowS
Show, ReadPrec [Point]
ReadPrec Point
Int -> ReadS Point
ReadS [Point]
(Int -> ReadS Point)
-> ReadS [Point]
-> ReadPrec Point
-> ReadPrec [Point]
-> Read Point
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Point
readsPrec :: Int -> ReadS Point
$creadList :: ReadS [Point]
readList :: ReadS [Point]
$creadPrec :: ReadPrec Point
readPrec :: ReadPrec Point
$creadListPrec :: ReadPrec [Point]
readListPrec :: ReadPrec [Point]
Read)
createPoint :: Double -> Double -> Point
createPoint :: Double -> Double -> Point
createPoint Double
x Double
y = Double -> Double -> Maybe Double -> Bool -> Point
Point Double
x Double
y Maybe Double
forall a. Maybe a
Nothing Bool
False
printPoint2DUnqt :: Point -> DotCode
printPoint2DUnqt :: Point -> DotCode
printPoint2DUnqt Point
p = Double -> Double -> DotCode
forall a b. (PrintDot a, PrintDot b) => a -> b -> DotCode
commaDel (Point -> Double
xCoord Point
p) (Point -> Double
yCoord Point
p)
printPoint2D :: Point -> DotCode
printPoint2D :: Point -> DotCode
printPoint2D = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> (Point -> DotCode) -> Point -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Point -> DotCode
printPoint2DUnqt
parsePoint2D :: Parse Point
parsePoint2D :: Parse Point
parsePoint2D = (Double -> Double -> Point) -> (Double, Double) -> Point
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Double -> Double -> Point
createPoint ((Double, Double) -> Point)
-> Parser GraphvizState (Double, Double) -> Parse Point
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState (Double, Double)
forall a b. (ParseDot a, ParseDot b) => Parse (a, b)
commaSepUnqt
instance PrintDot Point where
unqtDot :: Point -> DotCode
unqtDot (Point Double
x Double
y Maybe Double
mz Bool
frs) = (DotCode -> DotCode)
-> (DotCode -> DotCode) -> Bool -> DotCode -> DotCode
forall a. a -> a -> Bool -> a
bool DotCode -> DotCode
forall a. a -> a
id (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'!') Bool
frs
(DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotCode -> DotCode)
-> (Double -> DotCode -> DotCode)
-> Maybe Double
-> DotCode
-> DotCode
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DotCode -> DotCode
forall a. a -> a
id (\ Double
z -> (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
z) (DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode
forall (m :: * -> *). Applicative m => m Doc
comma)) Maybe Double
mz
(DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ Double -> Double -> DotCode
forall a b. (PrintDot a, PrintDot b) => a -> b -> DotCode
commaDel Double
x Double
y
toDot :: Point -> DotCode
toDot = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> (Point -> DotCode) -> Point -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Point -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
unqtListToDot :: [Point] -> DotCode
unqtListToDot = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hsep (DotCodeM [Doc] -> DotCode)
-> ([Point] -> DotCodeM [Doc]) -> [Point] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point -> DotCode) -> [Point] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Point -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
listToDot :: [Point] -> DotCode
listToDot = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> ([Point] -> DotCode) -> [Point] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Point] -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot
instance ParseDot Point where
parseUnqt :: Parse Point
parseUnqt = (Double -> Double -> Maybe Double -> Bool -> Point)
-> (Double, Double) -> Maybe Double -> Bool -> Point
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Double -> Double -> Maybe Double -> Bool -> Point
Point
((Double, Double) -> Maybe Double -> Bool -> Point)
-> Parser GraphvizState (Double, Double)
-> Parser GraphvizState (Maybe Double -> Bool -> Point)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState (Double, Double)
forall a b. (ParseDot a, ParseDot b) => Parse (a, b)
commaSepUnqt
Parser GraphvizState (Maybe Double -> Bool -> Point)
-> Parser GraphvizState (Maybe Double)
-> Parser GraphvizState (Bool -> Point)
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GraphvizState Double -> Parser GraphvizState (Maybe Double)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState ()
parseComma Parser GraphvizState ()
-> Parser GraphvizState Double -> Parser GraphvizState Double
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt)
Parser GraphvizState (Bool -> Point)
-> Parser GraphvizState Bool -> Parse Point
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe Char -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Char -> Bool)
-> Parser GraphvizState (Maybe Char) -> Parser GraphvizState Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Char -> Parser GraphvizState Char
character Char
'!'))
parse :: Parse Point
parse = Parse Point -> Parse Point
forall a. Parse a -> Parse a
quotedParse Parse Point
forall a. ParseDot a => Parse a
parseUnqt
parseUnqtList :: Parse [Point]
parseUnqtList = Parse Point -> Parser GraphvizState () -> Parse [Point]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse Point
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
whitespace1
data Overlap = KeepOverlaps
| ScaleOverlaps
| ScaleXYOverlaps
| PrismOverlap (Maybe Word16)
| VoronoiOverlap
| CompressOverlap
| VpscOverlap
| IpsepOverlap
deriving (Overlap -> Overlap -> Bool
(Overlap -> Overlap -> Bool)
-> (Overlap -> Overlap -> Bool) -> Eq Overlap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Overlap -> Overlap -> Bool
== :: Overlap -> Overlap -> Bool
$c/= :: Overlap -> Overlap -> Bool
/= :: Overlap -> Overlap -> Bool
Eq, Eq Overlap
Eq Overlap =>
(Overlap -> Overlap -> Ordering)
-> (Overlap -> Overlap -> Bool)
-> (Overlap -> Overlap -> Bool)
-> (Overlap -> Overlap -> Bool)
-> (Overlap -> Overlap -> Bool)
-> (Overlap -> Overlap -> Overlap)
-> (Overlap -> Overlap -> Overlap)
-> Ord Overlap
Overlap -> Overlap -> Bool
Overlap -> Overlap -> Ordering
Overlap -> Overlap -> Overlap
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
$ccompare :: Overlap -> Overlap -> Ordering
compare :: Overlap -> Overlap -> Ordering
$c< :: Overlap -> Overlap -> Bool
< :: Overlap -> Overlap -> Bool
$c<= :: Overlap -> Overlap -> Bool
<= :: Overlap -> Overlap -> Bool
$c> :: Overlap -> Overlap -> Bool
> :: Overlap -> Overlap -> Bool
$c>= :: Overlap -> Overlap -> Bool
>= :: Overlap -> Overlap -> Bool
$cmax :: Overlap -> Overlap -> Overlap
max :: Overlap -> Overlap -> Overlap
$cmin :: Overlap -> Overlap -> Overlap
min :: Overlap -> Overlap -> Overlap
Ord, Int -> Overlap -> ShowS
[Overlap] -> ShowS
Overlap -> String
(Int -> Overlap -> ShowS)
-> (Overlap -> String) -> ([Overlap] -> ShowS) -> Show Overlap
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Overlap -> ShowS
showsPrec :: Int -> Overlap -> ShowS
$cshow :: Overlap -> String
show :: Overlap -> String
$cshowList :: [Overlap] -> ShowS
showList :: [Overlap] -> ShowS
Show, ReadPrec [Overlap]
ReadPrec Overlap
Int -> ReadS Overlap
ReadS [Overlap]
(Int -> ReadS Overlap)
-> ReadS [Overlap]
-> ReadPrec Overlap
-> ReadPrec [Overlap]
-> Read Overlap
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Overlap
readsPrec :: Int -> ReadS Overlap
$creadList :: ReadS [Overlap]
readList :: ReadS [Overlap]
$creadPrec :: ReadPrec Overlap
readPrec :: ReadPrec Overlap
$creadListPrec :: ReadPrec [Overlap]
readListPrec :: ReadPrec [Overlap]
Read)
instance PrintDot Overlap where
unqtDot :: Overlap -> DotCode
unqtDot Overlap
KeepOverlaps = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot Overlap
ScaleOverlaps = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"scale"
unqtDot Overlap
ScaleXYOverlaps = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"scalexy"
unqtDot (PrismOverlap Maybe Word16
i) = (DotCode -> DotCode)
-> (Word16 -> DotCode -> DotCode)
-> Maybe Word16
-> DotCode
-> DotCode
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DotCode -> DotCode
forall a. a -> a
id ((DotCode -> DotCode -> DotCode) -> DotCode -> DotCode -> DotCode
forall a b c. (a -> b -> c) -> b -> a -> c
flip DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
(<>) (DotCode -> DotCode -> DotCode)
-> (Word16 -> DotCode) -> Word16 -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot) Maybe Word16
i (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"prism"
unqtDot Overlap
VoronoiOverlap = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"voronoi"
unqtDot Overlap
CompressOverlap = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"compress"
unqtDot Overlap
VpscOverlap = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"vpsc"
unqtDot Overlap
IpsepOverlap = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"ipsep"
instance ParseDot Overlap where
parseUnqt :: Parse Overlap
parseUnqt = [Parse Overlap] -> Parse Overlap
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
KeepOverlaps String
"true"
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
ScaleXYOverlaps String
"scalexy"
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
ScaleOverlaps String
"scale"
, String -> Parser GraphvizState ()
string String
"prism" Parser GraphvizState () -> Parse Overlap -> Parse Overlap
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (Maybe Word16 -> Overlap)
-> Parser GraphvizState (Maybe Word16) -> Parse Overlap
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Word16 -> Overlap
PrismOverlap (Parser GraphvizState Word16 -> Parser GraphvizState (Maybe Word16)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser GraphvizState Word16
forall a. ParseDot a => Parse a
parse)
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep (Maybe Word16 -> Overlap
PrismOverlap Maybe Word16
forall a. Maybe a
Nothing) String
"false"
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
VoronoiOverlap String
"voronoi"
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
CompressOverlap String
"compress"
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
VpscOverlap String
"vpsc"
, Overlap -> String -> Parse Overlap
forall a. a -> String -> Parse a
stringRep Overlap
IpsepOverlap String
"ipsep"
]
newtype LayerSep = LSep Text
deriving (LayerSep -> LayerSep -> Bool
(LayerSep -> LayerSep -> Bool)
-> (LayerSep -> LayerSep -> Bool) -> Eq LayerSep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LayerSep -> LayerSep -> Bool
== :: LayerSep -> LayerSep -> Bool
$c/= :: LayerSep -> LayerSep -> Bool
/= :: LayerSep -> LayerSep -> Bool
Eq, Eq LayerSep
Eq LayerSep =>
(LayerSep -> LayerSep -> Ordering)
-> (LayerSep -> LayerSep -> Bool)
-> (LayerSep -> LayerSep -> Bool)
-> (LayerSep -> LayerSep -> Bool)
-> (LayerSep -> LayerSep -> Bool)
-> (LayerSep -> LayerSep -> LayerSep)
-> (LayerSep -> LayerSep -> LayerSep)
-> Ord LayerSep
LayerSep -> LayerSep -> Bool
LayerSep -> LayerSep -> Ordering
LayerSep -> LayerSep -> LayerSep
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
$ccompare :: LayerSep -> LayerSep -> Ordering
compare :: LayerSep -> LayerSep -> Ordering
$c< :: LayerSep -> LayerSep -> Bool
< :: LayerSep -> LayerSep -> Bool
$c<= :: LayerSep -> LayerSep -> Bool
<= :: LayerSep -> LayerSep -> Bool
$c> :: LayerSep -> LayerSep -> Bool
> :: LayerSep -> LayerSep -> Bool
$c>= :: LayerSep -> LayerSep -> Bool
>= :: LayerSep -> LayerSep -> Bool
$cmax :: LayerSep -> LayerSep -> LayerSep
max :: LayerSep -> LayerSep -> LayerSep
$cmin :: LayerSep -> LayerSep -> LayerSep
min :: LayerSep -> LayerSep -> LayerSep
Ord, Int -> LayerSep -> ShowS
[LayerSep] -> ShowS
LayerSep -> String
(Int -> LayerSep -> ShowS)
-> (LayerSep -> String) -> ([LayerSep] -> ShowS) -> Show LayerSep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LayerSep -> ShowS
showsPrec :: Int -> LayerSep -> ShowS
$cshow :: LayerSep -> String
show :: LayerSep -> String
$cshowList :: [LayerSep] -> ShowS
showList :: [LayerSep] -> ShowS
Show, ReadPrec [LayerSep]
ReadPrec LayerSep
Int -> ReadS LayerSep
ReadS [LayerSep]
(Int -> ReadS LayerSep)
-> ReadS [LayerSep]
-> ReadPrec LayerSep
-> ReadPrec [LayerSep]
-> Read LayerSep
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LayerSep
readsPrec :: Int -> ReadS LayerSep
$creadList :: ReadS [LayerSep]
readList :: ReadS [LayerSep]
$creadPrec :: ReadPrec LayerSep
readPrec :: ReadPrec LayerSep
$creadListPrec :: ReadPrec [LayerSep]
readListPrec :: ReadPrec [LayerSep]
Read)
instance PrintDot LayerSep where
unqtDot :: LayerSep -> DotCode
unqtDot (LSep Text
ls) = String -> DotCodeM ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerSep (Text -> String
T.unpack Text
ls) DotCodeM () -> DotCode -> DotCode
forall a b. DotCodeM a -> DotCodeM b -> DotCodeM b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
ls
toDot :: LayerSep -> DotCode
toDot (LSep Text
ls) = String -> DotCodeM ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerSep (Text -> String
T.unpack Text
ls) DotCodeM () -> DotCode -> DotCode
forall a b. DotCodeM a -> DotCodeM b -> DotCodeM b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
ls
instance ParseDot LayerSep where
parseUnqt :: Parse LayerSep
parseUnqt = do Text
ls <- Parser GraphvizState Text
forall a. ParseDot a => Parse a
parseUnqt
String -> Parser GraphvizState ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerSep (String -> Parser GraphvizState ())
-> String -> Parser GraphvizState ()
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
ls
LayerSep -> Parse LayerSep
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (LayerSep -> Parse LayerSep) -> LayerSep -> Parse LayerSep
forall a b. (a -> b) -> a -> b
$ Text -> LayerSep
LSep Text
ls
parse :: Parse LayerSep
parse = do Text
ls <- Parser GraphvizState Text
forall a. ParseDot a => Parse a
parse
String -> Parser GraphvizState ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerSep (String -> Parser GraphvizState ())
-> String -> Parser GraphvizState ()
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
ls
LayerSep -> Parse LayerSep
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (LayerSep -> Parse LayerSep) -> LayerSep -> Parse LayerSep
forall a b. (a -> b) -> a -> b
$ Text -> LayerSep
LSep Text
ls
newtype LayerListSep = LLSep Text
deriving (LayerListSep -> LayerListSep -> Bool
(LayerListSep -> LayerListSep -> Bool)
-> (LayerListSep -> LayerListSep -> Bool) -> Eq LayerListSep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LayerListSep -> LayerListSep -> Bool
== :: LayerListSep -> LayerListSep -> Bool
$c/= :: LayerListSep -> LayerListSep -> Bool
/= :: LayerListSep -> LayerListSep -> Bool
Eq, Eq LayerListSep
Eq LayerListSep =>
(LayerListSep -> LayerListSep -> Ordering)
-> (LayerListSep -> LayerListSep -> Bool)
-> (LayerListSep -> LayerListSep -> Bool)
-> (LayerListSep -> LayerListSep -> Bool)
-> (LayerListSep -> LayerListSep -> Bool)
-> (LayerListSep -> LayerListSep -> LayerListSep)
-> (LayerListSep -> LayerListSep -> LayerListSep)
-> Ord LayerListSep
LayerListSep -> LayerListSep -> Bool
LayerListSep -> LayerListSep -> Ordering
LayerListSep -> LayerListSep -> LayerListSep
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
$ccompare :: LayerListSep -> LayerListSep -> Ordering
compare :: LayerListSep -> LayerListSep -> Ordering
$c< :: LayerListSep -> LayerListSep -> Bool
< :: LayerListSep -> LayerListSep -> Bool
$c<= :: LayerListSep -> LayerListSep -> Bool
<= :: LayerListSep -> LayerListSep -> Bool
$c> :: LayerListSep -> LayerListSep -> Bool
> :: LayerListSep -> LayerListSep -> Bool
$c>= :: LayerListSep -> LayerListSep -> Bool
>= :: LayerListSep -> LayerListSep -> Bool
$cmax :: LayerListSep -> LayerListSep -> LayerListSep
max :: LayerListSep -> LayerListSep -> LayerListSep
$cmin :: LayerListSep -> LayerListSep -> LayerListSep
min :: LayerListSep -> LayerListSep -> LayerListSep
Ord, Int -> LayerListSep -> ShowS
[LayerListSep] -> ShowS
LayerListSep -> String
(Int -> LayerListSep -> ShowS)
-> (LayerListSep -> String)
-> ([LayerListSep] -> ShowS)
-> Show LayerListSep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LayerListSep -> ShowS
showsPrec :: Int -> LayerListSep -> ShowS
$cshow :: LayerListSep -> String
show :: LayerListSep -> String
$cshowList :: [LayerListSep] -> ShowS
showList :: [LayerListSep] -> ShowS
Show, ReadPrec [LayerListSep]
ReadPrec LayerListSep
Int -> ReadS LayerListSep
ReadS [LayerListSep]
(Int -> ReadS LayerListSep)
-> ReadS [LayerListSep]
-> ReadPrec LayerListSep
-> ReadPrec [LayerListSep]
-> Read LayerListSep
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LayerListSep
readsPrec :: Int -> ReadS LayerListSep
$creadList :: ReadS [LayerListSep]
readList :: ReadS [LayerListSep]
$creadPrec :: ReadPrec LayerListSep
readPrec :: ReadPrec LayerListSep
$creadListPrec :: ReadPrec [LayerListSep]
readListPrec :: ReadPrec [LayerListSep]
Read)
instance PrintDot LayerListSep where
unqtDot :: LayerListSep -> DotCode
unqtDot (LLSep Text
ls) = String -> DotCodeM ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerListSep (Text -> String
T.unpack Text
ls) DotCodeM () -> DotCode -> DotCode
forall a b. DotCodeM a -> DotCodeM b -> DotCodeM b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
ls
toDot :: LayerListSep -> DotCode
toDot (LLSep Text
ls) = String -> DotCodeM ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerListSep (Text -> String
T.unpack Text
ls) DotCodeM () -> DotCode -> DotCode
forall a b. DotCodeM a -> DotCodeM b -> DotCodeM b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
ls
instance ParseDot LayerListSep where
parseUnqt :: Parse LayerListSep
parseUnqt = do Text
ls <- Parser GraphvizState Text
forall a. ParseDot a => Parse a
parseUnqt
String -> Parser GraphvizState ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerListSep (String -> Parser GraphvizState ())
-> String -> Parser GraphvizState ()
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
ls
LayerListSep -> Parse LayerListSep
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (LayerListSep -> Parse LayerListSep)
-> LayerListSep -> Parse LayerListSep
forall a b. (a -> b) -> a -> b
$ Text -> LayerListSep
LLSep Text
ls
parse :: Parse LayerListSep
parse = do Text
ls <- Parser GraphvizState Text
forall a. ParseDot a => Parse a
parse
String -> Parser GraphvizState ()
forall (m :: * -> *). GraphvizStateM m => String -> m ()
setLayerListSep (String -> Parser GraphvizState ())
-> String -> Parser GraphvizState ()
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
ls
LayerListSep -> Parse LayerListSep
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (LayerListSep -> Parse LayerListSep)
-> LayerListSep -> Parse LayerListSep
forall a b. (a -> b) -> a -> b
$ Text -> LayerListSep
LLSep Text
ls
type LayerRange = [LayerRangeElem]
data LayerRangeElem = LRID LayerID
| LRS LayerID LayerID
deriving (LayerRangeElem -> LayerRangeElem -> Bool
(LayerRangeElem -> LayerRangeElem -> Bool)
-> (LayerRangeElem -> LayerRangeElem -> Bool) -> Eq LayerRangeElem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LayerRangeElem -> LayerRangeElem -> Bool
== :: LayerRangeElem -> LayerRangeElem -> Bool
$c/= :: LayerRangeElem -> LayerRangeElem -> Bool
/= :: LayerRangeElem -> LayerRangeElem -> Bool
Eq, Eq LayerRangeElem
Eq LayerRangeElem =>
(LayerRangeElem -> LayerRangeElem -> Ordering)
-> (LayerRangeElem -> LayerRangeElem -> Bool)
-> (LayerRangeElem -> LayerRangeElem -> Bool)
-> (LayerRangeElem -> LayerRangeElem -> Bool)
-> (LayerRangeElem -> LayerRangeElem -> Bool)
-> (LayerRangeElem -> LayerRangeElem -> LayerRangeElem)
-> (LayerRangeElem -> LayerRangeElem -> LayerRangeElem)
-> Ord LayerRangeElem
LayerRangeElem -> LayerRangeElem -> Bool
LayerRangeElem -> LayerRangeElem -> Ordering
LayerRangeElem -> LayerRangeElem -> LayerRangeElem
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
$ccompare :: LayerRangeElem -> LayerRangeElem -> Ordering
compare :: LayerRangeElem -> LayerRangeElem -> Ordering
$c< :: LayerRangeElem -> LayerRangeElem -> Bool
< :: LayerRangeElem -> LayerRangeElem -> Bool
$c<= :: LayerRangeElem -> LayerRangeElem -> Bool
<= :: LayerRangeElem -> LayerRangeElem -> Bool
$c> :: LayerRangeElem -> LayerRangeElem -> Bool
> :: LayerRangeElem -> LayerRangeElem -> Bool
$c>= :: LayerRangeElem -> LayerRangeElem -> Bool
>= :: LayerRangeElem -> LayerRangeElem -> Bool
$cmax :: LayerRangeElem -> LayerRangeElem -> LayerRangeElem
max :: LayerRangeElem -> LayerRangeElem -> LayerRangeElem
$cmin :: LayerRangeElem -> LayerRangeElem -> LayerRangeElem
min :: LayerRangeElem -> LayerRangeElem -> LayerRangeElem
Ord, Int -> LayerRangeElem -> ShowS
[LayerRangeElem] -> ShowS
LayerRangeElem -> String
(Int -> LayerRangeElem -> ShowS)
-> (LayerRangeElem -> String)
-> ([LayerRangeElem] -> ShowS)
-> Show LayerRangeElem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LayerRangeElem -> ShowS
showsPrec :: Int -> LayerRangeElem -> ShowS
$cshow :: LayerRangeElem -> String
show :: LayerRangeElem -> String
$cshowList :: [LayerRangeElem] -> ShowS
showList :: [LayerRangeElem] -> ShowS
Show, ReadPrec [LayerRangeElem]
ReadPrec LayerRangeElem
Int -> ReadS LayerRangeElem
ReadS [LayerRangeElem]
(Int -> ReadS LayerRangeElem)
-> ReadS [LayerRangeElem]
-> ReadPrec LayerRangeElem
-> ReadPrec [LayerRangeElem]
-> Read LayerRangeElem
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LayerRangeElem
readsPrec :: Int -> ReadS LayerRangeElem
$creadList :: ReadS [LayerRangeElem]
readList :: ReadS [LayerRangeElem]
$creadPrec :: ReadPrec LayerRangeElem
readPrec :: ReadPrec LayerRangeElem
$creadListPrec :: ReadPrec [LayerRangeElem]
readListPrec :: ReadPrec [LayerRangeElem]
Read)
instance PrintDot LayerRangeElem where
unqtDot :: LayerRangeElem -> DotCode
unqtDot (LRID LayerID
lid) = LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot LayerID
lid
unqtDot (LRS LayerID
id1 LayerID
id2) = do String
ls <- DotCodeM String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerSep
let s :: DotCode
s = Char -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot (Char -> DotCode) -> Char -> DotCode
forall a b. (a -> b) -> a -> b
$ String -> Char
forall a. HasCallStack => [a] -> a
head String
ls
LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot LayerID
id1 DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode
s DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot LayerID
id2
toDot :: LayerRangeElem -> DotCode
toDot (LRID LayerID
lid) = LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
toDot LayerID
lid
toDot LayerRangeElem
lrs = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ LayerRangeElem -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot LayerRangeElem
lrs
unqtListToDot :: [LayerRangeElem] -> DotCode
unqtListToDot [LayerRangeElem]
lr = do String
lls <- DotCodeM String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerListSep
let s :: DotCode
s = Char -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot (Char -> DotCode) -> Char -> DotCode
forall a b. (a -> b) -> a -> b
$ String -> Char
forall a. HasCallStack => [a] -> a
head String
lls
DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> (DotCodeM [Doc] -> DotCodeM [Doc]) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate DotCode
s (DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall a b. (a -> b) -> a -> b
$ (LayerRangeElem -> DotCode) -> [LayerRangeElem] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM LayerRangeElem -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [LayerRangeElem]
lr
listToDot :: [LayerRangeElem] -> DotCode
listToDot [LayerRangeElem
lre] = LayerRangeElem -> DotCode
forall a. PrintDot a => a -> DotCode
toDot LayerRangeElem
lre
listToDot [LayerRangeElem]
lrs = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ [LayerRangeElem] -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot [LayerRangeElem]
lrs
instance ParseDot LayerRangeElem where
parseUnqt :: Parse LayerRangeElem
parseUnqt = (LayerID -> LayerID -> LayerRangeElem)
-> Parse LayerID
-> Parser GraphvizState ()
-> Parse LayerID
-> Parse LayerRangeElem
forall a b c sep.
(a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse c
ignoreSep LayerID -> LayerID -> LayerRangeElem
LRS Parse LayerID
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
parseLayerSep Parse LayerID
forall a. ParseDot a => Parse a
parseUnqt
Parse LayerRangeElem
-> Parse LayerRangeElem -> Parse LayerRangeElem
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(LayerID -> LayerRangeElem)
-> Parse LayerID -> Parse LayerRangeElem
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LayerID -> LayerRangeElem
LRID Parse LayerID
forall a. ParseDot a => Parse a
parseUnqt
parse :: Parse LayerRangeElem
parse = Parse LayerRangeElem -> Parse LayerRangeElem
forall a. Parse a -> Parse a
quotedParse ((LayerID -> LayerID -> LayerRangeElem)
-> Parse LayerID
-> Parser GraphvizState ()
-> Parse LayerID
-> Parse LayerRangeElem
forall a b c sep.
(a -> b -> c) -> Parse a -> Parse sep -> Parse b -> Parse c
ignoreSep LayerID -> LayerID -> LayerRangeElem
LRS Parse LayerID
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
parseLayerSep Parse LayerID
forall a. ParseDot a => Parse a
parseUnqt)
Parse LayerRangeElem
-> Parse LayerRangeElem -> Parse LayerRangeElem
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(LayerID -> LayerRangeElem)
-> Parse LayerID -> Parse LayerRangeElem
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap LayerID -> LayerRangeElem
LRID Parse LayerID
forall a. ParseDot a => Parse a
parse
parseUnqtList :: Parse [LayerRangeElem]
parseUnqtList = Parse LayerRangeElem
-> Parser GraphvizState () -> Parse [LayerRangeElem]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy Parse LayerRangeElem
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
parseLayerListSep
parseList :: Parse [LayerRangeElem]
parseList = Parse [LayerRangeElem] -> Parse [LayerRangeElem]
forall a. Parse a -> Parse a
quotedParse Parse [LayerRangeElem]
forall a. ParseDot a => Parse [a]
parseUnqtList
Parse [LayerRangeElem]
-> Parse [LayerRangeElem] -> Parse [LayerRangeElem]
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(LayerID -> [LayerRangeElem])
-> Parse LayerID -> Parse [LayerRangeElem]
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((LayerRangeElem -> [LayerRangeElem] -> [LayerRangeElem]
forall a. a -> [a] -> [a]
:[]) (LayerRangeElem -> [LayerRangeElem])
-> (LayerID -> LayerRangeElem) -> LayerID -> [LayerRangeElem]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LayerID -> LayerRangeElem
LRID) Parse LayerID
forall a. ParseDot a => Parse a
parse
parseLayerSep :: Parse ()
parseLayerSep :: Parser GraphvizState ()
parseLayerSep = do String
ls <- Parser GraphvizState String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerSep
(Char -> Bool) -> Parser GraphvizState Text
forall s. (Char -> Bool) -> Parser s Text
many1Satisfy (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
ls) Parser GraphvizState Text
-> Parser GraphvizState () -> Parser GraphvizState ()
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> () -> Parser GraphvizState ()
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
parseLayerName :: Parse Text
parseLayerName :: Parser GraphvizState Text
parseLayerName = Bool -> String -> String -> Parser GraphvizState Text
parseEscaped Bool
False [] (String -> Parser GraphvizState Text)
-> Parser GraphvizState String -> Parser GraphvizState Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (String -> ShowS)
-> Parser GraphvizState String
-> Parser GraphvizState String
-> Parser GraphvizState String
forall a b c.
(a -> b -> c)
-> Parser GraphvizState a
-> Parser GraphvizState b
-> Parser GraphvizState c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 String -> ShowS
forall a. [a] -> [a] -> [a]
(++) Parser GraphvizState String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerSep Parser GraphvizState String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerListSep
parseLayerName' :: Parse Text
parseLayerName' :: Parser GraphvizState Text
parseLayerName' = Parser GraphvizState Text
stringBlock
Parser GraphvizState Text
-> Parser GraphvizState Text -> Parser GraphvizState Text
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
Parser GraphvizState Text -> Parser GraphvizState Text
forall a. Parse a -> Parse a
quotedParse Parser GraphvizState Text
parseLayerName
parseLayerListSep :: Parse ()
parseLayerListSep :: Parser GraphvizState ()
parseLayerListSep = do String
lls <- Parser GraphvizState String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerListSep
(Char -> Bool) -> Parser GraphvizState Text
forall s. (Char -> Bool) -> Parser s Text
many1Satisfy (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
lls) Parser GraphvizState Text
-> Parser GraphvizState () -> Parser GraphvizState ()
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> () -> Parser GraphvizState ()
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
data LayerID = AllLayers
| LRInt Int
| LRName Text
deriving (LayerID -> LayerID -> Bool
(LayerID -> LayerID -> Bool)
-> (LayerID -> LayerID -> Bool) -> Eq LayerID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LayerID -> LayerID -> Bool
== :: LayerID -> LayerID -> Bool
$c/= :: LayerID -> LayerID -> Bool
/= :: LayerID -> LayerID -> Bool
Eq, Eq LayerID
Eq LayerID =>
(LayerID -> LayerID -> Ordering)
-> (LayerID -> LayerID -> Bool)
-> (LayerID -> LayerID -> Bool)
-> (LayerID -> LayerID -> Bool)
-> (LayerID -> LayerID -> Bool)
-> (LayerID -> LayerID -> LayerID)
-> (LayerID -> LayerID -> LayerID)
-> Ord LayerID
LayerID -> LayerID -> Bool
LayerID -> LayerID -> Ordering
LayerID -> LayerID -> LayerID
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
$ccompare :: LayerID -> LayerID -> Ordering
compare :: LayerID -> LayerID -> Ordering
$c< :: LayerID -> LayerID -> Bool
< :: LayerID -> LayerID -> Bool
$c<= :: LayerID -> LayerID -> Bool
<= :: LayerID -> LayerID -> Bool
$c> :: LayerID -> LayerID -> Bool
> :: LayerID -> LayerID -> Bool
$c>= :: LayerID -> LayerID -> Bool
>= :: LayerID -> LayerID -> Bool
$cmax :: LayerID -> LayerID -> LayerID
max :: LayerID -> LayerID -> LayerID
$cmin :: LayerID -> LayerID -> LayerID
min :: LayerID -> LayerID -> LayerID
Ord, Int -> LayerID -> ShowS
[LayerID] -> ShowS
LayerID -> String
(Int -> LayerID -> ShowS)
-> (LayerID -> String) -> ([LayerID] -> ShowS) -> Show LayerID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LayerID -> ShowS
showsPrec :: Int -> LayerID -> ShowS
$cshow :: LayerID -> String
show :: LayerID -> String
$cshowList :: [LayerID] -> ShowS
showList :: [LayerID] -> ShowS
Show, ReadPrec [LayerID]
ReadPrec LayerID
Int -> ReadS LayerID
ReadS [LayerID]
(Int -> ReadS LayerID)
-> ReadS [LayerID]
-> ReadPrec LayerID
-> ReadPrec [LayerID]
-> Read LayerID
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LayerID
readsPrec :: Int -> ReadS LayerID
$creadList :: ReadS [LayerID]
readList :: ReadS [LayerID]
$creadPrec :: ReadPrec LayerID
readPrec :: ReadPrec LayerID
$creadListPrec :: ReadPrec [LayerID]
readListPrec :: ReadPrec [LayerID]
Read)
instance PrintDot LayerID where
unqtDot :: LayerID -> DotCode
unqtDot LayerID
AllLayers = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"all"
unqtDot (LRInt Int
n) = Int -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Int
n
unqtDot (LRName Text
nm) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
nm
toDot :: LayerID -> DotCode
toDot (LRName Text
nm) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
nm
toDot LayerID
li = LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot LayerID
li
unqtListToDot :: [LayerID] -> DotCode
unqtListToDot [LayerID]
ll = do String
ls <- DotCodeM String
forall (m :: * -> *). GraphvizStateM m => m String
getLayerSep
let s :: DotCode
s = Char -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot (Char -> DotCode) -> Char -> DotCode
forall a b. (a -> b) -> a -> b
$ String -> Char
forall a. HasCallStack => [a] -> a
head String
ls
DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> (DotCodeM [Doc] -> DotCodeM [Doc]) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate DotCode
s (DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall a b. (a -> b) -> a -> b
$ (LayerID -> DotCode) -> [LayerID] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [LayerID]
ll
listToDot :: [LayerID] -> DotCode
listToDot [LayerID
l] = LayerID -> DotCode
forall a. PrintDot a => a -> DotCode
toDot LayerID
l
listToDot [LayerID]
ll = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ [LayerID] -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [LayerID]
ll
instance ParseDot LayerID where
parseUnqt :: Parse LayerID
parseUnqt = Text -> LayerID
checkLayerName (Text -> LayerID) -> Parser GraphvizState Text -> Parse LayerID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Text
parseLayerName
parse :: Parse LayerID
parse = [Parse LayerID] -> Parse LayerID
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Text -> LayerID
checkLayerName (Text -> LayerID) -> Parser GraphvizState Text -> Parse LayerID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Text
parseLayerName'
, Int -> LayerID
LRInt (Int -> LayerID) -> Parser GraphvizState Int -> Parse LayerID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Int
forall a. ParseDot a => Parse a
parse
]
checkLayerName :: Text -> LayerID
checkLayerName :: Text -> LayerID
checkLayerName Text
str = LayerID -> (Int -> LayerID) -> Maybe Int -> LayerID
forall b a. b -> (a -> b) -> Maybe a -> b
maybe LayerID
checkAll Int -> LayerID
LRInt (Maybe Int -> LayerID) -> Maybe Int -> LayerID
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Int
stringToInt Text
str
where
checkAll :: LayerID
checkAll = if Text -> Text
T.toLower Text
str Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"all"
then LayerID
AllLayers
else Text -> LayerID
LRName Text
str
newtype LayerList = LL [LayerID]
deriving (LayerList -> LayerList -> Bool
(LayerList -> LayerList -> Bool)
-> (LayerList -> LayerList -> Bool) -> Eq LayerList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LayerList -> LayerList -> Bool
== :: LayerList -> LayerList -> Bool
$c/= :: LayerList -> LayerList -> Bool
/= :: LayerList -> LayerList -> Bool
Eq, Eq LayerList
Eq LayerList =>
(LayerList -> LayerList -> Ordering)
-> (LayerList -> LayerList -> Bool)
-> (LayerList -> LayerList -> Bool)
-> (LayerList -> LayerList -> Bool)
-> (LayerList -> LayerList -> Bool)
-> (LayerList -> LayerList -> LayerList)
-> (LayerList -> LayerList -> LayerList)
-> Ord LayerList
LayerList -> LayerList -> Bool
LayerList -> LayerList -> Ordering
LayerList -> LayerList -> LayerList
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
$ccompare :: LayerList -> LayerList -> Ordering
compare :: LayerList -> LayerList -> Ordering
$c< :: LayerList -> LayerList -> Bool
< :: LayerList -> LayerList -> Bool
$c<= :: LayerList -> LayerList -> Bool
<= :: LayerList -> LayerList -> Bool
$c> :: LayerList -> LayerList -> Bool
> :: LayerList -> LayerList -> Bool
$c>= :: LayerList -> LayerList -> Bool
>= :: LayerList -> LayerList -> Bool
$cmax :: LayerList -> LayerList -> LayerList
max :: LayerList -> LayerList -> LayerList
$cmin :: LayerList -> LayerList -> LayerList
min :: LayerList -> LayerList -> LayerList
Ord, Int -> LayerList -> ShowS
[LayerList] -> ShowS
LayerList -> String
(Int -> LayerList -> ShowS)
-> (LayerList -> String)
-> ([LayerList] -> ShowS)
-> Show LayerList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LayerList -> ShowS
showsPrec :: Int -> LayerList -> ShowS
$cshow :: LayerList -> String
show :: LayerList -> String
$cshowList :: [LayerList] -> ShowS
showList :: [LayerList] -> ShowS
Show, ReadPrec [LayerList]
ReadPrec LayerList
Int -> ReadS LayerList
ReadS [LayerList]
(Int -> ReadS LayerList)
-> ReadS [LayerList]
-> ReadPrec LayerList
-> ReadPrec [LayerList]
-> Read LayerList
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LayerList
readsPrec :: Int -> ReadS LayerList
$creadList :: ReadS [LayerList]
readList :: ReadS [LayerList]
$creadPrec :: ReadPrec LayerList
readPrec :: ReadPrec LayerList
$creadListPrec :: ReadPrec [LayerList]
readListPrec :: ReadPrec [LayerList]
Read)
instance PrintDot LayerList where
unqtDot :: LayerList -> DotCode
unqtDot (LL [LayerID]
ll) = [LayerID] -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [LayerID]
ll
toDot :: LayerList -> DotCode
toDot (LL [LayerID]
ll) = [LayerID] -> DotCode
forall a. PrintDot a => a -> DotCode
toDot [LayerID]
ll
instance ParseDot LayerList where
parseUnqt :: Parse LayerList
parseUnqt = [LayerID] -> LayerList
LL ([LayerID] -> LayerList) -> Parse [LayerID] -> Parse LayerList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parse LayerID -> Parser GraphvizState () -> Parse [LayerID]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse LayerID
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
parseLayerSep
parse :: Parse LayerList
parse = Parse LayerList -> Parse LayerList
forall a. Parse a -> Parse a
quotedParse Parse LayerList
forall a. ParseDot a => Parse a
parseUnqt
Parse LayerList -> Parse LayerList -> Parse LayerList
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> LayerList) -> Parser GraphvizState Text -> Parse LayerList
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([LayerID] -> LayerList
LL ([LayerID] -> LayerList)
-> (Text -> [LayerID]) -> Text -> LayerList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LayerID -> [LayerID] -> [LayerID]
forall a. a -> [a] -> [a]
:[]) (LayerID -> [LayerID]) -> (Text -> LayerID) -> Text -> [LayerID]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LayerID
LRName) Parser GraphvizState Text
stringBlock
Parse LayerList -> Parse LayerList -> Parse LayerList
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
Parse LayerList -> Parse LayerList
forall a. Parse a -> Parse a
quotedParse (LayerList -> String -> Parse LayerList
forall a. a -> String -> Parse a
stringRep ([LayerID] -> LayerList
LL []) String
"")
data Order = OutEdges
| InEdges
deriving (Order -> Order -> Bool
(Order -> Order -> Bool) -> (Order -> Order -> Bool) -> Eq Order
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Order -> Order -> Bool
== :: Order -> Order -> Bool
$c/= :: Order -> Order -> Bool
/= :: Order -> Order -> Bool
Eq, Eq Order
Eq Order =>
(Order -> Order -> Ordering)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Order)
-> (Order -> Order -> Order)
-> Ord Order
Order -> Order -> Bool
Order -> Order -> Ordering
Order -> Order -> Order
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
$ccompare :: Order -> Order -> Ordering
compare :: Order -> Order -> Ordering
$c< :: Order -> Order -> Bool
< :: Order -> Order -> Bool
$c<= :: Order -> Order -> Bool
<= :: Order -> Order -> Bool
$c> :: Order -> Order -> Bool
> :: Order -> Order -> Bool
$c>= :: Order -> Order -> Bool
>= :: Order -> Order -> Bool
$cmax :: Order -> Order -> Order
max :: Order -> Order -> Order
$cmin :: Order -> Order -> Order
min :: Order -> Order -> Order
Ord, Order
Order -> Order -> Bounded Order
forall a. a -> a -> Bounded a
$cminBound :: Order
minBound :: Order
$cmaxBound :: Order
maxBound :: Order
Bounded, Int -> Order
Order -> Int
Order -> [Order]
Order -> Order
Order -> Order -> [Order]
Order -> Order -> Order -> [Order]
(Order -> Order)
-> (Order -> Order)
-> (Int -> Order)
-> (Order -> Int)
-> (Order -> [Order])
-> (Order -> Order -> [Order])
-> (Order -> Order -> [Order])
-> (Order -> Order -> Order -> [Order])
-> Enum Order
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Order -> Order
succ :: Order -> Order
$cpred :: Order -> Order
pred :: Order -> Order
$ctoEnum :: Int -> Order
toEnum :: Int -> Order
$cfromEnum :: Order -> Int
fromEnum :: Order -> Int
$cenumFrom :: Order -> [Order]
enumFrom :: Order -> [Order]
$cenumFromThen :: Order -> Order -> [Order]
enumFromThen :: Order -> Order -> [Order]
$cenumFromTo :: Order -> Order -> [Order]
enumFromTo :: Order -> Order -> [Order]
$cenumFromThenTo :: Order -> Order -> Order -> [Order]
enumFromThenTo :: Order -> Order -> Order -> [Order]
Enum, Int -> Order -> ShowS
[Order] -> ShowS
Order -> String
(Int -> Order -> ShowS)
-> (Order -> String) -> ([Order] -> ShowS) -> Show Order
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Order -> ShowS
showsPrec :: Int -> Order -> ShowS
$cshow :: Order -> String
show :: Order -> String
$cshowList :: [Order] -> ShowS
showList :: [Order] -> ShowS
Show, ReadPrec [Order]
ReadPrec Order
Int -> ReadS Order
ReadS [Order]
(Int -> ReadS Order)
-> ReadS [Order]
-> ReadPrec Order
-> ReadPrec [Order]
-> Read Order
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Order
readsPrec :: Int -> ReadS Order
$creadList :: ReadS [Order]
readList :: ReadS [Order]
$creadPrec :: ReadPrec Order
readPrec :: ReadPrec Order
$creadListPrec :: ReadPrec [Order]
readListPrec :: ReadPrec [Order]
Read)
instance PrintDot Order where
unqtDot :: Order -> DotCode
unqtDot Order
OutEdges = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"out"
unqtDot Order
InEdges = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"in"
instance ParseDot Order where
parseUnqt :: Parse Order
parseUnqt = [Parse Order] -> Parse Order
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Order -> String -> Parse Order
forall a. a -> String -> Parse a
stringRep Order
OutEdges String
"out"
, Order -> String -> Parse Order
forall a. a -> String -> Parse a
stringRep Order
InEdges String
"in"
]
data OutputMode = BreadthFirst | NodesFirst | EdgesFirst
deriving (OutputMode -> OutputMode -> Bool
(OutputMode -> OutputMode -> Bool)
-> (OutputMode -> OutputMode -> Bool) -> Eq OutputMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutputMode -> OutputMode -> Bool
== :: OutputMode -> OutputMode -> Bool
$c/= :: OutputMode -> OutputMode -> Bool
/= :: OutputMode -> OutputMode -> Bool
Eq, Eq OutputMode
Eq OutputMode =>
(OutputMode -> OutputMode -> Ordering)
-> (OutputMode -> OutputMode -> Bool)
-> (OutputMode -> OutputMode -> Bool)
-> (OutputMode -> OutputMode -> Bool)
-> (OutputMode -> OutputMode -> Bool)
-> (OutputMode -> OutputMode -> OutputMode)
-> (OutputMode -> OutputMode -> OutputMode)
-> Ord OutputMode
OutputMode -> OutputMode -> Bool
OutputMode -> OutputMode -> Ordering
OutputMode -> OutputMode -> OutputMode
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
$ccompare :: OutputMode -> OutputMode -> Ordering
compare :: OutputMode -> OutputMode -> Ordering
$c< :: OutputMode -> OutputMode -> Bool
< :: OutputMode -> OutputMode -> Bool
$c<= :: OutputMode -> OutputMode -> Bool
<= :: OutputMode -> OutputMode -> Bool
$c> :: OutputMode -> OutputMode -> Bool
> :: OutputMode -> OutputMode -> Bool
$c>= :: OutputMode -> OutputMode -> Bool
>= :: OutputMode -> OutputMode -> Bool
$cmax :: OutputMode -> OutputMode -> OutputMode
max :: OutputMode -> OutputMode -> OutputMode
$cmin :: OutputMode -> OutputMode -> OutputMode
min :: OutputMode -> OutputMode -> OutputMode
Ord, OutputMode
OutputMode -> OutputMode -> Bounded OutputMode
forall a. a -> a -> Bounded a
$cminBound :: OutputMode
minBound :: OutputMode
$cmaxBound :: OutputMode
maxBound :: OutputMode
Bounded, Int -> OutputMode
OutputMode -> Int
OutputMode -> [OutputMode]
OutputMode -> OutputMode
OutputMode -> OutputMode -> [OutputMode]
OutputMode -> OutputMode -> OutputMode -> [OutputMode]
(OutputMode -> OutputMode)
-> (OutputMode -> OutputMode)
-> (Int -> OutputMode)
-> (OutputMode -> Int)
-> (OutputMode -> [OutputMode])
-> (OutputMode -> OutputMode -> [OutputMode])
-> (OutputMode -> OutputMode -> [OutputMode])
-> (OutputMode -> OutputMode -> OutputMode -> [OutputMode])
-> Enum OutputMode
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: OutputMode -> OutputMode
succ :: OutputMode -> OutputMode
$cpred :: OutputMode -> OutputMode
pred :: OutputMode -> OutputMode
$ctoEnum :: Int -> OutputMode
toEnum :: Int -> OutputMode
$cfromEnum :: OutputMode -> Int
fromEnum :: OutputMode -> Int
$cenumFrom :: OutputMode -> [OutputMode]
enumFrom :: OutputMode -> [OutputMode]
$cenumFromThen :: OutputMode -> OutputMode -> [OutputMode]
enumFromThen :: OutputMode -> OutputMode -> [OutputMode]
$cenumFromTo :: OutputMode -> OutputMode -> [OutputMode]
enumFromTo :: OutputMode -> OutputMode -> [OutputMode]
$cenumFromThenTo :: OutputMode -> OutputMode -> OutputMode -> [OutputMode]
enumFromThenTo :: OutputMode -> OutputMode -> OutputMode -> [OutputMode]
Enum, Int -> OutputMode -> ShowS
[OutputMode] -> ShowS
OutputMode -> String
(Int -> OutputMode -> ShowS)
-> (OutputMode -> String)
-> ([OutputMode] -> ShowS)
-> Show OutputMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutputMode -> ShowS
showsPrec :: Int -> OutputMode -> ShowS
$cshow :: OutputMode -> String
show :: OutputMode -> String
$cshowList :: [OutputMode] -> ShowS
showList :: [OutputMode] -> ShowS
Show, ReadPrec [OutputMode]
ReadPrec OutputMode
Int -> ReadS OutputMode
ReadS [OutputMode]
(Int -> ReadS OutputMode)
-> ReadS [OutputMode]
-> ReadPrec OutputMode
-> ReadPrec [OutputMode]
-> Read OutputMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OutputMode
readsPrec :: Int -> ReadS OutputMode
$creadList :: ReadS [OutputMode]
readList :: ReadS [OutputMode]
$creadPrec :: ReadPrec OutputMode
readPrec :: ReadPrec OutputMode
$creadListPrec :: ReadPrec [OutputMode]
readListPrec :: ReadPrec [OutputMode]
Read)
instance PrintDot OutputMode where
unqtDot :: OutputMode -> DotCode
unqtDot OutputMode
BreadthFirst = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"breadthfirst"
unqtDot OutputMode
NodesFirst = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"nodesfirst"
unqtDot OutputMode
EdgesFirst = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"edgesfirst"
instance ParseDot OutputMode where
parseUnqt :: Parse OutputMode
parseUnqt = [Parse OutputMode] -> Parse OutputMode
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ OutputMode -> String -> Parse OutputMode
forall a. a -> String -> Parse a
stringRep OutputMode
BreadthFirst String
"breadthfirst"
, OutputMode -> String -> Parse OutputMode
forall a. a -> String -> Parse a
stringRep OutputMode
NodesFirst String
"nodesfirst"
, OutputMode -> String -> Parse OutputMode
forall a. a -> String -> Parse a
stringRep OutputMode
EdgesFirst String
"edgesfirst"
]
data Pack = DoPack
| DontPack
| PackMargin Int
deriving (Pack -> Pack -> Bool
(Pack -> Pack -> Bool) -> (Pack -> Pack -> Bool) -> Eq Pack
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pack -> Pack -> Bool
== :: Pack -> Pack -> Bool
$c/= :: Pack -> Pack -> Bool
/= :: Pack -> Pack -> Bool
Eq, Eq Pack
Eq Pack =>
(Pack -> Pack -> Ordering)
-> (Pack -> Pack -> Bool)
-> (Pack -> Pack -> Bool)
-> (Pack -> Pack -> Bool)
-> (Pack -> Pack -> Bool)
-> (Pack -> Pack -> Pack)
-> (Pack -> Pack -> Pack)
-> Ord Pack
Pack -> Pack -> Bool
Pack -> Pack -> Ordering
Pack -> Pack -> Pack
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
$ccompare :: Pack -> Pack -> Ordering
compare :: Pack -> Pack -> Ordering
$c< :: Pack -> Pack -> Bool
< :: Pack -> Pack -> Bool
$c<= :: Pack -> Pack -> Bool
<= :: Pack -> Pack -> Bool
$c> :: Pack -> Pack -> Bool
> :: Pack -> Pack -> Bool
$c>= :: Pack -> Pack -> Bool
>= :: Pack -> Pack -> Bool
$cmax :: Pack -> Pack -> Pack
max :: Pack -> Pack -> Pack
$cmin :: Pack -> Pack -> Pack
min :: Pack -> Pack -> Pack
Ord, Int -> Pack -> ShowS
[Pack] -> ShowS
Pack -> String
(Int -> Pack -> ShowS)
-> (Pack -> String) -> ([Pack] -> ShowS) -> Show Pack
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pack -> ShowS
showsPrec :: Int -> Pack -> ShowS
$cshow :: Pack -> String
show :: Pack -> String
$cshowList :: [Pack] -> ShowS
showList :: [Pack] -> ShowS
Show, ReadPrec [Pack]
ReadPrec Pack
Int -> ReadS Pack
ReadS [Pack]
(Int -> ReadS Pack)
-> ReadS [Pack] -> ReadPrec Pack -> ReadPrec [Pack] -> Read Pack
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pack
readsPrec :: Int -> ReadS Pack
$creadList :: ReadS [Pack]
readList :: ReadS [Pack]
$creadPrec :: ReadPrec Pack
readPrec :: ReadPrec Pack
$creadListPrec :: ReadPrec [Pack]
readListPrec :: ReadPrec [Pack]
Read)
instance PrintDot Pack where
unqtDot :: Pack -> DotCode
unqtDot Pack
DoPack = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot Pack
DontPack = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
False
unqtDot (PackMargin Int
m) = Int -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Int
m
instance ParseDot Pack where
parseUnqt :: Parse Pack
parseUnqt = [Parse Pack] -> Parse Pack
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Int -> Pack
PackMargin (Int -> Pack) -> Parser GraphvizState Int -> Parse Pack
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Int
forall a. ParseDot a => Parse a
parseUnqt
, Pack -> Pack -> Bool -> Pack
forall a. a -> a -> Bool -> a
bool Pack
DontPack Pack
DoPack (Bool -> Pack) -> Parser GraphvizState Bool -> Parse Pack
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Bool
onlyBool
]
data PackMode = PackNode
| PackClust
| PackGraph
| PackArray Bool Bool (Maybe Int)
deriving (PackMode -> PackMode -> Bool
(PackMode -> PackMode -> Bool)
-> (PackMode -> PackMode -> Bool) -> Eq PackMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PackMode -> PackMode -> Bool
== :: PackMode -> PackMode -> Bool
$c/= :: PackMode -> PackMode -> Bool
/= :: PackMode -> PackMode -> Bool
Eq, Eq PackMode
Eq PackMode =>
(PackMode -> PackMode -> Ordering)
-> (PackMode -> PackMode -> Bool)
-> (PackMode -> PackMode -> Bool)
-> (PackMode -> PackMode -> Bool)
-> (PackMode -> PackMode -> Bool)
-> (PackMode -> PackMode -> PackMode)
-> (PackMode -> PackMode -> PackMode)
-> Ord PackMode
PackMode -> PackMode -> Bool
PackMode -> PackMode -> Ordering
PackMode -> PackMode -> PackMode
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
$ccompare :: PackMode -> PackMode -> Ordering
compare :: PackMode -> PackMode -> Ordering
$c< :: PackMode -> PackMode -> Bool
< :: PackMode -> PackMode -> Bool
$c<= :: PackMode -> PackMode -> Bool
<= :: PackMode -> PackMode -> Bool
$c> :: PackMode -> PackMode -> Bool
> :: PackMode -> PackMode -> Bool
$c>= :: PackMode -> PackMode -> Bool
>= :: PackMode -> PackMode -> Bool
$cmax :: PackMode -> PackMode -> PackMode
max :: PackMode -> PackMode -> PackMode
$cmin :: PackMode -> PackMode -> PackMode
min :: PackMode -> PackMode -> PackMode
Ord, Int -> PackMode -> ShowS
[PackMode] -> ShowS
PackMode -> String
(Int -> PackMode -> ShowS)
-> (PackMode -> String) -> ([PackMode] -> ShowS) -> Show PackMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PackMode -> ShowS
showsPrec :: Int -> PackMode -> ShowS
$cshow :: PackMode -> String
show :: PackMode -> String
$cshowList :: [PackMode] -> ShowS
showList :: [PackMode] -> ShowS
Show, ReadPrec [PackMode]
ReadPrec PackMode
Int -> ReadS PackMode
ReadS [PackMode]
(Int -> ReadS PackMode)
-> ReadS [PackMode]
-> ReadPrec PackMode
-> ReadPrec [PackMode]
-> Read PackMode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PackMode
readsPrec :: Int -> ReadS PackMode
$creadList :: ReadS [PackMode]
readList :: ReadS [PackMode]
$creadPrec :: ReadPrec PackMode
readPrec :: ReadPrec PackMode
$creadListPrec :: ReadPrec [PackMode]
readListPrec :: ReadPrec [PackMode]
Read)
instance PrintDot PackMode where
unqtDot :: PackMode -> DotCode
unqtDot PackMode
PackNode = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"node"
unqtDot PackMode
PackClust = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"clust"
unqtDot PackMode
PackGraph = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"graph"
unqtDot (PackArray Bool
c Bool
u Maybe Int
mi) = DotCode -> DotCode
addNum (DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCode
isU (DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCode
isC (DotCode -> DotCode) -> (DotCode -> DotCode) -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCode
isUnder
(DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"array"
where
addNum :: DotCode -> DotCode
addNum = (DotCode -> DotCode)
-> (Int -> DotCode -> DotCode) -> Maybe Int -> DotCode -> DotCode
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DotCode -> DotCode
forall a. a -> a
id ((DotCode -> DotCode -> DotCode) -> DotCode -> DotCode -> DotCode
forall a b c. (a -> b -> c) -> b -> a -> c
flip DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
(<>) (DotCode -> DotCode -> DotCode)
-> (Int -> DotCode) -> Int -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot) Maybe Int
mi
isUnder :: DotCode -> DotCode
isUnder = if Bool
c Bool -> Bool -> Bool
|| Bool
u
then (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'_')
else DotCode -> DotCode
forall a. a -> a
id
isC :: DotCode -> DotCode
isC = if Bool
c
then (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'c')
else DotCode -> DotCode
forall a. a -> a
id
isU :: DotCode -> DotCode
isU = if Bool
u
then (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'u')
else DotCode -> DotCode
forall a. a -> a
id
instance ParseDot PackMode where
parseUnqt :: Parse PackMode
parseUnqt = [Parse PackMode] -> Parse PackMode
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ PackMode -> String -> Parse PackMode
forall a. a -> String -> Parse a
stringRep PackMode
PackNode String
"node"
, PackMode -> String -> Parse PackMode
forall a. a -> String -> Parse a
stringRep PackMode
PackClust String
"clust"
, PackMode -> String -> Parse PackMode
forall a. a -> String -> Parse a
stringRep PackMode
PackGraph String
"graph"
, do String -> Parser GraphvizState ()
string String
"array"
Maybe String
mcu <- Parser GraphvizState String -> Parser GraphvizState (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState String
-> Parser GraphvizState (Maybe String))
-> Parser GraphvizState String
-> Parser GraphvizState (Maybe String)
forall a b. (a -> b) -> a -> b
$ Char -> Parser GraphvizState Char
character Char
'_' Parser GraphvizState Char
-> Parser GraphvizState String -> Parser GraphvizState String
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState Char -> Parser GraphvizState String
forall (p :: * -> *) a. PolyParse p => p a -> p [a]
many1 ((Char -> Bool) -> Parser GraphvizState Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
isCU)
let c :: Bool
c = Maybe String -> Char -> Bool
forall {t :: * -> *} {a}.
(Foldable t, Eq a) =>
Maybe (t a) -> a -> Bool
hasCharacter Maybe String
mcu Char
'c'
u :: Bool
u = Maybe String -> Char -> Bool
forall {t :: * -> *} {a}.
(Foldable t, Eq a) =>
Maybe (t a) -> a -> Bool
hasCharacter Maybe String
mcu Char
'u'
Maybe Int
mi <- Parser GraphvizState Int -> Parser GraphvizState (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser GraphvizState Int
forall a. ParseDot a => Parse a
parseUnqt
PackMode -> Parse PackMode
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (PackMode -> Parse PackMode) -> PackMode -> Parse PackMode
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Maybe Int -> PackMode
PackArray Bool
c Bool
u Maybe Int
mi
]
where
hasCharacter :: Maybe (t a) -> a -> Bool
hasCharacter Maybe (t a)
ms a
c = Bool -> (t a -> Bool) -> Maybe (t a) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (a -> t a -> Bool
forall a. Eq a => a -> t a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
c) Maybe (t a)
ms
isCU :: Char -> Bool
isCU = (Char -> String -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'c', Char
'u'])
data Pos = PointPos Point
| SplinePos [Spline]
deriving (Pos -> Pos -> Bool
(Pos -> Pos -> Bool) -> (Pos -> Pos -> Bool) -> Eq Pos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Pos -> Pos -> Bool
== :: Pos -> Pos -> Bool
$c/= :: Pos -> Pos -> Bool
/= :: Pos -> Pos -> Bool
Eq, Eq Pos
Eq Pos =>
(Pos -> Pos -> Ordering)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Bool)
-> (Pos -> Pos -> Pos)
-> (Pos -> Pos -> Pos)
-> Ord Pos
Pos -> Pos -> Bool
Pos -> Pos -> Ordering
Pos -> Pos -> Pos
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
$ccompare :: Pos -> Pos -> Ordering
compare :: Pos -> Pos -> Ordering
$c< :: Pos -> Pos -> Bool
< :: Pos -> Pos -> Bool
$c<= :: Pos -> Pos -> Bool
<= :: Pos -> Pos -> Bool
$c> :: Pos -> Pos -> Bool
> :: Pos -> Pos -> Bool
$c>= :: Pos -> Pos -> Bool
>= :: Pos -> Pos -> Bool
$cmax :: Pos -> Pos -> Pos
max :: Pos -> Pos -> Pos
$cmin :: Pos -> Pos -> Pos
min :: Pos -> Pos -> Pos
Ord, Int -> Pos -> ShowS
[Pos] -> ShowS
Pos -> String
(Int -> Pos -> ShowS)
-> (Pos -> String) -> ([Pos] -> ShowS) -> Show Pos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Pos -> ShowS
showsPrec :: Int -> Pos -> ShowS
$cshow :: Pos -> String
show :: Pos -> String
$cshowList :: [Pos] -> ShowS
showList :: [Pos] -> ShowS
Show, ReadPrec [Pos]
ReadPrec Pos
Int -> ReadS Pos
ReadS [Pos]
(Int -> ReadS Pos)
-> ReadS [Pos] -> ReadPrec Pos -> ReadPrec [Pos] -> Read Pos
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Pos
readsPrec :: Int -> ReadS Pos
$creadList :: ReadS [Pos]
readList :: ReadS [Pos]
$creadPrec :: ReadPrec Pos
readPrec :: ReadPrec Pos
$creadListPrec :: ReadPrec [Pos]
readListPrec :: ReadPrec [Pos]
Read)
instance PrintDot Pos where
unqtDot :: Pos -> DotCode
unqtDot (PointPos Point
p) = Point -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Point
p
unqtDot (SplinePos [Spline]
ss) = [Spline] -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [Spline]
ss
toDot :: Pos -> DotCode
toDot (PointPos Point
p) = Point -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Point
p
toDot (SplinePos [Spline]
ss) = [Spline] -> DotCode
forall a. PrintDot a => a -> DotCode
toDot [Spline]
ss
instance ParseDot Pos where
parseUnqt :: Parse Pos
parseUnqt = do [Spline]
splns <- Parse [Spline]
forall a. ParseDot a => Parse a
parseUnqt
case [Spline]
splns of
[Spline Maybe Point
Nothing Maybe Point
Nothing [Point
p]] -> Pos -> Parse Pos
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pos -> Parse Pos) -> Pos -> Parse Pos
forall a b. (a -> b) -> a -> b
$ Point -> Pos
PointPos Point
p
[Spline]
_ -> Pos -> Parse Pos
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pos -> Parse Pos) -> Pos -> Parse Pos
forall a b. (a -> b) -> a -> b
$ [Spline] -> Pos
SplinePos [Spline]
splns
parse :: Parse Pos
parse = Parse Pos -> Parse Pos
forall a. Parse a -> Parse a
quotedParse Parse Pos
forall a. ParseDot a => Parse a
parseUnqt
data EdgeType = SplineEdges
| LineEdges
| NoEdges
| PolyLine
| Ortho
| Curved
| CompoundEdge
deriving (EdgeType -> EdgeType -> Bool
(EdgeType -> EdgeType -> Bool)
-> (EdgeType -> EdgeType -> Bool) -> Eq EdgeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EdgeType -> EdgeType -> Bool
== :: EdgeType -> EdgeType -> Bool
$c/= :: EdgeType -> EdgeType -> Bool
/= :: EdgeType -> EdgeType -> Bool
Eq, Eq EdgeType
Eq EdgeType =>
(EdgeType -> EdgeType -> Ordering)
-> (EdgeType -> EdgeType -> Bool)
-> (EdgeType -> EdgeType -> Bool)
-> (EdgeType -> EdgeType -> Bool)
-> (EdgeType -> EdgeType -> Bool)
-> (EdgeType -> EdgeType -> EdgeType)
-> (EdgeType -> EdgeType -> EdgeType)
-> Ord EdgeType
EdgeType -> EdgeType -> Bool
EdgeType -> EdgeType -> Ordering
EdgeType -> EdgeType -> EdgeType
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
$ccompare :: EdgeType -> EdgeType -> Ordering
compare :: EdgeType -> EdgeType -> Ordering
$c< :: EdgeType -> EdgeType -> Bool
< :: EdgeType -> EdgeType -> Bool
$c<= :: EdgeType -> EdgeType -> Bool
<= :: EdgeType -> EdgeType -> Bool
$c> :: EdgeType -> EdgeType -> Bool
> :: EdgeType -> EdgeType -> Bool
$c>= :: EdgeType -> EdgeType -> Bool
>= :: EdgeType -> EdgeType -> Bool
$cmax :: EdgeType -> EdgeType -> EdgeType
max :: EdgeType -> EdgeType -> EdgeType
$cmin :: EdgeType -> EdgeType -> EdgeType
min :: EdgeType -> EdgeType -> EdgeType
Ord, EdgeType
EdgeType -> EdgeType -> Bounded EdgeType
forall a. a -> a -> Bounded a
$cminBound :: EdgeType
minBound :: EdgeType
$cmaxBound :: EdgeType
maxBound :: EdgeType
Bounded, Int -> EdgeType
EdgeType -> Int
EdgeType -> [EdgeType]
EdgeType -> EdgeType
EdgeType -> EdgeType -> [EdgeType]
EdgeType -> EdgeType -> EdgeType -> [EdgeType]
(EdgeType -> EdgeType)
-> (EdgeType -> EdgeType)
-> (Int -> EdgeType)
-> (EdgeType -> Int)
-> (EdgeType -> [EdgeType])
-> (EdgeType -> EdgeType -> [EdgeType])
-> (EdgeType -> EdgeType -> [EdgeType])
-> (EdgeType -> EdgeType -> EdgeType -> [EdgeType])
-> Enum EdgeType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: EdgeType -> EdgeType
succ :: EdgeType -> EdgeType
$cpred :: EdgeType -> EdgeType
pred :: EdgeType -> EdgeType
$ctoEnum :: Int -> EdgeType
toEnum :: Int -> EdgeType
$cfromEnum :: EdgeType -> Int
fromEnum :: EdgeType -> Int
$cenumFrom :: EdgeType -> [EdgeType]
enumFrom :: EdgeType -> [EdgeType]
$cenumFromThen :: EdgeType -> EdgeType -> [EdgeType]
enumFromThen :: EdgeType -> EdgeType -> [EdgeType]
$cenumFromTo :: EdgeType -> EdgeType -> [EdgeType]
enumFromTo :: EdgeType -> EdgeType -> [EdgeType]
$cenumFromThenTo :: EdgeType -> EdgeType -> EdgeType -> [EdgeType]
enumFromThenTo :: EdgeType -> EdgeType -> EdgeType -> [EdgeType]
Enum, Int -> EdgeType -> ShowS
[EdgeType] -> ShowS
EdgeType -> String
(Int -> EdgeType -> ShowS)
-> (EdgeType -> String) -> ([EdgeType] -> ShowS) -> Show EdgeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EdgeType -> ShowS
showsPrec :: Int -> EdgeType -> ShowS
$cshow :: EdgeType -> String
show :: EdgeType -> String
$cshowList :: [EdgeType] -> ShowS
showList :: [EdgeType] -> ShowS
Show, ReadPrec [EdgeType]
ReadPrec EdgeType
Int -> ReadS EdgeType
ReadS [EdgeType]
(Int -> ReadS EdgeType)
-> ReadS [EdgeType]
-> ReadPrec EdgeType
-> ReadPrec [EdgeType]
-> Read EdgeType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EdgeType
readsPrec :: Int -> ReadS EdgeType
$creadList :: ReadS [EdgeType]
readList :: ReadS [EdgeType]
$creadPrec :: ReadPrec EdgeType
readPrec :: ReadPrec EdgeType
$creadListPrec :: ReadPrec [EdgeType]
readListPrec :: ReadPrec [EdgeType]
Read)
instance PrintDot EdgeType where
unqtDot :: EdgeType -> DotCode
unqtDot EdgeType
SplineEdges = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"spline"
unqtDot EdgeType
LineEdges = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"line"
unqtDot EdgeType
NoEdges = DotCode
forall (m :: * -> *). Applicative m => m Doc
empty
unqtDot EdgeType
PolyLine = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"polyline"
unqtDot EdgeType
Ortho = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"ortho"
unqtDot EdgeType
Curved = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"curved"
unqtDot EdgeType
CompoundEdge = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"compound"
toDot :: EdgeType -> DotCode
toDot EdgeType
NoEdges = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes DotCode
forall (m :: * -> *). Applicative m => m Doc
empty
toDot EdgeType
et = EdgeType -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot EdgeType
et
instance ParseDot EdgeType where
parseUnqt :: Parse EdgeType
parseUnqt = [Parse EdgeType] -> Parse EdgeType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ EdgeType -> EdgeType -> Bool -> EdgeType
forall a. a -> a -> Bool -> a
bool EdgeType
LineEdges EdgeType
SplineEdges (Bool -> EdgeType) -> Parser GraphvizState Bool -> Parse EdgeType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Bool
forall a. ParseDot a => Parse a
parse
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
SplineEdges String
"spline"
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
LineEdges String
"line"
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
NoEdges String
"none"
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
PolyLine String
"polyline"
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
Ortho String
"ortho"
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
Curved String
"curved"
, EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
CompoundEdge String
"compound"
]
parse :: Parse EdgeType
parse = EdgeType -> String -> Parse EdgeType
forall a. a -> String -> Parse a
stringRep EdgeType
NoEdges String
"\"\""
Parse EdgeType -> Parse EdgeType -> Parse EdgeType
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
Parse EdgeType -> Parse EdgeType
forall a. Parse a -> Parse a
optionalQuoted Parse EdgeType
forall a. ParseDot a => Parse a
parseUnqt
data PageDir = Bl | Br | Tl | Tr | Rb | Rt | Lb | Lt
deriving (PageDir -> PageDir -> Bool
(PageDir -> PageDir -> Bool)
-> (PageDir -> PageDir -> Bool) -> Eq PageDir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PageDir -> PageDir -> Bool
== :: PageDir -> PageDir -> Bool
$c/= :: PageDir -> PageDir -> Bool
/= :: PageDir -> PageDir -> Bool
Eq, Eq PageDir
Eq PageDir =>
(PageDir -> PageDir -> Ordering)
-> (PageDir -> PageDir -> Bool)
-> (PageDir -> PageDir -> Bool)
-> (PageDir -> PageDir -> Bool)
-> (PageDir -> PageDir -> Bool)
-> (PageDir -> PageDir -> PageDir)
-> (PageDir -> PageDir -> PageDir)
-> Ord PageDir
PageDir -> PageDir -> Bool
PageDir -> PageDir -> Ordering
PageDir -> PageDir -> PageDir
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
$ccompare :: PageDir -> PageDir -> Ordering
compare :: PageDir -> PageDir -> Ordering
$c< :: PageDir -> PageDir -> Bool
< :: PageDir -> PageDir -> Bool
$c<= :: PageDir -> PageDir -> Bool
<= :: PageDir -> PageDir -> Bool
$c> :: PageDir -> PageDir -> Bool
> :: PageDir -> PageDir -> Bool
$c>= :: PageDir -> PageDir -> Bool
>= :: PageDir -> PageDir -> Bool
$cmax :: PageDir -> PageDir -> PageDir
max :: PageDir -> PageDir -> PageDir
$cmin :: PageDir -> PageDir -> PageDir
min :: PageDir -> PageDir -> PageDir
Ord, PageDir
PageDir -> PageDir -> Bounded PageDir
forall a. a -> a -> Bounded a
$cminBound :: PageDir
minBound :: PageDir
$cmaxBound :: PageDir
maxBound :: PageDir
Bounded, Int -> PageDir
PageDir -> Int
PageDir -> [PageDir]
PageDir -> PageDir
PageDir -> PageDir -> [PageDir]
PageDir -> PageDir -> PageDir -> [PageDir]
(PageDir -> PageDir)
-> (PageDir -> PageDir)
-> (Int -> PageDir)
-> (PageDir -> Int)
-> (PageDir -> [PageDir])
-> (PageDir -> PageDir -> [PageDir])
-> (PageDir -> PageDir -> [PageDir])
-> (PageDir -> PageDir -> PageDir -> [PageDir])
-> Enum PageDir
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: PageDir -> PageDir
succ :: PageDir -> PageDir
$cpred :: PageDir -> PageDir
pred :: PageDir -> PageDir
$ctoEnum :: Int -> PageDir
toEnum :: Int -> PageDir
$cfromEnum :: PageDir -> Int
fromEnum :: PageDir -> Int
$cenumFrom :: PageDir -> [PageDir]
enumFrom :: PageDir -> [PageDir]
$cenumFromThen :: PageDir -> PageDir -> [PageDir]
enumFromThen :: PageDir -> PageDir -> [PageDir]
$cenumFromTo :: PageDir -> PageDir -> [PageDir]
enumFromTo :: PageDir -> PageDir -> [PageDir]
$cenumFromThenTo :: PageDir -> PageDir -> PageDir -> [PageDir]
enumFromThenTo :: PageDir -> PageDir -> PageDir -> [PageDir]
Enum, Int -> PageDir -> ShowS
[PageDir] -> ShowS
PageDir -> String
(Int -> PageDir -> ShowS)
-> (PageDir -> String) -> ([PageDir] -> ShowS) -> Show PageDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PageDir -> ShowS
showsPrec :: Int -> PageDir -> ShowS
$cshow :: PageDir -> String
show :: PageDir -> String
$cshowList :: [PageDir] -> ShowS
showList :: [PageDir] -> ShowS
Show, ReadPrec [PageDir]
ReadPrec PageDir
Int -> ReadS PageDir
ReadS [PageDir]
(Int -> ReadS PageDir)
-> ReadS [PageDir]
-> ReadPrec PageDir
-> ReadPrec [PageDir]
-> Read PageDir
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PageDir
readsPrec :: Int -> ReadS PageDir
$creadList :: ReadS [PageDir]
readList :: ReadS [PageDir]
$creadPrec :: ReadPrec PageDir
readPrec :: ReadPrec PageDir
$creadListPrec :: ReadPrec [PageDir]
readListPrec :: ReadPrec [PageDir]
Read)
instance PrintDot PageDir where
unqtDot :: PageDir -> DotCode
unqtDot PageDir
Bl = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"BL"
unqtDot PageDir
Br = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"BR"
unqtDot PageDir
Tl = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"TL"
unqtDot PageDir
Tr = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"TR"
unqtDot PageDir
Rb = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"RB"
unqtDot PageDir
Rt = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"RT"
unqtDot PageDir
Lb = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"LB"
unqtDot PageDir
Lt = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"LT"
instance ParseDot PageDir where
parseUnqt :: Parse PageDir
parseUnqt = [(String, PageDir)] -> Parse PageDir
forall a. [(String, a)] -> Parse a
stringValue [ (String
"BL", PageDir
Bl)
, (String
"BR", PageDir
Br)
, (String
"TL", PageDir
Tl)
, (String
"TR", PageDir
Tr)
, (String
"RB", PageDir
Rb)
, (String
"RT", PageDir
Rt)
, (String
"LB", PageDir
Lb)
, (String
"LT", PageDir
Lt)
]
data Spline = Spline { Spline -> Maybe Point
endPoint :: Maybe Point
, Spline -> Maybe Point
startPoint :: Maybe Point
, Spline -> [Point]
splinePoints :: [Point]
}
deriving (Spline -> Spline -> Bool
(Spline -> Spline -> Bool)
-> (Spline -> Spline -> Bool) -> Eq Spline
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Spline -> Spline -> Bool
== :: Spline -> Spline -> Bool
$c/= :: Spline -> Spline -> Bool
/= :: Spline -> Spline -> Bool
Eq, Eq Spline
Eq Spline =>
(Spline -> Spline -> Ordering)
-> (Spline -> Spline -> Bool)
-> (Spline -> Spline -> Bool)
-> (Spline -> Spline -> Bool)
-> (Spline -> Spline -> Bool)
-> (Spline -> Spline -> Spline)
-> (Spline -> Spline -> Spline)
-> Ord Spline
Spline -> Spline -> Bool
Spline -> Spline -> Ordering
Spline -> Spline -> Spline
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
$ccompare :: Spline -> Spline -> Ordering
compare :: Spline -> Spline -> Ordering
$c< :: Spline -> Spline -> Bool
< :: Spline -> Spline -> Bool
$c<= :: Spline -> Spline -> Bool
<= :: Spline -> Spline -> Bool
$c> :: Spline -> Spline -> Bool
> :: Spline -> Spline -> Bool
$c>= :: Spline -> Spline -> Bool
>= :: Spline -> Spline -> Bool
$cmax :: Spline -> Spline -> Spline
max :: Spline -> Spline -> Spline
$cmin :: Spline -> Spline -> Spline
min :: Spline -> Spline -> Spline
Ord, Int -> Spline -> ShowS
[Spline] -> ShowS
Spline -> String
(Int -> Spline -> ShowS)
-> (Spline -> String) -> ([Spline] -> ShowS) -> Show Spline
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Spline -> ShowS
showsPrec :: Int -> Spline -> ShowS
$cshow :: Spline -> String
show :: Spline -> String
$cshowList :: [Spline] -> ShowS
showList :: [Spline] -> ShowS
Show, ReadPrec [Spline]
ReadPrec Spline
Int -> ReadS Spline
ReadS [Spline]
(Int -> ReadS Spline)
-> ReadS [Spline]
-> ReadPrec Spline
-> ReadPrec [Spline]
-> Read Spline
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Spline
readsPrec :: Int -> ReadS Spline
$creadList :: ReadS [Spline]
readList :: ReadS [Spline]
$creadPrec :: ReadPrec Spline
readPrec :: ReadPrec Spline
$creadListPrec :: ReadPrec [Spline]
readListPrec :: ReadPrec [Spline]
Read)
instance PrintDot Spline where
unqtDot :: Spline -> DotCode
unqtDot (Spline Maybe Point
me Maybe Point
ms [Point]
ps) = DotCode -> DotCode
addE (DotCode -> DotCode)
-> (DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCode
addS
(DotCode -> DotCode)
-> (DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hsep
(DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall a b. (a -> b) -> a -> b
$ (Point -> DotCode) -> [Point] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Point -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [Point]
ps
where
addP :: a -> Maybe a -> DotCode -> DotCode
addP a
t = (DotCode -> DotCode)
-> (a -> DotCode -> DotCode) -> Maybe a -> DotCode -> DotCode
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DotCode -> DotCode
forall a. a -> a
id (DotCode -> DotCode -> DotCode
forall (m :: * -> *). Applicative m => m Doc -> m Doc -> m Doc
(<+>) (DotCode -> DotCode -> DotCode)
-> (a -> DotCode) -> a -> DotCode -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> DotCode
forall a b. (PrintDot a, PrintDot b) => a -> b -> DotCode
commaDel a
t)
addS :: DotCode -> DotCode
addS = Char -> Maybe Point -> DotCode -> DotCode
forall {a} {a}.
(PrintDot a, PrintDot a) =>
a -> Maybe a -> DotCode -> DotCode
addP Char
's' Maybe Point
ms
addE :: DotCode -> DotCode
addE = Char -> Maybe Point -> DotCode -> DotCode
forall {a} {a}.
(PrintDot a, PrintDot a) =>
a -> Maybe a -> DotCode -> DotCode
addP Char
'e' Maybe Point
me
toDot :: Spline -> DotCode
toDot = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> (Spline -> DotCode) -> Spline -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Spline -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
unqtListToDot :: [Spline] -> DotCode
unqtListToDot = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> ([Spline] -> DotCodeM [Doc]) -> [Spline] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate DotCode
forall (m :: * -> *). Applicative m => m Doc
semi (DotCodeM [Doc] -> DotCodeM [Doc])
-> ([Spline] -> DotCodeM [Doc]) -> [Spline] -> DotCodeM [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Spline -> DotCode) -> [Spline] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Spline -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
listToDot :: [Spline] -> DotCode
listToDot = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode)
-> ([Spline] -> DotCode) -> [Spline] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Spline] -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot
instance ParseDot Spline where
parseUnqt :: Parse Spline
parseUnqt = Maybe Point -> Maybe Point -> [Point] -> Spline
Spline (Maybe Point -> Maybe Point -> [Point] -> Spline)
-> Parser GraphvizState (Maybe Point)
-> Parser GraphvizState (Maybe Point -> [Point] -> Spline)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> Parser GraphvizState (Maybe Point)
forall {a}. ParseDot a => Char -> Parser GraphvizState (Maybe a)
parseP Char
'e' Parser GraphvizState (Maybe Point -> [Point] -> Spline)
-> Parser GraphvizState (Maybe Point)
-> Parser GraphvizState ([Point] -> Spline)
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Char -> Parser GraphvizState (Maybe Point)
forall {a}. ParseDot a => Char -> Parser GraphvizState (Maybe a)
parseP Char
's'
Parser GraphvizState ([Point] -> Spline)
-> Parse [Point] -> Parse Spline
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parse Point -> Parser GraphvizState () -> Parse [Point]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse Point
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState ()
whitespace1
where
parseP :: Char -> Parser GraphvizState (Maybe a)
parseP Char
t = Parser GraphvizState a -> Parser GraphvizState (Maybe a)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Char -> Parser GraphvizState Char
character Char
t Parser GraphvizState Char
-> Parser GraphvizState () -> Parser GraphvizState ()
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState ()
parseComma Parser GraphvizState ()
-> Parser GraphvizState a -> Parser GraphvizState a
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState a
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState a
-> Parser GraphvizState () -> Parser GraphvizState a
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser GraphvizState ()
whitespace1)
parse :: Parse Spline
parse = Parse Spline -> Parse Spline
forall a. Parse a -> Parse a
quotedParse Parse Spline
forall a. ParseDot a => Parse a
parseUnqt
parseUnqtList :: Parse [Spline]
parseUnqtList = Parse Spline -> Parser GraphvizState Char -> Parse [Spline]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse Spline
forall a. ParseDot a => Parse a
parseUnqt (Char -> Parser GraphvizState Char
character Char
';')
data QuadType = NormalQT
| FastQT
| NoQT
deriving (QuadType -> QuadType -> Bool
(QuadType -> QuadType -> Bool)
-> (QuadType -> QuadType -> Bool) -> Eq QuadType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuadType -> QuadType -> Bool
== :: QuadType -> QuadType -> Bool
$c/= :: QuadType -> QuadType -> Bool
/= :: QuadType -> QuadType -> Bool
Eq, Eq QuadType
Eq QuadType =>
(QuadType -> QuadType -> Ordering)
-> (QuadType -> QuadType -> Bool)
-> (QuadType -> QuadType -> Bool)
-> (QuadType -> QuadType -> Bool)
-> (QuadType -> QuadType -> Bool)
-> (QuadType -> QuadType -> QuadType)
-> (QuadType -> QuadType -> QuadType)
-> Ord QuadType
QuadType -> QuadType -> Bool
QuadType -> QuadType -> Ordering
QuadType -> QuadType -> QuadType
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
$ccompare :: QuadType -> QuadType -> Ordering
compare :: QuadType -> QuadType -> Ordering
$c< :: QuadType -> QuadType -> Bool
< :: QuadType -> QuadType -> Bool
$c<= :: QuadType -> QuadType -> Bool
<= :: QuadType -> QuadType -> Bool
$c> :: QuadType -> QuadType -> Bool
> :: QuadType -> QuadType -> Bool
$c>= :: QuadType -> QuadType -> Bool
>= :: QuadType -> QuadType -> Bool
$cmax :: QuadType -> QuadType -> QuadType
max :: QuadType -> QuadType -> QuadType
$cmin :: QuadType -> QuadType -> QuadType
min :: QuadType -> QuadType -> QuadType
Ord, QuadType
QuadType -> QuadType -> Bounded QuadType
forall a. a -> a -> Bounded a
$cminBound :: QuadType
minBound :: QuadType
$cmaxBound :: QuadType
maxBound :: QuadType
Bounded, Int -> QuadType
QuadType -> Int
QuadType -> [QuadType]
QuadType -> QuadType
QuadType -> QuadType -> [QuadType]
QuadType -> QuadType -> QuadType -> [QuadType]
(QuadType -> QuadType)
-> (QuadType -> QuadType)
-> (Int -> QuadType)
-> (QuadType -> Int)
-> (QuadType -> [QuadType])
-> (QuadType -> QuadType -> [QuadType])
-> (QuadType -> QuadType -> [QuadType])
-> (QuadType -> QuadType -> QuadType -> [QuadType])
-> Enum QuadType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: QuadType -> QuadType
succ :: QuadType -> QuadType
$cpred :: QuadType -> QuadType
pred :: QuadType -> QuadType
$ctoEnum :: Int -> QuadType
toEnum :: Int -> QuadType
$cfromEnum :: QuadType -> Int
fromEnum :: QuadType -> Int
$cenumFrom :: QuadType -> [QuadType]
enumFrom :: QuadType -> [QuadType]
$cenumFromThen :: QuadType -> QuadType -> [QuadType]
enumFromThen :: QuadType -> QuadType -> [QuadType]
$cenumFromTo :: QuadType -> QuadType -> [QuadType]
enumFromTo :: QuadType -> QuadType -> [QuadType]
$cenumFromThenTo :: QuadType -> QuadType -> QuadType -> [QuadType]
enumFromThenTo :: QuadType -> QuadType -> QuadType -> [QuadType]
Enum, Int -> QuadType -> ShowS
[QuadType] -> ShowS
QuadType -> String
(Int -> QuadType -> ShowS)
-> (QuadType -> String) -> ([QuadType] -> ShowS) -> Show QuadType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QuadType -> ShowS
showsPrec :: Int -> QuadType -> ShowS
$cshow :: QuadType -> String
show :: QuadType -> String
$cshowList :: [QuadType] -> ShowS
showList :: [QuadType] -> ShowS
Show, ReadPrec [QuadType]
ReadPrec QuadType
Int -> ReadS QuadType
ReadS [QuadType]
(Int -> ReadS QuadType)
-> ReadS [QuadType]
-> ReadPrec QuadType
-> ReadPrec [QuadType]
-> Read QuadType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS QuadType
readsPrec :: Int -> ReadS QuadType
$creadList :: ReadS [QuadType]
readList :: ReadS [QuadType]
$creadPrec :: ReadPrec QuadType
readPrec :: ReadPrec QuadType
$creadListPrec :: ReadPrec [QuadType]
readListPrec :: ReadPrec [QuadType]
Read)
instance PrintDot QuadType where
unqtDot :: QuadType -> DotCode
unqtDot QuadType
NormalQT = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"normal"
unqtDot QuadType
FastQT = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"fast"
unqtDot QuadType
NoQT = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"none"
instance ParseDot QuadType where
parseUnqt :: Parse QuadType
parseUnqt = [Parse QuadType] -> Parse QuadType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ QuadType -> String -> Parse QuadType
forall a. a -> String -> Parse a
stringRep QuadType
NormalQT String
"normal"
, QuadType -> String -> Parse QuadType
forall a. a -> String -> Parse a
stringRep QuadType
FastQT String
"fast"
, QuadType -> String -> Parse QuadType
forall a. a -> String -> Parse a
stringRep QuadType
NoQT String
"none"
, Char -> Parser GraphvizState Char
character Char
'2' Parser GraphvizState Char -> Parse QuadType -> Parse QuadType
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> QuadType -> Parse QuadType
forall a. a -> Parser GraphvizState a
forall (m :: * -> *) a. Monad m => a -> m a
return QuadType
FastQT
, QuadType -> QuadType -> Bool -> QuadType
forall a. a -> a -> Bool -> a
bool QuadType
NoQT QuadType
NormalQT (Bool -> QuadType) -> Parser GraphvizState Bool -> Parse QuadType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Bool
forall a. ParseDot a => Parse a
parse
]
data Root = IsCentral
| NotCentral
| NodeName Text
deriving (Root -> Root -> Bool
(Root -> Root -> Bool) -> (Root -> Root -> Bool) -> Eq Root
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Root -> Root -> Bool
== :: Root -> Root -> Bool
$c/= :: Root -> Root -> Bool
/= :: Root -> Root -> Bool
Eq, Eq Root
Eq Root =>
(Root -> Root -> Ordering)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Bool)
-> (Root -> Root -> Root)
-> (Root -> Root -> Root)
-> Ord Root
Root -> Root -> Bool
Root -> Root -> Ordering
Root -> Root -> Root
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
$ccompare :: Root -> Root -> Ordering
compare :: Root -> Root -> Ordering
$c< :: Root -> Root -> Bool
< :: Root -> Root -> Bool
$c<= :: Root -> Root -> Bool
<= :: Root -> Root -> Bool
$c> :: Root -> Root -> Bool
> :: Root -> Root -> Bool
$c>= :: Root -> Root -> Bool
>= :: Root -> Root -> Bool
$cmax :: Root -> Root -> Root
max :: Root -> Root -> Root
$cmin :: Root -> Root -> Root
min :: Root -> Root -> Root
Ord, Int -> Root -> ShowS
[Root] -> ShowS
Root -> String
(Int -> Root -> ShowS)
-> (Root -> String) -> ([Root] -> ShowS) -> Show Root
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Root -> ShowS
showsPrec :: Int -> Root -> ShowS
$cshow :: Root -> String
show :: Root -> String
$cshowList :: [Root] -> ShowS
showList :: [Root] -> ShowS
Show, ReadPrec [Root]
ReadPrec Root
Int -> ReadS Root
ReadS [Root]
(Int -> ReadS Root)
-> ReadS [Root] -> ReadPrec Root -> ReadPrec [Root] -> Read Root
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Root
readsPrec :: Int -> ReadS Root
$creadList :: ReadS [Root]
readList :: ReadS [Root]
$creadPrec :: ReadPrec Root
readPrec :: ReadPrec Root
$creadListPrec :: ReadPrec [Root]
readListPrec :: ReadPrec [Root]
Read)
instance PrintDot Root where
unqtDot :: Root -> DotCode
unqtDot Root
IsCentral = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot Root
NotCentral = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
False
unqtDot (NodeName Text
n) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
n
toDot :: Root -> DotCode
toDot (NodeName Text
n) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
n
toDot Root
r = Root -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Root
r
instance ParseDot Root where
parseUnqt :: Parse Root
parseUnqt = (Bool -> Root) -> Parser GraphvizState Bool -> Parse Root
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Root -> Root -> Bool -> Root
forall a. a -> a -> Bool -> a
bool Root
NotCentral Root
IsCentral) Parser GraphvizState Bool
onlyBool
Parse Root -> Parse Root -> Parse Root
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> Root) -> Parser GraphvizState Text -> Parse Root
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Root
NodeName Parser GraphvizState Text
forall a. ParseDot a => Parse a
parseUnqt
parse :: Parse Root
parse = Parse Root -> Parse Root
forall a. Parse a -> Parse a
optionalQuoted (Root -> Root -> Bool -> Root
forall a. a -> a -> Bool -> a
bool Root
NotCentral Root
IsCentral (Bool -> Root) -> Parser GraphvizState Bool -> Parse Root
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Bool
onlyBool)
Parse Root -> Parse Root -> Parse Root
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> Root) -> Parser GraphvizState Text -> Parse Root
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Root
NodeName Parser GraphvizState Text
forall a. ParseDot a => Parse a
parse
data RankType = SameRank
| MinRank
| SourceRank
| MaxRank
| SinkRank
deriving (RankType -> RankType -> Bool
(RankType -> RankType -> Bool)
-> (RankType -> RankType -> Bool) -> Eq RankType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RankType -> RankType -> Bool
== :: RankType -> RankType -> Bool
$c/= :: RankType -> RankType -> Bool
/= :: RankType -> RankType -> Bool
Eq, Eq RankType
Eq RankType =>
(RankType -> RankType -> Ordering)
-> (RankType -> RankType -> Bool)
-> (RankType -> RankType -> Bool)
-> (RankType -> RankType -> Bool)
-> (RankType -> RankType -> Bool)
-> (RankType -> RankType -> RankType)
-> (RankType -> RankType -> RankType)
-> Ord RankType
RankType -> RankType -> Bool
RankType -> RankType -> Ordering
RankType -> RankType -> RankType
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
$ccompare :: RankType -> RankType -> Ordering
compare :: RankType -> RankType -> Ordering
$c< :: RankType -> RankType -> Bool
< :: RankType -> RankType -> Bool
$c<= :: RankType -> RankType -> Bool
<= :: RankType -> RankType -> Bool
$c> :: RankType -> RankType -> Bool
> :: RankType -> RankType -> Bool
$c>= :: RankType -> RankType -> Bool
>= :: RankType -> RankType -> Bool
$cmax :: RankType -> RankType -> RankType
max :: RankType -> RankType -> RankType
$cmin :: RankType -> RankType -> RankType
min :: RankType -> RankType -> RankType
Ord, RankType
RankType -> RankType -> Bounded RankType
forall a. a -> a -> Bounded a
$cminBound :: RankType
minBound :: RankType
$cmaxBound :: RankType
maxBound :: RankType
Bounded, Int -> RankType
RankType -> Int
RankType -> [RankType]
RankType -> RankType
RankType -> RankType -> [RankType]
RankType -> RankType -> RankType -> [RankType]
(RankType -> RankType)
-> (RankType -> RankType)
-> (Int -> RankType)
-> (RankType -> Int)
-> (RankType -> [RankType])
-> (RankType -> RankType -> [RankType])
-> (RankType -> RankType -> [RankType])
-> (RankType -> RankType -> RankType -> [RankType])
-> Enum RankType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RankType -> RankType
succ :: RankType -> RankType
$cpred :: RankType -> RankType
pred :: RankType -> RankType
$ctoEnum :: Int -> RankType
toEnum :: Int -> RankType
$cfromEnum :: RankType -> Int
fromEnum :: RankType -> Int
$cenumFrom :: RankType -> [RankType]
enumFrom :: RankType -> [RankType]
$cenumFromThen :: RankType -> RankType -> [RankType]
enumFromThen :: RankType -> RankType -> [RankType]
$cenumFromTo :: RankType -> RankType -> [RankType]
enumFromTo :: RankType -> RankType -> [RankType]
$cenumFromThenTo :: RankType -> RankType -> RankType -> [RankType]
enumFromThenTo :: RankType -> RankType -> RankType -> [RankType]
Enum, Int -> RankType -> ShowS
[RankType] -> ShowS
RankType -> String
(Int -> RankType -> ShowS)
-> (RankType -> String) -> ([RankType] -> ShowS) -> Show RankType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RankType -> ShowS
showsPrec :: Int -> RankType -> ShowS
$cshow :: RankType -> String
show :: RankType -> String
$cshowList :: [RankType] -> ShowS
showList :: [RankType] -> ShowS
Show, ReadPrec [RankType]
ReadPrec RankType
Int -> ReadS RankType
ReadS [RankType]
(Int -> ReadS RankType)
-> ReadS [RankType]
-> ReadPrec RankType
-> ReadPrec [RankType]
-> Read RankType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RankType
readsPrec :: Int -> ReadS RankType
$creadList :: ReadS [RankType]
readList :: ReadS [RankType]
$creadPrec :: ReadPrec RankType
readPrec :: ReadPrec RankType
$creadListPrec :: ReadPrec [RankType]
readListPrec :: ReadPrec [RankType]
Read)
instance PrintDot RankType where
unqtDot :: RankType -> DotCode
unqtDot RankType
SameRank = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"same"
unqtDot RankType
MinRank = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"min"
unqtDot RankType
SourceRank = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"source"
unqtDot RankType
MaxRank = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"max"
unqtDot RankType
SinkRank = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"sink"
instance ParseDot RankType where
parseUnqt :: Parse RankType
parseUnqt = [(String, RankType)] -> Parse RankType
forall a. [(String, a)] -> Parse a
stringValue [ (String
"same", RankType
SameRank)
, (String
"min", RankType
MinRank)
, (String
"source", RankType
SourceRank)
, (String
"max", RankType
MaxRank)
, (String
"sink", RankType
SinkRank)
]
data RankDir = FromTop
| FromLeft
| FromBottom
| FromRight
deriving (RankDir -> RankDir -> Bool
(RankDir -> RankDir -> Bool)
-> (RankDir -> RankDir -> Bool) -> Eq RankDir
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RankDir -> RankDir -> Bool
== :: RankDir -> RankDir -> Bool
$c/= :: RankDir -> RankDir -> Bool
/= :: RankDir -> RankDir -> Bool
Eq, Eq RankDir
Eq RankDir =>
(RankDir -> RankDir -> Ordering)
-> (RankDir -> RankDir -> Bool)
-> (RankDir -> RankDir -> Bool)
-> (RankDir -> RankDir -> Bool)
-> (RankDir -> RankDir -> Bool)
-> (RankDir -> RankDir -> RankDir)
-> (RankDir -> RankDir -> RankDir)
-> Ord RankDir
RankDir -> RankDir -> Bool
RankDir -> RankDir -> Ordering
RankDir -> RankDir -> RankDir
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
$ccompare :: RankDir -> RankDir -> Ordering
compare :: RankDir -> RankDir -> Ordering
$c< :: RankDir -> RankDir -> Bool
< :: RankDir -> RankDir -> Bool
$c<= :: RankDir -> RankDir -> Bool
<= :: RankDir -> RankDir -> Bool
$c> :: RankDir -> RankDir -> Bool
> :: RankDir -> RankDir -> Bool
$c>= :: RankDir -> RankDir -> Bool
>= :: RankDir -> RankDir -> Bool
$cmax :: RankDir -> RankDir -> RankDir
max :: RankDir -> RankDir -> RankDir
$cmin :: RankDir -> RankDir -> RankDir
min :: RankDir -> RankDir -> RankDir
Ord, RankDir
RankDir -> RankDir -> Bounded RankDir
forall a. a -> a -> Bounded a
$cminBound :: RankDir
minBound :: RankDir
$cmaxBound :: RankDir
maxBound :: RankDir
Bounded, Int -> RankDir
RankDir -> Int
RankDir -> [RankDir]
RankDir -> RankDir
RankDir -> RankDir -> [RankDir]
RankDir -> RankDir -> RankDir -> [RankDir]
(RankDir -> RankDir)
-> (RankDir -> RankDir)
-> (Int -> RankDir)
-> (RankDir -> Int)
-> (RankDir -> [RankDir])
-> (RankDir -> RankDir -> [RankDir])
-> (RankDir -> RankDir -> [RankDir])
-> (RankDir -> RankDir -> RankDir -> [RankDir])
-> Enum RankDir
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RankDir -> RankDir
succ :: RankDir -> RankDir
$cpred :: RankDir -> RankDir
pred :: RankDir -> RankDir
$ctoEnum :: Int -> RankDir
toEnum :: Int -> RankDir
$cfromEnum :: RankDir -> Int
fromEnum :: RankDir -> Int
$cenumFrom :: RankDir -> [RankDir]
enumFrom :: RankDir -> [RankDir]
$cenumFromThen :: RankDir -> RankDir -> [RankDir]
enumFromThen :: RankDir -> RankDir -> [RankDir]
$cenumFromTo :: RankDir -> RankDir -> [RankDir]
enumFromTo :: RankDir -> RankDir -> [RankDir]
$cenumFromThenTo :: RankDir -> RankDir -> RankDir -> [RankDir]
enumFromThenTo :: RankDir -> RankDir -> RankDir -> [RankDir]
Enum, Int -> RankDir -> ShowS
[RankDir] -> ShowS
RankDir -> String
(Int -> RankDir -> ShowS)
-> (RankDir -> String) -> ([RankDir] -> ShowS) -> Show RankDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RankDir -> ShowS
showsPrec :: Int -> RankDir -> ShowS
$cshow :: RankDir -> String
show :: RankDir -> String
$cshowList :: [RankDir] -> ShowS
showList :: [RankDir] -> ShowS
Show, ReadPrec [RankDir]
ReadPrec RankDir
Int -> ReadS RankDir
ReadS [RankDir]
(Int -> ReadS RankDir)
-> ReadS [RankDir]
-> ReadPrec RankDir
-> ReadPrec [RankDir]
-> Read RankDir
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RankDir
readsPrec :: Int -> ReadS RankDir
$creadList :: ReadS [RankDir]
readList :: ReadS [RankDir]
$creadPrec :: ReadPrec RankDir
readPrec :: ReadPrec RankDir
$creadListPrec :: ReadPrec [RankDir]
readListPrec :: ReadPrec [RankDir]
Read)
instance PrintDot RankDir where
unqtDot :: RankDir -> DotCode
unqtDot RankDir
FromTop = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"TB"
unqtDot RankDir
FromLeft = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"LR"
unqtDot RankDir
FromBottom = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"BT"
unqtDot RankDir
FromRight = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"RL"
instance ParseDot RankDir where
parseUnqt :: Parse RankDir
parseUnqt = [Parse RankDir] -> Parse RankDir
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ RankDir -> String -> Parse RankDir
forall a. a -> String -> Parse a
stringRep RankDir
FromTop String
"TB"
, RankDir -> String -> Parse RankDir
forall a. a -> String -> Parse a
stringRep RankDir
FromLeft String
"LR"
, RankDir -> String -> Parse RankDir
forall a. a -> String -> Parse a
stringRep RankDir
FromBottom String
"BT"
, RankDir -> String -> Parse RankDir
forall a. a -> String -> Parse a
stringRep RankDir
FromRight String
"RL"
]
data Shape
= BoxShape
| Polygon
| Ellipse
| Circle
| PointShape
| Egg
| Triangle
| PlainText
| DiamondShape
| Trapezium
| Parallelogram
| House
| Pentagon
| Hexagon
| Septagon
| Octagon
| DoubleCircle
| DoubleOctagon
| TripleOctagon
| InvTriangle
| InvTrapezium
| InvHouse
| MDiamond
| MSquare
| MCircle
| Square
| Star
| Underline
| Note
| Tab
| Folder
| Box3D
| Component
| Promoter
| CDS
| Terminator
| UTR
| PrimerSite
| RestrictionSite
| FivePovOverhang
| ThreePovOverhang
| NoOverhang
| Assembly
| Signature
| Insulator
| Ribosite
| RNAStab
| ProteaseSite
| ProteinStab
| RPromoter
| RArrow
| LArrow
| LPromoter
| Record
| MRecord
deriving (Shape -> Shape -> Bool
(Shape -> Shape -> Bool) -> (Shape -> Shape -> Bool) -> Eq Shape
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Shape -> Shape -> Bool
== :: Shape -> Shape -> Bool
$c/= :: Shape -> Shape -> Bool
/= :: Shape -> Shape -> Bool
Eq, Eq Shape
Eq Shape =>
(Shape -> Shape -> Ordering)
-> (Shape -> Shape -> Bool)
-> (Shape -> Shape -> Bool)
-> (Shape -> Shape -> Bool)
-> (Shape -> Shape -> Bool)
-> (Shape -> Shape -> Shape)
-> (Shape -> Shape -> Shape)
-> Ord Shape
Shape -> Shape -> Bool
Shape -> Shape -> Ordering
Shape -> Shape -> Shape
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
$ccompare :: Shape -> Shape -> Ordering
compare :: Shape -> Shape -> Ordering
$c< :: Shape -> Shape -> Bool
< :: Shape -> Shape -> Bool
$c<= :: Shape -> Shape -> Bool
<= :: Shape -> Shape -> Bool
$c> :: Shape -> Shape -> Bool
> :: Shape -> Shape -> Bool
$c>= :: Shape -> Shape -> Bool
>= :: Shape -> Shape -> Bool
$cmax :: Shape -> Shape -> Shape
max :: Shape -> Shape -> Shape
$cmin :: Shape -> Shape -> Shape
min :: Shape -> Shape -> Shape
Ord, Shape
Shape -> Shape -> Bounded Shape
forall a. a -> a -> Bounded a
$cminBound :: Shape
minBound :: Shape
$cmaxBound :: Shape
maxBound :: Shape
Bounded, Int -> Shape
Shape -> Int
Shape -> [Shape]
Shape -> Shape
Shape -> Shape -> [Shape]
Shape -> Shape -> Shape -> [Shape]
(Shape -> Shape)
-> (Shape -> Shape)
-> (Int -> Shape)
-> (Shape -> Int)
-> (Shape -> [Shape])
-> (Shape -> Shape -> [Shape])
-> (Shape -> Shape -> [Shape])
-> (Shape -> Shape -> Shape -> [Shape])
-> Enum Shape
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Shape -> Shape
succ :: Shape -> Shape
$cpred :: Shape -> Shape
pred :: Shape -> Shape
$ctoEnum :: Int -> Shape
toEnum :: Int -> Shape
$cfromEnum :: Shape -> Int
fromEnum :: Shape -> Int
$cenumFrom :: Shape -> [Shape]
enumFrom :: Shape -> [Shape]
$cenumFromThen :: Shape -> Shape -> [Shape]
enumFromThen :: Shape -> Shape -> [Shape]
$cenumFromTo :: Shape -> Shape -> [Shape]
enumFromTo :: Shape -> Shape -> [Shape]
$cenumFromThenTo :: Shape -> Shape -> Shape -> [Shape]
enumFromThenTo :: Shape -> Shape -> Shape -> [Shape]
Enum, Int -> Shape -> ShowS
[Shape] -> ShowS
Shape -> String
(Int -> Shape -> ShowS)
-> (Shape -> String) -> ([Shape] -> ShowS) -> Show Shape
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Shape -> ShowS
showsPrec :: Int -> Shape -> ShowS
$cshow :: Shape -> String
show :: Shape -> String
$cshowList :: [Shape] -> ShowS
showList :: [Shape] -> ShowS
Show, ReadPrec [Shape]
ReadPrec Shape
Int -> ReadS Shape
ReadS [Shape]
(Int -> ReadS Shape)
-> ReadS [Shape]
-> ReadPrec Shape
-> ReadPrec [Shape]
-> Read Shape
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Shape
readsPrec :: Int -> ReadS Shape
$creadList :: ReadS [Shape]
readList :: ReadS [Shape]
$creadPrec :: ReadPrec Shape
readPrec :: ReadPrec Shape
$creadListPrec :: ReadPrec [Shape]
readListPrec :: ReadPrec [Shape]
Read)
instance PrintDot Shape where
unqtDot :: Shape -> DotCode
unqtDot Shape
BoxShape = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"box"
unqtDot Shape
Polygon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"polygon"
unqtDot Shape
Ellipse = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"ellipse"
unqtDot Shape
Circle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"circle"
unqtDot Shape
PointShape = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"point"
unqtDot Shape
Egg = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"egg"
unqtDot Shape
Triangle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"triangle"
unqtDot Shape
PlainText = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"plaintext"
unqtDot Shape
DiamondShape = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"diamond"
unqtDot Shape
Trapezium = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"trapezium"
unqtDot Shape
Parallelogram = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"parallelogram"
unqtDot Shape
House = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"house"
unqtDot Shape
Pentagon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"pentagon"
unqtDot Shape
Hexagon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"hexagon"
unqtDot Shape
Septagon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"septagon"
unqtDot Shape
Octagon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"octagon"
unqtDot Shape
DoubleCircle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"doublecircle"
unqtDot Shape
DoubleOctagon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"doubleoctagon"
unqtDot Shape
TripleOctagon = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"tripleoctagon"
unqtDot Shape
InvTriangle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"invtriangle"
unqtDot Shape
InvTrapezium = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"invtrapezium"
unqtDot Shape
InvHouse = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"invhouse"
unqtDot Shape
MDiamond = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"Mdiamond"
unqtDot Shape
MSquare = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"Msquare"
unqtDot Shape
MCircle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"Mcircle"
unqtDot Shape
Square = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"square"
unqtDot Shape
Star = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"star"
unqtDot Shape
Underline = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"underline"
unqtDot Shape
Note = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"note"
unqtDot Shape
Tab = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"tab"
unqtDot Shape
Folder = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"folder"
unqtDot Shape
Box3D = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"box3d"
unqtDot Shape
Component = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"component"
unqtDot Shape
Promoter = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"promoter"
unqtDot Shape
CDS = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"cds"
unqtDot Shape
Terminator = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"terminator"
unqtDot Shape
UTR = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"utr"
unqtDot Shape
PrimerSite = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"primersite"
unqtDot Shape
RestrictionSite = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"restrictionsite"
unqtDot Shape
FivePovOverhang = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"fivepovoverhang"
unqtDot Shape
ThreePovOverhang = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"threepovoverhang"
unqtDot Shape
NoOverhang = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"nooverhang"
unqtDot Shape
Assembly = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"assembly"
unqtDot Shape
Signature = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"signature"
unqtDot Shape
Insulator = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"insulator"
unqtDot Shape
Ribosite = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"ribosite"
unqtDot Shape
RNAStab = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"rnastab"
unqtDot Shape
ProteaseSite = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"proteasesite"
unqtDot Shape
ProteinStab = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"proteinstab"
unqtDot Shape
RPromoter = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"rpromoter"
unqtDot Shape
RArrow = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"rarrow"
unqtDot Shape
LArrow = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"larrow"
unqtDot Shape
LPromoter = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"lpromoter"
unqtDot Shape
Record = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"record"
unqtDot Shape
MRecord = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"Mrecord"
instance ParseDot Shape where
parseUnqt :: Parse Shape
parseUnqt = [(String, Shape)] -> Parse Shape
forall a. [(String, a)] -> Parse a
stringValue [ (String
"box3d", Shape
Box3D)
, (String
"box", Shape
BoxShape)
, (String
"rectangle", Shape
BoxShape)
, (String
"rect", Shape
BoxShape)
, (String
"polygon", Shape
Polygon)
, (String
"ellipse", Shape
Ellipse)
, (String
"oval", Shape
Ellipse)
, (String
"circle", Shape
Circle)
, (String
"point", Shape
PointShape)
, (String
"egg", Shape
Egg)
, (String
"triangle", Shape
Triangle)
, (String
"plaintext", Shape
PlainText)
, (String
"none", Shape
PlainText)
, (String
"diamond", Shape
DiamondShape)
, (String
"trapezium", Shape
Trapezium)
, (String
"parallelogram", Shape
Parallelogram)
, (String
"house", Shape
House)
, (String
"pentagon", Shape
Pentagon)
, (String
"hexagon", Shape
Hexagon)
, (String
"septagon", Shape
Septagon)
, (String
"octagon", Shape
Octagon)
, (String
"doublecircle", Shape
DoubleCircle)
, (String
"doubleoctagon", Shape
DoubleOctagon)
, (String
"tripleoctagon", Shape
TripleOctagon)
, (String
"invtriangle", Shape
InvTriangle)
, (String
"invtrapezium", Shape
InvTrapezium)
, (String
"invhouse", Shape
InvHouse)
, (String
"Mdiamond", Shape
MDiamond)
, (String
"Msquare", Shape
MSquare)
, (String
"Mcircle", Shape
MCircle)
, (String
"square", Shape
Square)
, (String
"star", Shape
Star)
, (String
"underline", Shape
Underline)
, (String
"note", Shape
Note)
, (String
"tab", Shape
Tab)
, (String
"folder", Shape
Folder)
, (String
"component", Shape
Component)
, (String
"promoter", Shape
Promoter)
, (String
"cds", Shape
CDS)
, (String
"terminator", Shape
Terminator)
, (String
"utr", Shape
UTR)
, (String
"primersite", Shape
PrimerSite)
, (String
"restrictionsite", Shape
RestrictionSite)
, (String
"fivepovoverhang", Shape
FivePovOverhang)
, (String
"threepovoverhang", Shape
ThreePovOverhang)
, (String
"nooverhang", Shape
NoOverhang)
, (String
"assembly", Shape
Assembly)
, (String
"signature", Shape
Signature)
, (String
"insulator", Shape
Insulator)
, (String
"ribosite", Shape
Ribosite)
, (String
"rnastab", Shape
RNAStab)
, (String
"proteasesite", Shape
ProteaseSite)
, (String
"proteinstab", Shape
ProteinStab)
, (String
"rpromoter", Shape
RPromoter)
, (String
"rarrow", Shape
RArrow)
, (String
"larrow", Shape
LArrow)
, (String
"lpromoter", Shape
LPromoter)
, (String
"record", Shape
Record)
, (String
"Mrecord", Shape
MRecord)
]
data SmoothType = NoSmooth
| AvgDist
| GraphDist
| PowerDist
| RNG
| Spring
| TriangleSmooth
deriving (SmoothType -> SmoothType -> Bool
(SmoothType -> SmoothType -> Bool)
-> (SmoothType -> SmoothType -> Bool) -> Eq SmoothType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SmoothType -> SmoothType -> Bool
== :: SmoothType -> SmoothType -> Bool
$c/= :: SmoothType -> SmoothType -> Bool
/= :: SmoothType -> SmoothType -> Bool
Eq, Eq SmoothType
Eq SmoothType =>
(SmoothType -> SmoothType -> Ordering)
-> (SmoothType -> SmoothType -> Bool)
-> (SmoothType -> SmoothType -> Bool)
-> (SmoothType -> SmoothType -> Bool)
-> (SmoothType -> SmoothType -> Bool)
-> (SmoothType -> SmoothType -> SmoothType)
-> (SmoothType -> SmoothType -> SmoothType)
-> Ord SmoothType
SmoothType -> SmoothType -> Bool
SmoothType -> SmoothType -> Ordering
SmoothType -> SmoothType -> SmoothType
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
$ccompare :: SmoothType -> SmoothType -> Ordering
compare :: SmoothType -> SmoothType -> Ordering
$c< :: SmoothType -> SmoothType -> Bool
< :: SmoothType -> SmoothType -> Bool
$c<= :: SmoothType -> SmoothType -> Bool
<= :: SmoothType -> SmoothType -> Bool
$c> :: SmoothType -> SmoothType -> Bool
> :: SmoothType -> SmoothType -> Bool
$c>= :: SmoothType -> SmoothType -> Bool
>= :: SmoothType -> SmoothType -> Bool
$cmax :: SmoothType -> SmoothType -> SmoothType
max :: SmoothType -> SmoothType -> SmoothType
$cmin :: SmoothType -> SmoothType -> SmoothType
min :: SmoothType -> SmoothType -> SmoothType
Ord, SmoothType
SmoothType -> SmoothType -> Bounded SmoothType
forall a. a -> a -> Bounded a
$cminBound :: SmoothType
minBound :: SmoothType
$cmaxBound :: SmoothType
maxBound :: SmoothType
Bounded, Int -> SmoothType
SmoothType -> Int
SmoothType -> [SmoothType]
SmoothType -> SmoothType
SmoothType -> SmoothType -> [SmoothType]
SmoothType -> SmoothType -> SmoothType -> [SmoothType]
(SmoothType -> SmoothType)
-> (SmoothType -> SmoothType)
-> (Int -> SmoothType)
-> (SmoothType -> Int)
-> (SmoothType -> [SmoothType])
-> (SmoothType -> SmoothType -> [SmoothType])
-> (SmoothType -> SmoothType -> [SmoothType])
-> (SmoothType -> SmoothType -> SmoothType -> [SmoothType])
-> Enum SmoothType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SmoothType -> SmoothType
succ :: SmoothType -> SmoothType
$cpred :: SmoothType -> SmoothType
pred :: SmoothType -> SmoothType
$ctoEnum :: Int -> SmoothType
toEnum :: Int -> SmoothType
$cfromEnum :: SmoothType -> Int
fromEnum :: SmoothType -> Int
$cenumFrom :: SmoothType -> [SmoothType]
enumFrom :: SmoothType -> [SmoothType]
$cenumFromThen :: SmoothType -> SmoothType -> [SmoothType]
enumFromThen :: SmoothType -> SmoothType -> [SmoothType]
$cenumFromTo :: SmoothType -> SmoothType -> [SmoothType]
enumFromTo :: SmoothType -> SmoothType -> [SmoothType]
$cenumFromThenTo :: SmoothType -> SmoothType -> SmoothType -> [SmoothType]
enumFromThenTo :: SmoothType -> SmoothType -> SmoothType -> [SmoothType]
Enum, Int -> SmoothType -> ShowS
[SmoothType] -> ShowS
SmoothType -> String
(Int -> SmoothType -> ShowS)
-> (SmoothType -> String)
-> ([SmoothType] -> ShowS)
-> Show SmoothType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SmoothType -> ShowS
showsPrec :: Int -> SmoothType -> ShowS
$cshow :: SmoothType -> String
show :: SmoothType -> String
$cshowList :: [SmoothType] -> ShowS
showList :: [SmoothType] -> ShowS
Show, ReadPrec [SmoothType]
ReadPrec SmoothType
Int -> ReadS SmoothType
ReadS [SmoothType]
(Int -> ReadS SmoothType)
-> ReadS [SmoothType]
-> ReadPrec SmoothType
-> ReadPrec [SmoothType]
-> Read SmoothType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SmoothType
readsPrec :: Int -> ReadS SmoothType
$creadList :: ReadS [SmoothType]
readList :: ReadS [SmoothType]
$creadPrec :: ReadPrec SmoothType
readPrec :: ReadPrec SmoothType
$creadListPrec :: ReadPrec [SmoothType]
readListPrec :: ReadPrec [SmoothType]
Read)
instance PrintDot SmoothType where
unqtDot :: SmoothType -> DotCode
unqtDot SmoothType
NoSmooth = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"none"
unqtDot SmoothType
AvgDist = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"avg_dist"
unqtDot SmoothType
GraphDist = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"graph_dist"
unqtDot SmoothType
PowerDist = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"power_dist"
unqtDot SmoothType
RNG = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"rng"
unqtDot SmoothType
Spring = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"spring"
unqtDot SmoothType
TriangleSmooth = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"triangle"
instance ParseDot SmoothType where
parseUnqt :: Parse SmoothType
parseUnqt = [Parse SmoothType] -> Parse SmoothType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
NoSmooth String
"none"
, SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
AvgDist String
"avg_dist"
, SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
GraphDist String
"graph_dist"
, SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
PowerDist String
"power_dist"
, SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
RNG String
"rng"
, SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
Spring String
"spring"
, SmoothType -> String -> Parse SmoothType
forall a. a -> String -> Parse a
stringRep SmoothType
TriangleSmooth String
"triangle"
]
data StartType = StartStyle STStyle
| StartSeed Int
| StartStyleSeed STStyle Int
deriving (StartType -> StartType -> Bool
(StartType -> StartType -> Bool)
-> (StartType -> StartType -> Bool) -> Eq StartType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StartType -> StartType -> Bool
== :: StartType -> StartType -> Bool
$c/= :: StartType -> StartType -> Bool
/= :: StartType -> StartType -> Bool
Eq, Eq StartType
Eq StartType =>
(StartType -> StartType -> Ordering)
-> (StartType -> StartType -> Bool)
-> (StartType -> StartType -> Bool)
-> (StartType -> StartType -> Bool)
-> (StartType -> StartType -> Bool)
-> (StartType -> StartType -> StartType)
-> (StartType -> StartType -> StartType)
-> Ord StartType
StartType -> StartType -> Bool
StartType -> StartType -> Ordering
StartType -> StartType -> StartType
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
$ccompare :: StartType -> StartType -> Ordering
compare :: StartType -> StartType -> Ordering
$c< :: StartType -> StartType -> Bool
< :: StartType -> StartType -> Bool
$c<= :: StartType -> StartType -> Bool
<= :: StartType -> StartType -> Bool
$c> :: StartType -> StartType -> Bool
> :: StartType -> StartType -> Bool
$c>= :: StartType -> StartType -> Bool
>= :: StartType -> StartType -> Bool
$cmax :: StartType -> StartType -> StartType
max :: StartType -> StartType -> StartType
$cmin :: StartType -> StartType -> StartType
min :: StartType -> StartType -> StartType
Ord, Int -> StartType -> ShowS
[StartType] -> ShowS
StartType -> String
(Int -> StartType -> ShowS)
-> (StartType -> String)
-> ([StartType] -> ShowS)
-> Show StartType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StartType -> ShowS
showsPrec :: Int -> StartType -> ShowS
$cshow :: StartType -> String
show :: StartType -> String
$cshowList :: [StartType] -> ShowS
showList :: [StartType] -> ShowS
Show, ReadPrec [StartType]
ReadPrec StartType
Int -> ReadS StartType
ReadS [StartType]
(Int -> ReadS StartType)
-> ReadS [StartType]
-> ReadPrec StartType
-> ReadPrec [StartType]
-> Read StartType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StartType
readsPrec :: Int -> ReadS StartType
$creadList :: ReadS [StartType]
readList :: ReadS [StartType]
$creadPrec :: ReadPrec StartType
readPrec :: ReadPrec StartType
$creadListPrec :: ReadPrec [StartType]
readListPrec :: ReadPrec [StartType]
Read)
instance PrintDot StartType where
unqtDot :: StartType -> DotCode
unqtDot (StartStyle STStyle
ss) = STStyle -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot STStyle
ss
unqtDot (StartSeed Int
s) = Int -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Int
s
unqtDot (StartStyleSeed STStyle
ss Int
s) = STStyle -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot STStyle
ss DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Int -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Int
s
instance ParseDot StartType where
parseUnqt :: Parse StartType
parseUnqt = [Parse StartType] -> Parse StartType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ (STStyle -> Int -> StartType)
-> Parser GraphvizState STStyle
-> Parser GraphvizState Int
-> Parse StartType
forall a b c.
(a -> b -> c)
-> Parser GraphvizState a
-> Parser GraphvizState b
-> Parser GraphvizState c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 STStyle -> Int -> StartType
StartStyleSeed Parser GraphvizState STStyle
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState Int
forall a. ParseDot a => Parse a
parseUnqt
, STStyle -> StartType
StartStyle (STStyle -> StartType)
-> Parser GraphvizState STStyle -> Parse StartType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState STStyle
forall a. ParseDot a => Parse a
parseUnqt
, Int -> StartType
StartSeed (Int -> StartType) -> Parser GraphvizState Int -> Parse StartType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Int
forall a. ParseDot a => Parse a
parseUnqt
]
data STStyle = RegularStyle
| SelfStyle
| RandomStyle
deriving (STStyle -> STStyle -> Bool
(STStyle -> STStyle -> Bool)
-> (STStyle -> STStyle -> Bool) -> Eq STStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: STStyle -> STStyle -> Bool
== :: STStyle -> STStyle -> Bool
$c/= :: STStyle -> STStyle -> Bool
/= :: STStyle -> STStyle -> Bool
Eq, Eq STStyle
Eq STStyle =>
(STStyle -> STStyle -> Ordering)
-> (STStyle -> STStyle -> Bool)
-> (STStyle -> STStyle -> Bool)
-> (STStyle -> STStyle -> Bool)
-> (STStyle -> STStyle -> Bool)
-> (STStyle -> STStyle -> STStyle)
-> (STStyle -> STStyle -> STStyle)
-> Ord STStyle
STStyle -> STStyle -> Bool
STStyle -> STStyle -> Ordering
STStyle -> STStyle -> STStyle
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
$ccompare :: STStyle -> STStyle -> Ordering
compare :: STStyle -> STStyle -> Ordering
$c< :: STStyle -> STStyle -> Bool
< :: STStyle -> STStyle -> Bool
$c<= :: STStyle -> STStyle -> Bool
<= :: STStyle -> STStyle -> Bool
$c> :: STStyle -> STStyle -> Bool
> :: STStyle -> STStyle -> Bool
$c>= :: STStyle -> STStyle -> Bool
>= :: STStyle -> STStyle -> Bool
$cmax :: STStyle -> STStyle -> STStyle
max :: STStyle -> STStyle -> STStyle
$cmin :: STStyle -> STStyle -> STStyle
min :: STStyle -> STStyle -> STStyle
Ord, STStyle
STStyle -> STStyle -> Bounded STStyle
forall a. a -> a -> Bounded a
$cminBound :: STStyle
minBound :: STStyle
$cmaxBound :: STStyle
maxBound :: STStyle
Bounded, Int -> STStyle
STStyle -> Int
STStyle -> [STStyle]
STStyle -> STStyle
STStyle -> STStyle -> [STStyle]
STStyle -> STStyle -> STStyle -> [STStyle]
(STStyle -> STStyle)
-> (STStyle -> STStyle)
-> (Int -> STStyle)
-> (STStyle -> Int)
-> (STStyle -> [STStyle])
-> (STStyle -> STStyle -> [STStyle])
-> (STStyle -> STStyle -> [STStyle])
-> (STStyle -> STStyle -> STStyle -> [STStyle])
-> Enum STStyle
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: STStyle -> STStyle
succ :: STStyle -> STStyle
$cpred :: STStyle -> STStyle
pred :: STStyle -> STStyle
$ctoEnum :: Int -> STStyle
toEnum :: Int -> STStyle
$cfromEnum :: STStyle -> Int
fromEnum :: STStyle -> Int
$cenumFrom :: STStyle -> [STStyle]
enumFrom :: STStyle -> [STStyle]
$cenumFromThen :: STStyle -> STStyle -> [STStyle]
enumFromThen :: STStyle -> STStyle -> [STStyle]
$cenumFromTo :: STStyle -> STStyle -> [STStyle]
enumFromTo :: STStyle -> STStyle -> [STStyle]
$cenumFromThenTo :: STStyle -> STStyle -> STStyle -> [STStyle]
enumFromThenTo :: STStyle -> STStyle -> STStyle -> [STStyle]
Enum, Int -> STStyle -> ShowS
[STStyle] -> ShowS
STStyle -> String
(Int -> STStyle -> ShowS)
-> (STStyle -> String) -> ([STStyle] -> ShowS) -> Show STStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> STStyle -> ShowS
showsPrec :: Int -> STStyle -> ShowS
$cshow :: STStyle -> String
show :: STStyle -> String
$cshowList :: [STStyle] -> ShowS
showList :: [STStyle] -> ShowS
Show, ReadPrec [STStyle]
ReadPrec STStyle
Int -> ReadS STStyle
ReadS [STStyle]
(Int -> ReadS STStyle)
-> ReadS [STStyle]
-> ReadPrec STStyle
-> ReadPrec [STStyle]
-> Read STStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS STStyle
readsPrec :: Int -> ReadS STStyle
$creadList :: ReadS [STStyle]
readList :: ReadS [STStyle]
$creadPrec :: ReadPrec STStyle
readPrec :: ReadPrec STStyle
$creadListPrec :: ReadPrec [STStyle]
readListPrec :: ReadPrec [STStyle]
Read)
instance PrintDot STStyle where
unqtDot :: STStyle -> DotCode
unqtDot STStyle
RegularStyle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"regular"
unqtDot STStyle
SelfStyle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"self"
unqtDot STStyle
RandomStyle = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"random"
instance ParseDot STStyle where
parseUnqt :: Parser GraphvizState STStyle
parseUnqt = [Parser GraphvizState STStyle] -> Parser GraphvizState STStyle
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ STStyle -> String -> Parser GraphvizState STStyle
forall a. a -> String -> Parse a
stringRep STStyle
RegularStyle String
"regular"
, STStyle -> String -> Parser GraphvizState STStyle
forall a. a -> String -> Parse a
stringRep STStyle
SelfStyle String
"self"
, STStyle -> String -> Parser GraphvizState STStyle
forall a. a -> String -> Parse a
stringRep STStyle
RandomStyle String
"random"
]
data StyleItem = SItem StyleName [Text]
deriving (StyleItem -> StyleItem -> Bool
(StyleItem -> StyleItem -> Bool)
-> (StyleItem -> StyleItem -> Bool) -> Eq StyleItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StyleItem -> StyleItem -> Bool
== :: StyleItem -> StyleItem -> Bool
$c/= :: StyleItem -> StyleItem -> Bool
/= :: StyleItem -> StyleItem -> Bool
Eq, Eq StyleItem
Eq StyleItem =>
(StyleItem -> StyleItem -> Ordering)
-> (StyleItem -> StyleItem -> Bool)
-> (StyleItem -> StyleItem -> Bool)
-> (StyleItem -> StyleItem -> Bool)
-> (StyleItem -> StyleItem -> Bool)
-> (StyleItem -> StyleItem -> StyleItem)
-> (StyleItem -> StyleItem -> StyleItem)
-> Ord StyleItem
StyleItem -> StyleItem -> Bool
StyleItem -> StyleItem -> Ordering
StyleItem -> StyleItem -> StyleItem
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
$ccompare :: StyleItem -> StyleItem -> Ordering
compare :: StyleItem -> StyleItem -> Ordering
$c< :: StyleItem -> StyleItem -> Bool
< :: StyleItem -> StyleItem -> Bool
$c<= :: StyleItem -> StyleItem -> Bool
<= :: StyleItem -> StyleItem -> Bool
$c> :: StyleItem -> StyleItem -> Bool
> :: StyleItem -> StyleItem -> Bool
$c>= :: StyleItem -> StyleItem -> Bool
>= :: StyleItem -> StyleItem -> Bool
$cmax :: StyleItem -> StyleItem -> StyleItem
max :: StyleItem -> StyleItem -> StyleItem
$cmin :: StyleItem -> StyleItem -> StyleItem
min :: StyleItem -> StyleItem -> StyleItem
Ord, Int -> StyleItem -> ShowS
[StyleItem] -> ShowS
StyleItem -> String
(Int -> StyleItem -> ShowS)
-> (StyleItem -> String)
-> ([StyleItem] -> ShowS)
-> Show StyleItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StyleItem -> ShowS
showsPrec :: Int -> StyleItem -> ShowS
$cshow :: StyleItem -> String
show :: StyleItem -> String
$cshowList :: [StyleItem] -> ShowS
showList :: [StyleItem] -> ShowS
Show, ReadPrec [StyleItem]
ReadPrec StyleItem
Int -> ReadS StyleItem
ReadS [StyleItem]
(Int -> ReadS StyleItem)
-> ReadS [StyleItem]
-> ReadPrec StyleItem
-> ReadPrec [StyleItem]
-> Read StyleItem
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StyleItem
readsPrec :: Int -> ReadS StyleItem
$creadList :: ReadS [StyleItem]
readList :: ReadS [StyleItem]
$creadPrec :: ReadPrec StyleItem
readPrec :: ReadPrec StyleItem
$creadListPrec :: ReadPrec [StyleItem]
readListPrec :: ReadPrec [StyleItem]
Read)
instance PrintDot StyleItem where
unqtDot :: StyleItem -> DotCode
unqtDot (SItem StyleName
nm [Text]
args)
| [Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
args = DotCode
dnm
| Bool
otherwise = DotCode
dnm DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
parens DotCode
args'
where
dnm :: DotCode
dnm = StyleName -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot StyleName
nm
args' :: DotCode
args' = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> (DotCodeM [Doc] -> DotCodeM [Doc]) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate DotCode
forall (m :: * -> *). Applicative m => m Doc
comma (DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall a b. (a -> b) -> a -> b
$ (Text -> DotCode) -> [Text] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot [Text]
args
toDot :: StyleItem -> DotCode
toDot si :: StyleItem
si@(SItem StyleName
nm [Text]
args)
| [Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
args = StyleName -> DotCode
forall a. PrintDot a => a -> DotCode
toDot StyleName
nm
| Bool
otherwise = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ StyleItem -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot StyleItem
si
unqtListToDot :: [StyleItem] -> DotCode
unqtListToDot = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> ([StyleItem] -> DotCodeM [Doc]) -> [StyleItem] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate DotCode
forall (m :: * -> *). Applicative m => m Doc
comma (DotCodeM [Doc] -> DotCodeM [Doc])
-> ([StyleItem] -> DotCodeM [Doc]) -> [StyleItem] -> DotCodeM [Doc]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StyleItem -> DotCode) -> [StyleItem] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM StyleItem -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
listToDot :: [StyleItem] -> DotCode
listToDot [SItem StyleName
nm []] = StyleName -> DotCode
forall a. PrintDot a => a -> DotCode
toDot StyleName
nm
listToDot [StyleItem]
sis = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ [StyleItem] -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot [StyleItem]
sis
instance ParseDot StyleItem where
parseUnqt :: Parse StyleItem
parseUnqt = (StyleName -> [Text] -> StyleItem)
-> Parser GraphvizState StyleName
-> Parser GraphvizState [Text]
-> Parse StyleItem
forall a b c.
(a -> b -> c)
-> Parser GraphvizState a
-> Parser GraphvizState b
-> Parser GraphvizState c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 StyleName -> [Text] -> StyleItem
SItem Parser GraphvizState StyleName
forall a. ParseDot a => Parse a
parseUnqt (Parser GraphvizState [Text] -> Parser GraphvizState [Text]
forall a. Parse [a] -> Parse [a]
tryParseList' Parser GraphvizState [Text]
parseArgs)
parse :: Parse StyleItem
parse = Parse StyleItem -> Parse StyleItem
forall a. Parse a -> Parse a
quotedParse ((StyleName -> [Text] -> StyleItem)
-> Parser GraphvizState StyleName
-> Parser GraphvizState [Text]
-> Parse StyleItem
forall a b c.
(a -> b -> c)
-> Parser GraphvizState a
-> Parser GraphvizState b
-> Parser GraphvizState c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 StyleName -> [Text] -> StyleItem
SItem Parser GraphvizState StyleName
forall a. ParseDot a => Parse a
parseUnqt Parser GraphvizState [Text]
parseArgs)
Parse StyleItem -> Parse StyleItem -> Parse StyleItem
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(StyleName -> StyleItem)
-> Parser GraphvizState StyleName -> Parse StyleItem
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (StyleName -> [Text] -> StyleItem
`SItem` []) Parser GraphvizState StyleName
forall a. ParseDot a => Parse a
parse
parseUnqtList :: Parse [StyleItem]
parseUnqtList = Parse StyleItem -> Parser GraphvizState () -> Parse [StyleItem]
forall (p :: * -> *) a sep. PolyParse p => p a -> p sep -> p [a]
sepBy1 Parse StyleItem
forall a. ParseDot a => Parse a
parseUnqt (Parser GraphvizState () -> Parser GraphvizState ()
forall a. Parse a -> Parse a
wrapWhitespace Parser GraphvizState ()
parseComma)
parseList :: Parse [StyleItem]
parseList = Parse [StyleItem] -> Parse [StyleItem]
forall a. Parse a -> Parse a
quotedParse Parse [StyleItem]
forall a. ParseDot a => Parse [a]
parseUnqtList
Parse [StyleItem] -> Parse [StyleItem] -> Parse [StyleItem]
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(StyleItem -> [StyleItem]) -> Parse StyleItem -> Parse [StyleItem]
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StyleItem -> [StyleItem]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return Parse StyleItem
forall a. ParseDot a => Parse a
parse
parseArgs :: Parse [Text]
parseArgs :: Parser GraphvizState [Text]
parseArgs = Parser GraphvizState Char
-> Parser GraphvizState ()
-> Parser GraphvizState Char
-> Parser GraphvizState Text
-> Parser GraphvizState [Text]
forall (p :: * -> *) bra sep ket a.
PolyParse p =>
p bra -> p sep -> p ket -> p a -> p [a]
bracketSep (Char -> Parser GraphvizState Char
character Char
'(')
Parser GraphvizState ()
parseComma
(Char -> Parser GraphvizState Char
character Char
')')
Parser GraphvizState Text
parseStyleName
data StyleName = Dashed
| Dotted
| Solid
| Bold
| Invisible
| Filled
| Striped
| Wedged
| Diagonals
| Rounded
| Tapered
| Radial
| DD Text
deriving (StyleName -> StyleName -> Bool
(StyleName -> StyleName -> Bool)
-> (StyleName -> StyleName -> Bool) -> Eq StyleName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StyleName -> StyleName -> Bool
== :: StyleName -> StyleName -> Bool
$c/= :: StyleName -> StyleName -> Bool
/= :: StyleName -> StyleName -> Bool
Eq, Eq StyleName
Eq StyleName =>
(StyleName -> StyleName -> Ordering)
-> (StyleName -> StyleName -> Bool)
-> (StyleName -> StyleName -> Bool)
-> (StyleName -> StyleName -> Bool)
-> (StyleName -> StyleName -> Bool)
-> (StyleName -> StyleName -> StyleName)
-> (StyleName -> StyleName -> StyleName)
-> Ord StyleName
StyleName -> StyleName -> Bool
StyleName -> StyleName -> Ordering
StyleName -> StyleName -> StyleName
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
$ccompare :: StyleName -> StyleName -> Ordering
compare :: StyleName -> StyleName -> Ordering
$c< :: StyleName -> StyleName -> Bool
< :: StyleName -> StyleName -> Bool
$c<= :: StyleName -> StyleName -> Bool
<= :: StyleName -> StyleName -> Bool
$c> :: StyleName -> StyleName -> Bool
> :: StyleName -> StyleName -> Bool
$c>= :: StyleName -> StyleName -> Bool
>= :: StyleName -> StyleName -> Bool
$cmax :: StyleName -> StyleName -> StyleName
max :: StyleName -> StyleName -> StyleName
$cmin :: StyleName -> StyleName -> StyleName
min :: StyleName -> StyleName -> StyleName
Ord, Int -> StyleName -> ShowS
[StyleName] -> ShowS
StyleName -> String
(Int -> StyleName -> ShowS)
-> (StyleName -> String)
-> ([StyleName] -> ShowS)
-> Show StyleName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StyleName -> ShowS
showsPrec :: Int -> StyleName -> ShowS
$cshow :: StyleName -> String
show :: StyleName -> String
$cshowList :: [StyleName] -> ShowS
showList :: [StyleName] -> ShowS
Show, ReadPrec [StyleName]
ReadPrec StyleName
Int -> ReadS StyleName
ReadS [StyleName]
(Int -> ReadS StyleName)
-> ReadS [StyleName]
-> ReadPrec StyleName
-> ReadPrec [StyleName]
-> Read StyleName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StyleName
readsPrec :: Int -> ReadS StyleName
$creadList :: ReadS [StyleName]
readList :: ReadS [StyleName]
$creadPrec :: ReadPrec StyleName
readPrec :: ReadPrec StyleName
$creadListPrec :: ReadPrec [StyleName]
readListPrec :: ReadPrec [StyleName]
Read)
instance PrintDot StyleName where
unqtDot :: StyleName -> DotCode
unqtDot StyleName
Dashed = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"dashed"
unqtDot StyleName
Dotted = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"dotted"
unqtDot StyleName
Solid = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"solid"
unqtDot StyleName
Bold = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"bold"
unqtDot StyleName
Invisible = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"invis"
unqtDot StyleName
Filled = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"filled"
unqtDot StyleName
Striped = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"striped"
unqtDot StyleName
Wedged = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"wedged"
unqtDot StyleName
Diagonals = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"diagonals"
unqtDot StyleName
Rounded = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"rounded"
unqtDot StyleName
Tapered = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"tapered"
unqtDot StyleName
Radial = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"radial"
unqtDot (DD Text
nm) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
nm
toDot :: StyleName -> DotCode
toDot (DD Text
nm) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
nm
toDot StyleName
sn = StyleName -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot StyleName
sn
instance ParseDot StyleName where
parseUnqt :: Parser GraphvizState StyleName
parseUnqt = Text -> StyleName
checkDD (Text -> StyleName)
-> Parser GraphvizState Text -> Parser GraphvizState StyleName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Text
parseStyleName
parse :: Parser GraphvizState StyleName
parse = Parser GraphvizState StyleName -> Parser GraphvizState StyleName
forall a. Parse a -> Parse a
quotedParse Parser GraphvizState StyleName
forall a. ParseDot a => Parse a
parseUnqt
Parser GraphvizState StyleName
-> Parser GraphvizState StyleName -> Parser GraphvizState StyleName
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> StyleName)
-> Parser GraphvizState Text -> Parser GraphvizState StyleName
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> StyleName
checkDD Parser GraphvizState Text
quotelessString
checkDD :: Text -> StyleName
checkDD :: Text -> StyleName
checkDD Text
str = case Text -> Text
T.toLower Text
str of
Text
"dashed" -> StyleName
Dashed
Text
"dotted" -> StyleName
Dotted
Text
"solid" -> StyleName
Solid
Text
"bold" -> StyleName
Bold
Text
"invis" -> StyleName
Invisible
Text
"filled" -> StyleName
Filled
Text
"striped" -> StyleName
Striped
Text
"wedged" -> StyleName
Wedged
Text
"diagonals" -> StyleName
Diagonals
Text
"rounded" -> StyleName
Rounded
Text
"tapered" -> StyleName
Tapered
Text
"radial" -> StyleName
Radial
Text
_ -> Text -> StyleName
DD Text
str
parseStyleName :: Parse Text
parseStyleName :: Parser GraphvizState Text
parseStyleName = (Char -> Text -> Text)
-> Parser GraphvizState Char
-> Parser GraphvizState Text
-> Parser GraphvizState Text
forall a b c.
(a -> b -> c)
-> Parser GraphvizState a
-> Parser GraphvizState b
-> Parser GraphvizState c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Char -> Text -> Text
T.cons (Parser GraphvizState Char -> Parser GraphvizState Char
orEscaped (Parser GraphvizState Char -> Parser GraphvizState Char)
-> (String -> Parser GraphvizState Char)
-> String
-> Parser GraphvizState Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Parser GraphvizState Char
noneOf (String -> Parser GraphvizState Char)
-> String -> Parser GraphvizState Char
forall a b. (a -> b) -> a -> b
$ Char
' ' Char -> ShowS
forall a. a -> [a] -> [a]
: String
disallowedChars)
(Bool -> String -> String -> Parser GraphvizState Text
parseEscaped Bool
True [] String
disallowedChars)
where
disallowedChars :: String
disallowedChars = [Char
quoteChar, Char
'(', Char
')', Char
',']
orSlash :: Parser GraphvizState Char -> Parser GraphvizState Char
orSlash Parser GraphvizState Char
p = Char -> String -> Parser GraphvizState Char
forall a. a -> String -> Parse a
stringRep Char
'\\' String
"\\\\" Parser GraphvizState Char
-> Parser GraphvizState Char -> Parser GraphvizState Char
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail` Parser GraphvizState Char
p
orEscaped :: Parser GraphvizState Char -> Parser GraphvizState Char
orEscaped = Parser GraphvizState Char -> Parser GraphvizState Char
orQuote (Parser GraphvizState Char -> Parser GraphvizState Char)
-> (Parser GraphvizState Char -> Parser GraphvizState Char)
-> Parser GraphvizState Char
-> Parser GraphvizState Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser GraphvizState Char -> Parser GraphvizState Char
orSlash
data ViewPort = VP { ViewPort -> Double
wVal :: Double
, ViewPort -> Double
hVal :: Double
, ViewPort -> Double
zVal :: Double
, ViewPort -> Maybe FocusType
focus :: Maybe FocusType
}
deriving (ViewPort -> ViewPort -> Bool
(ViewPort -> ViewPort -> Bool)
-> (ViewPort -> ViewPort -> Bool) -> Eq ViewPort
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ViewPort -> ViewPort -> Bool
== :: ViewPort -> ViewPort -> Bool
$c/= :: ViewPort -> ViewPort -> Bool
/= :: ViewPort -> ViewPort -> Bool
Eq, Eq ViewPort
Eq ViewPort =>
(ViewPort -> ViewPort -> Ordering)
-> (ViewPort -> ViewPort -> Bool)
-> (ViewPort -> ViewPort -> Bool)
-> (ViewPort -> ViewPort -> Bool)
-> (ViewPort -> ViewPort -> Bool)
-> (ViewPort -> ViewPort -> ViewPort)
-> (ViewPort -> ViewPort -> ViewPort)
-> Ord ViewPort
ViewPort -> ViewPort -> Bool
ViewPort -> ViewPort -> Ordering
ViewPort -> ViewPort -> ViewPort
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
$ccompare :: ViewPort -> ViewPort -> Ordering
compare :: ViewPort -> ViewPort -> Ordering
$c< :: ViewPort -> ViewPort -> Bool
< :: ViewPort -> ViewPort -> Bool
$c<= :: ViewPort -> ViewPort -> Bool
<= :: ViewPort -> ViewPort -> Bool
$c> :: ViewPort -> ViewPort -> Bool
> :: ViewPort -> ViewPort -> Bool
$c>= :: ViewPort -> ViewPort -> Bool
>= :: ViewPort -> ViewPort -> Bool
$cmax :: ViewPort -> ViewPort -> ViewPort
max :: ViewPort -> ViewPort -> ViewPort
$cmin :: ViewPort -> ViewPort -> ViewPort
min :: ViewPort -> ViewPort -> ViewPort
Ord, Int -> ViewPort -> ShowS
[ViewPort] -> ShowS
ViewPort -> String
(Int -> ViewPort -> ShowS)
-> (ViewPort -> String) -> ([ViewPort] -> ShowS) -> Show ViewPort
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ViewPort -> ShowS
showsPrec :: Int -> ViewPort -> ShowS
$cshow :: ViewPort -> String
show :: ViewPort -> String
$cshowList :: [ViewPort] -> ShowS
showList :: [ViewPort] -> ShowS
Show, ReadPrec [ViewPort]
ReadPrec ViewPort
Int -> ReadS ViewPort
ReadS [ViewPort]
(Int -> ReadS ViewPort)
-> ReadS [ViewPort]
-> ReadPrec ViewPort
-> ReadPrec [ViewPort]
-> Read ViewPort
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ViewPort
readsPrec :: Int -> ReadS ViewPort
$creadList :: ReadS [ViewPort]
readList :: ReadS [ViewPort]
$creadPrec :: ReadPrec ViewPort
readPrec :: ReadPrec ViewPort
$creadListPrec :: ReadPrec [ViewPort]
readListPrec :: ReadPrec [ViewPort]
Read)
instance PrintDot ViewPort where
unqtDot :: ViewPort -> DotCode
unqtDot ViewPort
vp = DotCode -> (FocusType -> DotCode) -> Maybe FocusType -> DotCode
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DotCode
vs (DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
(<>) (DotCode
vs DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode
forall (m :: * -> *). Applicative m => m Doc
comma) (DotCode -> DotCode)
-> (FocusType -> DotCode) -> FocusType -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FocusType -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot)
(Maybe FocusType -> DotCode) -> Maybe FocusType -> DotCode
forall a b. (a -> b) -> a -> b
$ ViewPort -> Maybe FocusType
focus ViewPort
vp
where
vs :: DotCode
vs = DotCodeM [Doc] -> DotCode
forall (m :: * -> *). Functor m => m [Doc] -> m Doc
hcat (DotCodeM [Doc] -> DotCode)
-> (DotCodeM [Doc] -> DotCodeM [Doc]) -> DotCodeM [Doc] -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DotCode -> DotCodeM [Doc] -> DotCodeM [Doc]
forall (m :: * -> *). Applicative m => m Doc -> m [Doc] -> m [Doc]
punctuate DotCode
forall (m :: * -> *). Applicative m => m Doc
comma
(DotCodeM [Doc] -> DotCode) -> DotCodeM [Doc] -> DotCode
forall a b. (a -> b) -> a -> b
$ ((ViewPort -> Double) -> DotCode)
-> [ViewPort -> Double] -> DotCodeM [Doc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot (Double -> DotCode)
-> ((ViewPort -> Double) -> Double)
-> (ViewPort -> Double)
-> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ViewPort -> Double) -> ViewPort -> Double
forall a b. (a -> b) -> a -> b
$ViewPort
vp)) [ViewPort -> Double
wVal, ViewPort -> Double
hVal, ViewPort -> Double
zVal]
toDot :: ViewPort -> DotCode
toDot = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode)
-> (ViewPort -> DotCode) -> ViewPort -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ViewPort -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot
instance ParseDot ViewPort where
parseUnqt :: Parse ViewPort
parseUnqt = Double -> Double -> Double -> Maybe FocusType -> ViewPort
VP (Double -> Double -> Double -> Maybe FocusType -> ViewPort)
-> Parser GraphvizState Double
-> Parser
GraphvizState (Double -> Double -> Maybe FocusType -> ViewPort)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt
Parser
GraphvizState (Double -> Double -> Maybe FocusType -> ViewPort)
-> Parser GraphvizState ()
-> Parser
GraphvizState (Double -> Double -> Maybe FocusType -> ViewPort)
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser GraphvizState ()
parseComma
Parser
GraphvizState (Double -> Double -> Maybe FocusType -> ViewPort)
-> Parser GraphvizState Double
-> Parser GraphvizState (Double -> Maybe FocusType -> ViewPort)
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt
Parser GraphvizState (Double -> Maybe FocusType -> ViewPort)
-> Parser GraphvizState ()
-> Parser GraphvizState (Double -> Maybe FocusType -> ViewPort)
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser GraphvizState ()
parseComma
Parser GraphvizState (Double -> Maybe FocusType -> ViewPort)
-> Parser GraphvizState Double
-> Parser GraphvizState (Maybe FocusType -> ViewPort)
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GraphvizState Double
forall a. ParseDot a => Parse a
parseUnqt
Parser GraphvizState (Maybe FocusType -> ViewPort)
-> Parser GraphvizState (Maybe FocusType) -> Parse ViewPort
forall a b.
Parser GraphvizState (a -> b)
-> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GraphvizState FocusType
-> Parser GraphvizState (Maybe FocusType)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState ()
parseComma Parser GraphvizState ()
-> Parser GraphvizState FocusType -> Parser GraphvizState FocusType
forall a b.
Parser GraphvizState a
-> Parser GraphvizState b -> Parser GraphvizState b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser GraphvizState FocusType
forall a. ParseDot a => Parse a
parseUnqt)
parse :: Parse ViewPort
parse = Parse ViewPort -> Parse ViewPort
forall a. Parse a -> Parse a
quotedParse Parse ViewPort
forall a. ParseDot a => Parse a
parseUnqt
data FocusType = XY Point
| NodeFocus Text
deriving (FocusType -> FocusType -> Bool
(FocusType -> FocusType -> Bool)
-> (FocusType -> FocusType -> Bool) -> Eq FocusType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FocusType -> FocusType -> Bool
== :: FocusType -> FocusType -> Bool
$c/= :: FocusType -> FocusType -> Bool
/= :: FocusType -> FocusType -> Bool
Eq, Eq FocusType
Eq FocusType =>
(FocusType -> FocusType -> Ordering)
-> (FocusType -> FocusType -> Bool)
-> (FocusType -> FocusType -> Bool)
-> (FocusType -> FocusType -> Bool)
-> (FocusType -> FocusType -> Bool)
-> (FocusType -> FocusType -> FocusType)
-> (FocusType -> FocusType -> FocusType)
-> Ord FocusType
FocusType -> FocusType -> Bool
FocusType -> FocusType -> Ordering
FocusType -> FocusType -> FocusType
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
$ccompare :: FocusType -> FocusType -> Ordering
compare :: FocusType -> FocusType -> Ordering
$c< :: FocusType -> FocusType -> Bool
< :: FocusType -> FocusType -> Bool
$c<= :: FocusType -> FocusType -> Bool
<= :: FocusType -> FocusType -> Bool
$c> :: FocusType -> FocusType -> Bool
> :: FocusType -> FocusType -> Bool
$c>= :: FocusType -> FocusType -> Bool
>= :: FocusType -> FocusType -> Bool
$cmax :: FocusType -> FocusType -> FocusType
max :: FocusType -> FocusType -> FocusType
$cmin :: FocusType -> FocusType -> FocusType
min :: FocusType -> FocusType -> FocusType
Ord, Int -> FocusType -> ShowS
[FocusType] -> ShowS
FocusType -> String
(Int -> FocusType -> ShowS)
-> (FocusType -> String)
-> ([FocusType] -> ShowS)
-> Show FocusType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FocusType -> ShowS
showsPrec :: Int -> FocusType -> ShowS
$cshow :: FocusType -> String
show :: FocusType -> String
$cshowList :: [FocusType] -> ShowS
showList :: [FocusType] -> ShowS
Show, ReadPrec [FocusType]
ReadPrec FocusType
Int -> ReadS FocusType
ReadS [FocusType]
(Int -> ReadS FocusType)
-> ReadS [FocusType]
-> ReadPrec FocusType
-> ReadPrec [FocusType]
-> Read FocusType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FocusType
readsPrec :: Int -> ReadS FocusType
$creadList :: ReadS [FocusType]
readList :: ReadS [FocusType]
$creadPrec :: ReadPrec FocusType
readPrec :: ReadPrec FocusType
$creadListPrec :: ReadPrec [FocusType]
readListPrec :: ReadPrec [FocusType]
Read)
instance PrintDot FocusType where
unqtDot :: FocusType -> DotCode
unqtDot (XY Point
p) = Point -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Point
p
unqtDot (NodeFocus Text
nm) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Text
nm
toDot :: FocusType -> DotCode
toDot (XY Point
p) = Point -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Point
p
toDot (NodeFocus Text
nm) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
nm
instance ParseDot FocusType where
parseUnqt :: Parser GraphvizState FocusType
parseUnqt = (Point -> FocusType)
-> Parse Point -> Parser GraphvizState FocusType
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Point -> FocusType
XY Parse Point
forall a. ParseDot a => Parse a
parseUnqt
Parser GraphvizState FocusType
-> Parser GraphvizState FocusType -> Parser GraphvizState FocusType
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> FocusType)
-> Parser GraphvizState Text -> Parser GraphvizState FocusType
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> FocusType
NodeFocus Parser GraphvizState Text
forall a. ParseDot a => Parse a
parseUnqt
parse :: Parser GraphvizState FocusType
parse = (Point -> FocusType)
-> Parse Point -> Parser GraphvizState FocusType
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Point -> FocusType
XY Parse Point
forall a. ParseDot a => Parse a
parse
Parser GraphvizState FocusType
-> Parser GraphvizState FocusType -> Parser GraphvizState FocusType
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> FocusType)
-> Parser GraphvizState Text -> Parser GraphvizState FocusType
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> FocusType
NodeFocus Parser GraphvizState Text
forall a. ParseDot a => Parse a
parse
data VerticalPlacement = VTop
| VCenter
| VBottom
deriving (VerticalPlacement -> VerticalPlacement -> Bool
(VerticalPlacement -> VerticalPlacement -> Bool)
-> (VerticalPlacement -> VerticalPlacement -> Bool)
-> Eq VerticalPlacement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VerticalPlacement -> VerticalPlacement -> Bool
== :: VerticalPlacement -> VerticalPlacement -> Bool
$c/= :: VerticalPlacement -> VerticalPlacement -> Bool
/= :: VerticalPlacement -> VerticalPlacement -> Bool
Eq, Eq VerticalPlacement
Eq VerticalPlacement =>
(VerticalPlacement -> VerticalPlacement -> Ordering)
-> (VerticalPlacement -> VerticalPlacement -> Bool)
-> (VerticalPlacement -> VerticalPlacement -> Bool)
-> (VerticalPlacement -> VerticalPlacement -> Bool)
-> (VerticalPlacement -> VerticalPlacement -> Bool)
-> (VerticalPlacement -> VerticalPlacement -> VerticalPlacement)
-> (VerticalPlacement -> VerticalPlacement -> VerticalPlacement)
-> Ord VerticalPlacement
VerticalPlacement -> VerticalPlacement -> Bool
VerticalPlacement -> VerticalPlacement -> Ordering
VerticalPlacement -> VerticalPlacement -> VerticalPlacement
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
$ccompare :: VerticalPlacement -> VerticalPlacement -> Ordering
compare :: VerticalPlacement -> VerticalPlacement -> Ordering
$c< :: VerticalPlacement -> VerticalPlacement -> Bool
< :: VerticalPlacement -> VerticalPlacement -> Bool
$c<= :: VerticalPlacement -> VerticalPlacement -> Bool
<= :: VerticalPlacement -> VerticalPlacement -> Bool
$c> :: VerticalPlacement -> VerticalPlacement -> Bool
> :: VerticalPlacement -> VerticalPlacement -> Bool
$c>= :: VerticalPlacement -> VerticalPlacement -> Bool
>= :: VerticalPlacement -> VerticalPlacement -> Bool
$cmax :: VerticalPlacement -> VerticalPlacement -> VerticalPlacement
max :: VerticalPlacement -> VerticalPlacement -> VerticalPlacement
$cmin :: VerticalPlacement -> VerticalPlacement -> VerticalPlacement
min :: VerticalPlacement -> VerticalPlacement -> VerticalPlacement
Ord, VerticalPlacement
VerticalPlacement -> VerticalPlacement -> Bounded VerticalPlacement
forall a. a -> a -> Bounded a
$cminBound :: VerticalPlacement
minBound :: VerticalPlacement
$cmaxBound :: VerticalPlacement
maxBound :: VerticalPlacement
Bounded, Int -> VerticalPlacement
VerticalPlacement -> Int
VerticalPlacement -> [VerticalPlacement]
VerticalPlacement -> VerticalPlacement
VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
VerticalPlacement
-> VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
(VerticalPlacement -> VerticalPlacement)
-> (VerticalPlacement -> VerticalPlacement)
-> (Int -> VerticalPlacement)
-> (VerticalPlacement -> Int)
-> (VerticalPlacement -> [VerticalPlacement])
-> (VerticalPlacement -> VerticalPlacement -> [VerticalPlacement])
-> (VerticalPlacement -> VerticalPlacement -> [VerticalPlacement])
-> (VerticalPlacement
-> VerticalPlacement -> VerticalPlacement -> [VerticalPlacement])
-> Enum VerticalPlacement
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: VerticalPlacement -> VerticalPlacement
succ :: VerticalPlacement -> VerticalPlacement
$cpred :: VerticalPlacement -> VerticalPlacement
pred :: VerticalPlacement -> VerticalPlacement
$ctoEnum :: Int -> VerticalPlacement
toEnum :: Int -> VerticalPlacement
$cfromEnum :: VerticalPlacement -> Int
fromEnum :: VerticalPlacement -> Int
$cenumFrom :: VerticalPlacement -> [VerticalPlacement]
enumFrom :: VerticalPlacement -> [VerticalPlacement]
$cenumFromThen :: VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
enumFromThen :: VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
$cenumFromTo :: VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
enumFromTo :: VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
$cenumFromThenTo :: VerticalPlacement
-> VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
enumFromThenTo :: VerticalPlacement
-> VerticalPlacement -> VerticalPlacement -> [VerticalPlacement]
Enum, Int -> VerticalPlacement -> ShowS
[VerticalPlacement] -> ShowS
VerticalPlacement -> String
(Int -> VerticalPlacement -> ShowS)
-> (VerticalPlacement -> String)
-> ([VerticalPlacement] -> ShowS)
-> Show VerticalPlacement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerticalPlacement -> ShowS
showsPrec :: Int -> VerticalPlacement -> ShowS
$cshow :: VerticalPlacement -> String
show :: VerticalPlacement -> String
$cshowList :: [VerticalPlacement] -> ShowS
showList :: [VerticalPlacement] -> ShowS
Show, ReadPrec [VerticalPlacement]
ReadPrec VerticalPlacement
Int -> ReadS VerticalPlacement
ReadS [VerticalPlacement]
(Int -> ReadS VerticalPlacement)
-> ReadS [VerticalPlacement]
-> ReadPrec VerticalPlacement
-> ReadPrec [VerticalPlacement]
-> Read VerticalPlacement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VerticalPlacement
readsPrec :: Int -> ReadS VerticalPlacement
$creadList :: ReadS [VerticalPlacement]
readList :: ReadS [VerticalPlacement]
$creadPrec :: ReadPrec VerticalPlacement
readPrec :: ReadPrec VerticalPlacement
$creadListPrec :: ReadPrec [VerticalPlacement]
readListPrec :: ReadPrec [VerticalPlacement]
Read)
instance PrintDot VerticalPlacement where
unqtDot :: VerticalPlacement -> DotCode
unqtDot VerticalPlacement
VTop = Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
't'
unqtDot VerticalPlacement
VCenter = Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'c'
unqtDot VerticalPlacement
VBottom = Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'b'
instance ParseDot VerticalPlacement where
parseUnqt :: Parse VerticalPlacement
parseUnqt = [Parse VerticalPlacement] -> Parse VerticalPlacement
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ VerticalPlacement -> [String] -> Parse VerticalPlacement
forall a. a -> [String] -> Parse a
stringReps VerticalPlacement
VTop [String
"top", String
"t"]
, VerticalPlacement -> [String] -> Parse VerticalPlacement
forall a. a -> [String] -> Parse a
stringReps VerticalPlacement
VCenter [String
"centre", String
"center", String
"c"]
, VerticalPlacement -> [String] -> Parse VerticalPlacement
forall a. a -> [String] -> Parse a
stringReps VerticalPlacement
VBottom [String
"bottom", String
"b"]
]
newtype Paths = Paths { Paths -> [String]
paths :: [FilePath] }
deriving (Paths -> Paths -> Bool
(Paths -> Paths -> Bool) -> (Paths -> Paths -> Bool) -> Eq Paths
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Paths -> Paths -> Bool
== :: Paths -> Paths -> Bool
$c/= :: Paths -> Paths -> Bool
/= :: Paths -> Paths -> Bool
Eq, Eq Paths
Eq Paths =>
(Paths -> Paths -> Ordering)
-> (Paths -> Paths -> Bool)
-> (Paths -> Paths -> Bool)
-> (Paths -> Paths -> Bool)
-> (Paths -> Paths -> Bool)
-> (Paths -> Paths -> Paths)
-> (Paths -> Paths -> Paths)
-> Ord Paths
Paths -> Paths -> Bool
Paths -> Paths -> Ordering
Paths -> Paths -> Paths
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
$ccompare :: Paths -> Paths -> Ordering
compare :: Paths -> Paths -> Ordering
$c< :: Paths -> Paths -> Bool
< :: Paths -> Paths -> Bool
$c<= :: Paths -> Paths -> Bool
<= :: Paths -> Paths -> Bool
$c> :: Paths -> Paths -> Bool
> :: Paths -> Paths -> Bool
$c>= :: Paths -> Paths -> Bool
>= :: Paths -> Paths -> Bool
$cmax :: Paths -> Paths -> Paths
max :: Paths -> Paths -> Paths
$cmin :: Paths -> Paths -> Paths
min :: Paths -> Paths -> Paths
Ord, Int -> Paths -> ShowS
[Paths] -> ShowS
Paths -> String
(Int -> Paths -> ShowS)
-> (Paths -> String) -> ([Paths] -> ShowS) -> Show Paths
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Paths -> ShowS
showsPrec :: Int -> Paths -> ShowS
$cshow :: Paths -> String
show :: Paths -> String
$cshowList :: [Paths] -> ShowS
showList :: [Paths] -> ShowS
Show, ReadPrec [Paths]
ReadPrec Paths
Int -> ReadS Paths
ReadS [Paths]
(Int -> ReadS Paths)
-> ReadS [Paths]
-> ReadPrec Paths
-> ReadPrec [Paths]
-> Read Paths
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Paths
readsPrec :: Int -> ReadS Paths
$creadList :: ReadS [Paths]
readList :: ReadS [Paths]
$creadPrec :: ReadPrec Paths
readPrec :: ReadPrec Paths
$creadListPrec :: ReadPrec [Paths]
readListPrec :: ReadPrec [Paths]
Read)
instance PrintDot Paths where
unqtDot :: Paths -> DotCode
unqtDot = String -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot (String -> DotCode) -> (Paths -> String) -> Paths -> DotCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate [Char
searchPathSeparator] ([String] -> String) -> (Paths -> [String]) -> Paths -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Paths -> [String]
paths
toDot :: Paths -> DotCode
toDot (Paths [String
p]) = String -> DotCode
forall a. PrintDot a => a -> DotCode
toDot String
p
toDot Paths
ps = DotCode -> DotCode
forall (m :: * -> *). Functor m => m Doc -> m Doc
dquotes (DotCode -> DotCode) -> DotCode -> DotCode
forall a b. (a -> b) -> a -> b
$ Paths -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Paths
ps
instance ParseDot Paths where
parseUnqt :: Parse Paths
parseUnqt = [String] -> Paths
Paths ([String] -> Paths) -> (String -> [String]) -> String -> Paths
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
splitSearchPath (String -> Paths) -> Parser GraphvizState String -> Parse Paths
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState String
forall a. ParseDot a => Parse a
parseUnqt
parse :: Parse Paths
parse = Parse Paths -> Parse Paths
forall a. Parse a -> Parse a
quotedParse Parse Paths
forall a. ParseDot a => Parse a
parseUnqt
Parse Paths -> Parse Paths -> Parse Paths
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
(Text -> Paths) -> Parser GraphvizState Text -> Parse Paths
forall a b.
(a -> b) -> Parser GraphvizState a -> Parser GraphvizState b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([String] -> Paths
Paths ([String] -> Paths) -> (Text -> [String]) -> Text -> Paths
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[]) (String -> [String]) -> (Text -> String) -> Text -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) Parser GraphvizState Text
quotelessString
data ScaleType = UniformScale
| NoScale
| FillWidth
| FillHeight
| FillBoth
deriving (ScaleType -> ScaleType -> Bool
(ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool) -> Eq ScaleType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScaleType -> ScaleType -> Bool
== :: ScaleType -> ScaleType -> Bool
$c/= :: ScaleType -> ScaleType -> Bool
/= :: ScaleType -> ScaleType -> Bool
Eq, Eq ScaleType
Eq ScaleType =>
(ScaleType -> ScaleType -> Ordering)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> Bool)
-> (ScaleType -> ScaleType -> ScaleType)
-> (ScaleType -> ScaleType -> ScaleType)
-> Ord ScaleType
ScaleType -> ScaleType -> Bool
ScaleType -> ScaleType -> Ordering
ScaleType -> ScaleType -> ScaleType
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
$ccompare :: ScaleType -> ScaleType -> Ordering
compare :: ScaleType -> ScaleType -> Ordering
$c< :: ScaleType -> ScaleType -> Bool
< :: ScaleType -> ScaleType -> Bool
$c<= :: ScaleType -> ScaleType -> Bool
<= :: ScaleType -> ScaleType -> Bool
$c> :: ScaleType -> ScaleType -> Bool
> :: ScaleType -> ScaleType -> Bool
$c>= :: ScaleType -> ScaleType -> Bool
>= :: ScaleType -> ScaleType -> Bool
$cmax :: ScaleType -> ScaleType -> ScaleType
max :: ScaleType -> ScaleType -> ScaleType
$cmin :: ScaleType -> ScaleType -> ScaleType
min :: ScaleType -> ScaleType -> ScaleType
Ord, ScaleType
ScaleType -> ScaleType -> Bounded ScaleType
forall a. a -> a -> Bounded a
$cminBound :: ScaleType
minBound :: ScaleType
$cmaxBound :: ScaleType
maxBound :: ScaleType
Bounded, Int -> ScaleType
ScaleType -> Int
ScaleType -> [ScaleType]
ScaleType -> ScaleType
ScaleType -> ScaleType -> [ScaleType]
ScaleType -> ScaleType -> ScaleType -> [ScaleType]
(ScaleType -> ScaleType)
-> (ScaleType -> ScaleType)
-> (Int -> ScaleType)
-> (ScaleType -> Int)
-> (ScaleType -> [ScaleType])
-> (ScaleType -> ScaleType -> [ScaleType])
-> (ScaleType -> ScaleType -> [ScaleType])
-> (ScaleType -> ScaleType -> ScaleType -> [ScaleType])
-> Enum ScaleType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: ScaleType -> ScaleType
succ :: ScaleType -> ScaleType
$cpred :: ScaleType -> ScaleType
pred :: ScaleType -> ScaleType
$ctoEnum :: Int -> ScaleType
toEnum :: Int -> ScaleType
$cfromEnum :: ScaleType -> Int
fromEnum :: ScaleType -> Int
$cenumFrom :: ScaleType -> [ScaleType]
enumFrom :: ScaleType -> [ScaleType]
$cenumFromThen :: ScaleType -> ScaleType -> [ScaleType]
enumFromThen :: ScaleType -> ScaleType -> [ScaleType]
$cenumFromTo :: ScaleType -> ScaleType -> [ScaleType]
enumFromTo :: ScaleType -> ScaleType -> [ScaleType]
$cenumFromThenTo :: ScaleType -> ScaleType -> ScaleType -> [ScaleType]
enumFromThenTo :: ScaleType -> ScaleType -> ScaleType -> [ScaleType]
Enum, Int -> ScaleType -> ShowS
[ScaleType] -> ShowS
ScaleType -> String
(Int -> ScaleType -> ShowS)
-> (ScaleType -> String)
-> ([ScaleType] -> ShowS)
-> Show ScaleType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScaleType -> ShowS
showsPrec :: Int -> ScaleType -> ShowS
$cshow :: ScaleType -> String
show :: ScaleType -> String
$cshowList :: [ScaleType] -> ShowS
showList :: [ScaleType] -> ShowS
Show, ReadPrec [ScaleType]
ReadPrec ScaleType
Int -> ReadS ScaleType
ReadS [ScaleType]
(Int -> ReadS ScaleType)
-> ReadS [ScaleType]
-> ReadPrec ScaleType
-> ReadPrec [ScaleType]
-> Read ScaleType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScaleType
readsPrec :: Int -> ReadS ScaleType
$creadList :: ReadS [ScaleType]
readList :: ReadS [ScaleType]
$creadPrec :: ReadPrec ScaleType
readPrec :: ReadPrec ScaleType
$creadListPrec :: ReadPrec [ScaleType]
readListPrec :: ReadPrec [ScaleType]
Read)
instance PrintDot ScaleType where
unqtDot :: ScaleType -> DotCode
unqtDot ScaleType
UniformScale = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot ScaleType
NoScale = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
False
unqtDot ScaleType
FillWidth = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"width"
unqtDot ScaleType
FillHeight = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"height"
unqtDot ScaleType
FillBoth = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"both"
instance ParseDot ScaleType where
parseUnqt :: Parse ScaleType
parseUnqt = [Parse ScaleType] -> Parse ScaleType
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ ScaleType -> String -> Parse ScaleType
forall a. a -> String -> Parse a
stringRep ScaleType
UniformScale String
"true"
, ScaleType -> String -> Parse ScaleType
forall a. a -> String -> Parse a
stringRep ScaleType
NoScale String
"false"
, ScaleType -> String -> Parse ScaleType
forall a. a -> String -> Parse a
stringRep ScaleType
FillWidth String
"width"
, ScaleType -> String -> Parse ScaleType
forall a. a -> String -> Parse a
stringRep ScaleType
FillHeight String
"height"
, ScaleType -> String -> Parse ScaleType
forall a. a -> String -> Parse a
stringRep ScaleType
FillBoth String
"both"
]
data Justification = JLeft
| JRight
| JCenter
deriving (Justification -> Justification -> Bool
(Justification -> Justification -> Bool)
-> (Justification -> Justification -> Bool) -> Eq Justification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Justification -> Justification -> Bool
== :: Justification -> Justification -> Bool
$c/= :: Justification -> Justification -> Bool
/= :: Justification -> Justification -> Bool
Eq, Eq Justification
Eq Justification =>
(Justification -> Justification -> Ordering)
-> (Justification -> Justification -> Bool)
-> (Justification -> Justification -> Bool)
-> (Justification -> Justification -> Bool)
-> (Justification -> Justification -> Bool)
-> (Justification -> Justification -> Justification)
-> (Justification -> Justification -> Justification)
-> Ord Justification
Justification -> Justification -> Bool
Justification -> Justification -> Ordering
Justification -> Justification -> Justification
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
$ccompare :: Justification -> Justification -> Ordering
compare :: Justification -> Justification -> Ordering
$c< :: Justification -> Justification -> Bool
< :: Justification -> Justification -> Bool
$c<= :: Justification -> Justification -> Bool
<= :: Justification -> Justification -> Bool
$c> :: Justification -> Justification -> Bool
> :: Justification -> Justification -> Bool
$c>= :: Justification -> Justification -> Bool
>= :: Justification -> Justification -> Bool
$cmax :: Justification -> Justification -> Justification
max :: Justification -> Justification -> Justification
$cmin :: Justification -> Justification -> Justification
min :: Justification -> Justification -> Justification
Ord, Justification
Justification -> Justification -> Bounded Justification
forall a. a -> a -> Bounded a
$cminBound :: Justification
minBound :: Justification
$cmaxBound :: Justification
maxBound :: Justification
Bounded, Int -> Justification
Justification -> Int
Justification -> [Justification]
Justification -> Justification
Justification -> Justification -> [Justification]
Justification -> Justification -> Justification -> [Justification]
(Justification -> Justification)
-> (Justification -> Justification)
-> (Int -> Justification)
-> (Justification -> Int)
-> (Justification -> [Justification])
-> (Justification -> Justification -> [Justification])
-> (Justification -> Justification -> [Justification])
-> (Justification
-> Justification -> Justification -> [Justification])
-> Enum Justification
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Justification -> Justification
succ :: Justification -> Justification
$cpred :: Justification -> Justification
pred :: Justification -> Justification
$ctoEnum :: Int -> Justification
toEnum :: Int -> Justification
$cfromEnum :: Justification -> Int
fromEnum :: Justification -> Int
$cenumFrom :: Justification -> [Justification]
enumFrom :: Justification -> [Justification]
$cenumFromThen :: Justification -> Justification -> [Justification]
enumFromThen :: Justification -> Justification -> [Justification]
$cenumFromTo :: Justification -> Justification -> [Justification]
enumFromTo :: Justification -> Justification -> [Justification]
$cenumFromThenTo :: Justification -> Justification -> Justification -> [Justification]
enumFromThenTo :: Justification -> Justification -> Justification -> [Justification]
Enum, Int -> Justification -> ShowS
[Justification] -> ShowS
Justification -> String
(Int -> Justification -> ShowS)
-> (Justification -> String)
-> ([Justification] -> ShowS)
-> Show Justification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Justification -> ShowS
showsPrec :: Int -> Justification -> ShowS
$cshow :: Justification -> String
show :: Justification -> String
$cshowList :: [Justification] -> ShowS
showList :: [Justification] -> ShowS
Show, ReadPrec [Justification]
ReadPrec Justification
Int -> ReadS Justification
ReadS [Justification]
(Int -> ReadS Justification)
-> ReadS [Justification]
-> ReadPrec Justification
-> ReadPrec [Justification]
-> Read Justification
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Justification
readsPrec :: Int -> ReadS Justification
$creadList :: ReadS [Justification]
readList :: ReadS [Justification]
$creadPrec :: ReadPrec Justification
readPrec :: ReadPrec Justification
$creadListPrec :: ReadPrec [Justification]
readListPrec :: ReadPrec [Justification]
Read)
instance PrintDot Justification where
unqtDot :: Justification -> DotCode
unqtDot Justification
JLeft = Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'l'
unqtDot Justification
JRight = Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'r'
unqtDot Justification
JCenter = Char -> DotCode
forall (m :: * -> *). Applicative m => Char -> m Doc
char Char
'c'
instance ParseDot Justification where
parseUnqt :: Parse Justification
parseUnqt = [Parse Justification] -> Parse Justification
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Justification -> [String] -> Parse Justification
forall a. a -> [String] -> Parse a
stringReps Justification
JLeft [String
"left", String
"l"]
, Justification -> [String] -> Parse Justification
forall a. a -> [String] -> Parse a
stringReps Justification
JRight [String
"right", String
"r"]
, Justification -> [String] -> Parse Justification
forall a. a -> [String] -> Parse a
stringReps Justification
JCenter [String
"center", String
"centre", String
"c"]
]
data Ratios = AspectRatio Double
| FillRatio
| CompressRatio
| ExpandRatio
| AutoRatio
deriving (Ratios -> Ratios -> Bool
(Ratios -> Ratios -> Bool)
-> (Ratios -> Ratios -> Bool) -> Eq Ratios
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ratios -> Ratios -> Bool
== :: Ratios -> Ratios -> Bool
$c/= :: Ratios -> Ratios -> Bool
/= :: Ratios -> Ratios -> Bool
Eq, Eq Ratios
Eq Ratios =>
(Ratios -> Ratios -> Ordering)
-> (Ratios -> Ratios -> Bool)
-> (Ratios -> Ratios -> Bool)
-> (Ratios -> Ratios -> Bool)
-> (Ratios -> Ratios -> Bool)
-> (Ratios -> Ratios -> Ratios)
-> (Ratios -> Ratios -> Ratios)
-> Ord Ratios
Ratios -> Ratios -> Bool
Ratios -> Ratios -> Ordering
Ratios -> Ratios -> Ratios
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
$ccompare :: Ratios -> Ratios -> Ordering
compare :: Ratios -> Ratios -> Ordering
$c< :: Ratios -> Ratios -> Bool
< :: Ratios -> Ratios -> Bool
$c<= :: Ratios -> Ratios -> Bool
<= :: Ratios -> Ratios -> Bool
$c> :: Ratios -> Ratios -> Bool
> :: Ratios -> Ratios -> Bool
$c>= :: Ratios -> Ratios -> Bool
>= :: Ratios -> Ratios -> Bool
$cmax :: Ratios -> Ratios -> Ratios
max :: Ratios -> Ratios -> Ratios
$cmin :: Ratios -> Ratios -> Ratios
min :: Ratios -> Ratios -> Ratios
Ord, Int -> Ratios -> ShowS
[Ratios] -> ShowS
Ratios -> String
(Int -> Ratios -> ShowS)
-> (Ratios -> String) -> ([Ratios] -> ShowS) -> Show Ratios
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ratios -> ShowS
showsPrec :: Int -> Ratios -> ShowS
$cshow :: Ratios -> String
show :: Ratios -> String
$cshowList :: [Ratios] -> ShowS
showList :: [Ratios] -> ShowS
Show, ReadPrec [Ratios]
ReadPrec Ratios
Int -> ReadS Ratios
ReadS [Ratios]
(Int -> ReadS Ratios)
-> ReadS [Ratios]
-> ReadPrec Ratios
-> ReadPrec [Ratios]
-> Read Ratios
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Ratios
readsPrec :: Int -> ReadS Ratios
$creadList :: ReadS [Ratios]
readList :: ReadS [Ratios]
$creadPrec :: ReadPrec Ratios
readPrec :: ReadPrec Ratios
$creadListPrec :: ReadPrec [Ratios]
readListPrec :: ReadPrec [Ratios]
Read)
instance PrintDot Ratios where
unqtDot :: Ratios -> DotCode
unqtDot (AspectRatio Double
r) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
r
unqtDot Ratios
FillRatio = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"fill"
unqtDot Ratios
CompressRatio = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"compress"
unqtDot Ratios
ExpandRatio = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"expand"
unqtDot Ratios
AutoRatio = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"auto"
toDot :: Ratios -> DotCode
toDot (AspectRatio Double
r) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Double
r
toDot Ratios
r = Ratios -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Ratios
r
instance ParseDot Ratios where
parseUnqt :: Parse Ratios
parseUnqt = Bool -> Parse Ratios
parseRatio Bool
True
parse :: Parse Ratios
parse = Parse Ratios -> Parse Ratios
forall a. Parse a -> Parse a
quotedParse Parse Ratios
forall a. ParseDot a => Parse a
parseUnqt Parse Ratios -> Parse Ratios -> Parse Ratios
forall a.
Parser GraphvizState a
-> Parser GraphvizState a -> Parser GraphvizState a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parse Ratios
parseRatio Bool
False
parseRatio :: Bool -> Parse Ratios
parseRatio :: Bool -> Parse Ratios
parseRatio Bool
q = [Parse Ratios] -> Parse Ratios
forall (p :: * -> *) a. PolyParse p => [p a] -> p a
oneOf [ Double -> Ratios
AspectRatio (Double -> Ratios) -> Parser GraphvizState Double -> Parse Ratios
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> Parser GraphvizState Double
parseSignedFloat Bool
q
, Ratios -> String -> Parse Ratios
forall a. a -> String -> Parse a
stringRep Ratios
FillRatio String
"fill"
, Ratios -> String -> Parse Ratios
forall a. a -> String -> Parse a
stringRep Ratios
CompressRatio String
"compress"
, Ratios -> String -> Parse Ratios
forall a. a -> String -> Parse a
stringRep Ratios
ExpandRatio String
"expand"
, Ratios -> String -> Parse Ratios
forall a. a -> String -> Parse a
stringRep Ratios
AutoRatio String
"auto"
]
data Number = Int Int
| Dbl Double
deriving (Number -> Number -> Bool
(Number -> Number -> Bool)
-> (Number -> Number -> Bool) -> Eq Number
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Number -> Number -> Bool
== :: Number -> Number -> Bool
$c/= :: Number -> Number -> Bool
/= :: Number -> Number -> Bool
Eq, Eq Number
Eq Number =>
(Number -> Number -> Ordering)
-> (Number -> Number -> Bool)
-> (Number -> Number -> Bool)
-> (Number -> Number -> Bool)
-> (Number -> Number -> Bool)
-> (Number -> Number -> Number)
-> (Number -> Number -> Number)
-> Ord Number
Number -> Number -> Bool
Number -> Number -> Ordering
Number -> Number -> Number
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
$ccompare :: Number -> Number -> Ordering
compare :: Number -> Number -> Ordering
$c< :: Number -> Number -> Bool
< :: Number -> Number -> Bool
$c<= :: Number -> Number -> Bool
<= :: Number -> Number -> Bool
$c> :: Number -> Number -> Bool
> :: Number -> Number -> Bool
$c>= :: Number -> Number -> Bool
>= :: Number -> Number -> Bool
$cmax :: Number -> Number -> Number
max :: Number -> Number -> Number
$cmin :: Number -> Number -> Number
min :: Number -> Number -> Number
Ord, Int -> Number -> ShowS
[Number] -> ShowS
Number -> String
(Int -> Number -> ShowS)
-> (Number -> String) -> ([Number] -> ShowS) -> Show Number
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Number -> ShowS
showsPrec :: Int -> Number -> ShowS
$cshow :: Number -> String
show :: Number -> String
$cshowList :: [Number] -> ShowS
showList :: [Number] -> ShowS
Show, ReadPrec [Number]
ReadPrec Number
Int -> ReadS Number
ReadS [Number]
(Int -> ReadS Number)
-> ReadS [Number]
-> ReadPrec Number
-> ReadPrec [Number]
-> Read Number
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Number
readsPrec :: Int -> ReadS Number
$creadList :: ReadS [Number]
readList :: ReadS [Number]
$creadPrec :: ReadPrec Number
readPrec :: ReadPrec Number
$creadListPrec :: ReadPrec [Number]
readListPrec :: ReadPrec [Number]
Read)
instance PrintDot Number where
unqtDot :: Number -> DotCode
unqtDot (Int Int
i) = Int -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Int
i
unqtDot (Dbl Double
d) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
d
toDot :: Number -> DotCode
toDot (Int Int
i) = Int -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Int
i
toDot (Dbl Double
d) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Double
d
instance ParseDot Number where
parseUnqt :: Parse Number
parseUnqt = Bool -> Parse Number
parseNumber Bool
True
parse :: Parse Number
parse = Parse Number -> Parse Number
forall a. Parse a -> Parse a
quotedParse Parse Number
forall a. ParseDot a => Parse a
parseUnqt
Parse Number -> Parse Number -> Parse Number
forall a.
Parser GraphvizState a
-> Parser GraphvizState a -> Parser GraphvizState a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Bool -> Parse Number
parseNumber Bool
False
parseNumber :: Bool -> Parse Number
parseNumber :: Bool -> Parse Number
parseNumber Bool
q = Double -> Number
Dbl (Double -> Number) -> Parser GraphvizState Double -> Parse Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> Parser GraphvizState Double
parseStrictFloat Bool
q
Parse Number -> Parse Number -> Parse Number
forall a.
Parser GraphvizState a
-> Parser GraphvizState a -> Parser GraphvizState a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Int -> Number
Int (Int -> Number) -> Parser GraphvizState Int -> Parse Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Int
forall a. ParseDot a => Parse a
parseUnqt
data Normalized = IsNormalized
| NotNormalized
| NormalizedAngle Double
deriving (Normalized -> Normalized -> Bool
(Normalized -> Normalized -> Bool)
-> (Normalized -> Normalized -> Bool) -> Eq Normalized
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Normalized -> Normalized -> Bool
== :: Normalized -> Normalized -> Bool
$c/= :: Normalized -> Normalized -> Bool
/= :: Normalized -> Normalized -> Bool
Eq, Eq Normalized
Eq Normalized =>
(Normalized -> Normalized -> Ordering)
-> (Normalized -> Normalized -> Bool)
-> (Normalized -> Normalized -> Bool)
-> (Normalized -> Normalized -> Bool)
-> (Normalized -> Normalized -> Bool)
-> (Normalized -> Normalized -> Normalized)
-> (Normalized -> Normalized -> Normalized)
-> Ord Normalized
Normalized -> Normalized -> Bool
Normalized -> Normalized -> Ordering
Normalized -> Normalized -> Normalized
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
$ccompare :: Normalized -> Normalized -> Ordering
compare :: Normalized -> Normalized -> Ordering
$c< :: Normalized -> Normalized -> Bool
< :: Normalized -> Normalized -> Bool
$c<= :: Normalized -> Normalized -> Bool
<= :: Normalized -> Normalized -> Bool
$c> :: Normalized -> Normalized -> Bool
> :: Normalized -> Normalized -> Bool
$c>= :: Normalized -> Normalized -> Bool
>= :: Normalized -> Normalized -> Bool
$cmax :: Normalized -> Normalized -> Normalized
max :: Normalized -> Normalized -> Normalized
$cmin :: Normalized -> Normalized -> Normalized
min :: Normalized -> Normalized -> Normalized
Ord, Int -> Normalized -> ShowS
[Normalized] -> ShowS
Normalized -> String
(Int -> Normalized -> ShowS)
-> (Normalized -> String)
-> ([Normalized] -> ShowS)
-> Show Normalized
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Normalized -> ShowS
showsPrec :: Int -> Normalized -> ShowS
$cshow :: Normalized -> String
show :: Normalized -> String
$cshowList :: [Normalized] -> ShowS
showList :: [Normalized] -> ShowS
Show, ReadPrec [Normalized]
ReadPrec Normalized
Int -> ReadS Normalized
ReadS [Normalized]
(Int -> ReadS Normalized)
-> ReadS [Normalized]
-> ReadPrec Normalized
-> ReadPrec [Normalized]
-> Read Normalized
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Normalized
readsPrec :: Int -> ReadS Normalized
$creadList :: ReadS [Normalized]
readList :: ReadS [Normalized]
$creadPrec :: ReadPrec Normalized
readPrec :: ReadPrec Normalized
$creadListPrec :: ReadPrec [Normalized]
readListPrec :: ReadPrec [Normalized]
Read)
instance PrintDot Normalized where
unqtDot :: Normalized -> DotCode
unqtDot Normalized
IsNormalized = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot Normalized
NotNormalized = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
False
unqtDot (NormalizedAngle Double
a) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Double
a
toDot :: Normalized -> DotCode
toDot (NormalizedAngle Double
a) = Double -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Double
a
toDot Normalized
norm = Normalized -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Normalized
norm
instance ParseDot Normalized where
parseUnqt :: Parse Normalized
parseUnqt = Bool -> Parse Normalized
parseNormalized Bool
True
parse :: Parse Normalized
parse = Parse Normalized -> Parse Normalized
forall a. Parse a -> Parse a
quotedParse Parse Normalized
forall a. ParseDot a => Parse a
parseUnqt Parse Normalized -> Parse Normalized -> Parse Normalized
forall a.
Parser GraphvizState a
-> Parser GraphvizState a -> Parser GraphvizState a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parse Normalized
parseNormalized Bool
False
parseNormalized :: Bool -> Parse Normalized
parseNormalized :: Bool -> Parse Normalized
parseNormalized Bool
q = Double -> Normalized
NormalizedAngle (Double -> Normalized)
-> Parser GraphvizState Double -> Parse Normalized
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> Parser GraphvizState Double
parseSignedFloat Bool
q
Parse Normalized -> Parse Normalized -> Parse Normalized
forall a.
Parser GraphvizState a
-> Parser GraphvizState a -> Parser GraphvizState a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Normalized -> Normalized -> Bool -> Normalized
forall a. a -> a -> Bool -> a
bool Normalized
NotNormalized Normalized
IsNormalized (Bool -> Normalized)
-> Parser GraphvizState Bool -> Parse Normalized
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Bool
onlyBool
data NodeSize = GrowAsNeeded
| SetNodeSize
| SetShapeSize
deriving (NodeSize -> NodeSize -> Bool
(NodeSize -> NodeSize -> Bool)
-> (NodeSize -> NodeSize -> Bool) -> Eq NodeSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeSize -> NodeSize -> Bool
== :: NodeSize -> NodeSize -> Bool
$c/= :: NodeSize -> NodeSize -> Bool
/= :: NodeSize -> NodeSize -> Bool
Eq, Eq NodeSize
Eq NodeSize =>
(NodeSize -> NodeSize -> Ordering)
-> (NodeSize -> NodeSize -> Bool)
-> (NodeSize -> NodeSize -> Bool)
-> (NodeSize -> NodeSize -> Bool)
-> (NodeSize -> NodeSize -> Bool)
-> (NodeSize -> NodeSize -> NodeSize)
-> (NodeSize -> NodeSize -> NodeSize)
-> Ord NodeSize
NodeSize -> NodeSize -> Bool
NodeSize -> NodeSize -> Ordering
NodeSize -> NodeSize -> NodeSize
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
$ccompare :: NodeSize -> NodeSize -> Ordering
compare :: NodeSize -> NodeSize -> Ordering
$c< :: NodeSize -> NodeSize -> Bool
< :: NodeSize -> NodeSize -> Bool
$c<= :: NodeSize -> NodeSize -> Bool
<= :: NodeSize -> NodeSize -> Bool
$c> :: NodeSize -> NodeSize -> Bool
> :: NodeSize -> NodeSize -> Bool
$c>= :: NodeSize -> NodeSize -> Bool
>= :: NodeSize -> NodeSize -> Bool
$cmax :: NodeSize -> NodeSize -> NodeSize
max :: NodeSize -> NodeSize -> NodeSize
$cmin :: NodeSize -> NodeSize -> NodeSize
min :: NodeSize -> NodeSize -> NodeSize
Ord, NodeSize
NodeSize -> NodeSize -> Bounded NodeSize
forall a. a -> a -> Bounded a
$cminBound :: NodeSize
minBound :: NodeSize
$cmaxBound :: NodeSize
maxBound :: NodeSize
Bounded, Int -> NodeSize
NodeSize -> Int
NodeSize -> [NodeSize]
NodeSize -> NodeSize
NodeSize -> NodeSize -> [NodeSize]
NodeSize -> NodeSize -> NodeSize -> [NodeSize]
(NodeSize -> NodeSize)
-> (NodeSize -> NodeSize)
-> (Int -> NodeSize)
-> (NodeSize -> Int)
-> (NodeSize -> [NodeSize])
-> (NodeSize -> NodeSize -> [NodeSize])
-> (NodeSize -> NodeSize -> [NodeSize])
-> (NodeSize -> NodeSize -> NodeSize -> [NodeSize])
-> Enum NodeSize
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: NodeSize -> NodeSize
succ :: NodeSize -> NodeSize
$cpred :: NodeSize -> NodeSize
pred :: NodeSize -> NodeSize
$ctoEnum :: Int -> NodeSize
toEnum :: Int -> NodeSize
$cfromEnum :: NodeSize -> Int
fromEnum :: NodeSize -> Int
$cenumFrom :: NodeSize -> [NodeSize]
enumFrom :: NodeSize -> [NodeSize]
$cenumFromThen :: NodeSize -> NodeSize -> [NodeSize]
enumFromThen :: NodeSize -> NodeSize -> [NodeSize]
$cenumFromTo :: NodeSize -> NodeSize -> [NodeSize]
enumFromTo :: NodeSize -> NodeSize -> [NodeSize]
$cenumFromThenTo :: NodeSize -> NodeSize -> NodeSize -> [NodeSize]
enumFromThenTo :: NodeSize -> NodeSize -> NodeSize -> [NodeSize]
Enum, Int -> NodeSize -> ShowS
[NodeSize] -> ShowS
NodeSize -> String
(Int -> NodeSize -> ShowS)
-> (NodeSize -> String) -> ([NodeSize] -> ShowS) -> Show NodeSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NodeSize -> ShowS
showsPrec :: Int -> NodeSize -> ShowS
$cshow :: NodeSize -> String
show :: NodeSize -> String
$cshowList :: [NodeSize] -> ShowS
showList :: [NodeSize] -> ShowS
Show, ReadPrec [NodeSize]
ReadPrec NodeSize
Int -> ReadS NodeSize
ReadS [NodeSize]
(Int -> ReadS NodeSize)
-> ReadS [NodeSize]
-> ReadPrec NodeSize
-> ReadPrec [NodeSize]
-> Read NodeSize
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NodeSize
readsPrec :: Int -> ReadS NodeSize
$creadList :: ReadS [NodeSize]
readList :: ReadS [NodeSize]
$creadPrec :: ReadPrec NodeSize
readPrec :: ReadPrec NodeSize
$creadListPrec :: ReadPrec [NodeSize]
readListPrec :: ReadPrec [NodeSize]
Read)
instance PrintDot NodeSize where
unqtDot :: NodeSize -> DotCode
unqtDot NodeSize
GrowAsNeeded = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
False
unqtDot NodeSize
SetNodeSize = Bool -> DotCode
forall a. PrintDot a => a -> DotCode
unqtDot Bool
True
unqtDot NodeSize
SetShapeSize = Text -> DotCode
forall (m :: * -> *). Applicative m => Text -> m Doc
text Text
"shape"
instance ParseDot NodeSize where
parseUnqt :: Parse NodeSize
parseUnqt = NodeSize -> NodeSize -> Bool -> NodeSize
forall a. a -> a -> Bool -> a
bool NodeSize
GrowAsNeeded NodeSize
SetNodeSize (Bool -> NodeSize) -> Parser GraphvizState Bool -> Parse NodeSize
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GraphvizState Bool
forall a. ParseDot a => Parse a
parseUnqt
Parse NodeSize -> Parse NodeSize -> Parse NodeSize
forall a.
Parser GraphvizState a
-> Parser GraphvizState a -> Parser GraphvizState a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
NodeSize -> String -> Parse NodeSize
forall a. a -> String -> Parse a
stringRep NodeSize
SetShapeSize String
"shape"