{-# LANGUAGE CPP, OverloadedStrings #-}
module Data.GraphViz.Attributes.Complete
(
Attribute(..)
, Attributes
, sameAttribute
, defaultAttributeValue
, rmUnwantedAttributes
, usedByGraphs
, usedBySubGraphs
, usedByClusters
, usedByNodes
, usedByEdges
, validUnknown
, AttributeName
, CustomAttribute
, customAttribute
, isCustom
, isSpecifiedCustom
, customValue
, customName
, findCustoms
, findSpecifiedCustom
, deleteCustomAttributes
, deleteSpecifiedCustom
, module Data.GraphViz.Attributes.Colors
, Number (..)
, EscString
, Label(..)
, VerticalPlacement(..)
, LabelScheme(..)
, SVGFontNames(..)
, RecordFields
, RecordField(..)
, Rect(..)
, Justification(..)
, Shape(..)
, Paths(..)
, ScaleType(..)
, NodeSize(..)
, DirType(..)
, EdgeType(..)
, PortName(..)
, PortPos(..)
, CompassPoint(..)
, ArrowType(..)
, ArrowShape(..)
, ArrowModifier(..)
, ArrowFill(..)
, ArrowSide(..)
, noMods
, openMod
, Point(..)
, createPoint
, Pos(..)
, Spline(..)
, DPoint(..)
, Normalized (..)
, GraphvizCommand(..)
, GraphSize(..)
, ClusterMode(..)
, Model(..)
, Overlap(..)
, Root(..)
, Order(..)
, OutputMode(..)
, Pack(..)
, PackMode(..)
, PageDir(..)
, QuadType(..)
, RankType(..)
, RankDir(..)
, StartType(..)
, ViewPort(..)
, FocusType(..)
, Ratios(..)
, ModeType(..)
, DEConstraints(..)
, LayerSep(..)
, LayerListSep(..)
, LayerRange
, LayerRangeElem(..)
, LayerID(..)
, LayerList(..)
, SmoothType(..)
, STStyle(..)
, StyleItem(..)
, StyleName(..)
) where
import Data.GraphViz.Attributes.Arrows
import Data.GraphViz.Attributes.Colors
import Data.GraphViz.Attributes.Colors.X11 (X11Color(Black))
import Data.GraphViz.Attributes.Internal
import Data.GraphViz.Attributes.Values
import Data.GraphViz.Commands.Available
import Data.GraphViz.Exception (GraphvizException(NotCustomAttr),
throw)
import Data.GraphViz.Internal.State (getsGS, parseStrictly)
import Data.GraphViz.Internal.Util (bool, isIDString, keywords,
restIDString)
import Data.GraphViz.Parsing
import Data.GraphViz.Printing
import Data.List (partition)
import Data.Maybe (isNothing)
import qualified Data.Set as S
import Data.Text.Lazy (Text)
import qualified Data.Text.Lazy as T
import Data.Version (Version(..))
import Data.Word (Word16)
#if !MIN_VERSION_base (4,13,0)
import Data.Monoid ((<>))
#endif
data Attribute
= Damping Double
| K Double
| URL EscString
| Area Double
| ArrowHead ArrowType
| ArrowSize Double
| ArrowTail ArrowType
| Background Text
| BoundingBox Rect
| BgColor ColorList
| Center Bool
| ClusterRank ClusterMode
| Color ColorList
| ColorScheme ColorScheme
| Text
| Compound Bool
| Concentrate Bool
| Constraint Bool
| Decorate Bool
| DefaultDist Double
| Dim Int
| Dimen Int
| Dir DirType
| DirEdgeConstraints DEConstraints
| Distortion Double
| DPI Double
| EdgeURL EscString
| EdgeTarget EscString
| EdgeTooltip EscString
| Epsilon Double
| ESep DPoint
| FillColor ColorList
| FixedSize NodeSize
| FontColor Color
| FontName Text
| FontNames SVGFontNames
| FontPath Paths
| FontSize Double
| ForceLabels Bool
| GradientAngle Int
| Group Text
| HeadURL EscString
| Head_LP Point
| HeadClip Bool
| HeadLabel Label
| HeadPort PortPos
| HeadTarget EscString
| HeadTooltip EscString
| Height Double
| ID EscString
| Image Text
| ImagePath Paths
| ImageScale ScaleType
| InputScale Double
| Label Label
| LabelURL EscString
| LabelScheme LabelScheme
| LabelAngle Double
| LabelDistance Double
| LabelFloat Bool
| LabelFontColor Color
| LabelFontName Text
| LabelFontSize Double
| LabelJust Justification
| LabelLoc VerticalPlacement
| LabelTarget EscString
| LabelTooltip EscString
| Landscape Bool
| Layer LayerRange
| LayerListSep LayerListSep
| Layers LayerList
| LayerSelect LayerRange
| LayerSep LayerSep
| Layout GraphvizCommand
| Len Double
| Levels Int
| LevelsGap Double
| LHead Text
| LHeight Double
| LPos Point
| LTail Text
| LWidth Double
| Margin DPoint
| MaxIter Int
| MCLimit Double
| MinDist Double
| MinLen Int
| Mode ModeType
| Model Model
| Mosek Bool
| NodeSep Double
| NoJustify Bool
| Normalize Normalized
| NoTranslate Bool
| Nslimit Double
| Nslimit1 Double
| Ordering Order
| Orientation Double
| OutputOrder OutputMode
| Overlap Overlap
| OverlapScaling Double
| OverlapShrink Bool
| Pack Pack
| PackMode PackMode
| Pad DPoint
| Page Point
| PageDir PageDir
| PenColor Color
| PenWidth Double
| Peripheries Int
| Pin Bool
| Pos Pos
| QuadTree QuadType
| Quantum Double
| Rank RankType
| RankDir RankDir
| RankSep [Double]
| Ratio Ratios
| Rects [Rect]
| Regular Bool
| ReMinCross Bool
| RepulsiveForce Double
| Root Root
| Rotate Int
| Rotation Double
| SameHead Text
| SameTail Text
| SamplePoints Int
| Scale DPoint
| SearchSize Int
| Sep DPoint
| Shape Shape
| ShowBoxes Int
| Sides Int
| Size GraphSize
| Skew Double
| Smoothing SmoothType
| SortV Word16
| Splines EdgeType
| Start StartType
| Style [StyleItem]
| StyleSheet Text
| TailURL EscString
| Tail_LP Point
| TailClip Bool
| TailLabel Label
| TailPort PortPos
| TailTarget EscString
| TailTooltip EscString
| Target EscString
| Tooltip EscString
| TrueColor Bool
| Vertices [Point]
| ViewPort ViewPort
| VoroMargin Double
| Weight Number
| Width Double
| XDotVersion Version
| XLabel Label
| XLP Point
| UnknownAttribute AttributeName Text
deriving (Attribute -> Attribute -> Bool
(Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool) -> Eq Attribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c== :: Attribute -> Attribute -> Bool
Eq, Eq Attribute
Eq Attribute
-> (Attribute -> Attribute -> Ordering)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Attribute)
-> (Attribute -> Attribute -> Attribute)
-> Ord Attribute
Attribute -> Attribute -> Bool
Attribute -> Attribute -> Ordering
Attribute -> Attribute -> Attribute
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Attribute -> Attribute -> Attribute
$cmin :: Attribute -> Attribute -> Attribute
max :: Attribute -> Attribute -> Attribute
$cmax :: Attribute -> Attribute -> Attribute
>= :: Attribute -> Attribute -> Bool
$c>= :: Attribute -> Attribute -> Bool
> :: Attribute -> Attribute -> Bool
$c> :: Attribute -> Attribute -> Bool
<= :: Attribute -> Attribute -> Bool
$c<= :: Attribute -> Attribute -> Bool
< :: Attribute -> Attribute -> Bool
$c< :: Attribute -> Attribute -> Bool
compare :: Attribute -> Attribute -> Ordering
$ccompare :: Attribute -> Attribute -> Ordering
$cp1Ord :: Eq Attribute
Ord, Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
(Int -> Attribute -> ShowS)
-> (Attribute -> String)
-> ([Attribute] -> ShowS)
-> Show Attribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> String
$cshow :: Attribute -> String
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show, ReadPrec [Attribute]
ReadPrec Attribute
Int -> ReadS Attribute
ReadS [Attribute]
(Int -> ReadS Attribute)
-> ReadS [Attribute]
-> ReadPrec Attribute
-> ReadPrec [Attribute]
-> Read Attribute
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Attribute]
$creadListPrec :: ReadPrec [Attribute]
readPrec :: ReadPrec Attribute
$creadPrec :: ReadPrec Attribute
readList :: ReadS [Attribute]
$creadList :: ReadS [Attribute]
readsPrec :: Int -> ReadS Attribute
$creadsPrec :: Int -> ReadS Attribute
Read)
type Attributes = [Attribute]
type AttributeName = Text
instance PrintDot Attribute where
unqtDot :: Attribute -> DotCode
unqtDot (Damping Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"Damping" Double
v
unqtDot (K Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"K" Double
v
unqtDot (URL Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"URL" Text
v
unqtDot (Area Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"area" Double
v
unqtDot (ArrowHead ArrowType
v) = Text -> ArrowType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"arrowhead" ArrowType
v
unqtDot (ArrowSize Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"arrowsize" Double
v
unqtDot (ArrowTail ArrowType
v) = Text -> ArrowType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"arrowtail" ArrowType
v
unqtDot (Background Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"_background" Text
v
unqtDot (BoundingBox Rect
v) = Text -> Rect -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"bb" Rect
v
unqtDot (BgColor ColorList
v) = Text -> ColorList -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"bgcolor" ColorList
v
unqtDot (Center Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"center" Bool
v
unqtDot (ClusterRank ClusterMode
v) = Text -> ClusterMode -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"clusterrank" ClusterMode
v
unqtDot (Color ColorList
v) = Text -> ColorList -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"color" ColorList
v
unqtDot (ColorScheme ColorScheme
v) = Text -> ColorScheme -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"colorscheme" ColorScheme
v
unqtDot (Comment Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"comment" Text
v
unqtDot (Compound Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"compound" Bool
v
unqtDot (Concentrate Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"concentrate" Bool
v
unqtDot (Constraint Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"constraint" Bool
v
unqtDot (Decorate Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"decorate" Bool
v
unqtDot (DefaultDist Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"defaultdist" Double
v
unqtDot (Dim Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"dim" Int
v
unqtDot (Dimen Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"dimen" Int
v
unqtDot (Dir DirType
v) = Text -> DirType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"dir" DirType
v
unqtDot (DirEdgeConstraints DEConstraints
v) = Text -> DEConstraints -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"diredgeconstraints" DEConstraints
v
unqtDot (Distortion Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"distortion" Double
v
unqtDot (DPI Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"dpi" Double
v
unqtDot (EdgeURL Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"edgeURL" Text
v
unqtDot (EdgeTarget Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"edgetarget" Text
v
unqtDot (EdgeTooltip Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"edgetooltip" Text
v
unqtDot (Epsilon Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"epsilon" Double
v
unqtDot (ESep DPoint
v) = Text -> DPoint -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"esep" DPoint
v
unqtDot (FillColor ColorList
v) = Text -> ColorList -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fillcolor" ColorList
v
unqtDot (FixedSize NodeSize
v) = Text -> NodeSize -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fixedsize" NodeSize
v
unqtDot (FontColor Color
v) = Text -> Color -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fontcolor" Color
v
unqtDot (FontName Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fontname" Text
v
unqtDot (FontNames SVGFontNames
v) = Text -> SVGFontNames -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fontnames" SVGFontNames
v
unqtDot (FontPath Paths
v) = Text -> Paths -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fontpath" Paths
v
unqtDot (FontSize Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"fontsize" Double
v
unqtDot (ForceLabels Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"forcelabels" Bool
v
unqtDot (GradientAngle Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"gradientangle" Int
v
unqtDot (Group Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"group" Text
v
unqtDot (HeadURL Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"headURL" Text
v
unqtDot (Head_LP Point
v) = Text -> Point -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"head_lp" Point
v
unqtDot (HeadClip Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"headclip" Bool
v
unqtDot (HeadLabel Label
v) = Text -> Label -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"headlabel" Label
v
unqtDot (HeadPort PortPos
v) = Text -> PortPos -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"headport" PortPos
v
unqtDot (HeadTarget Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"headtarget" Text
v
unqtDot (HeadTooltip Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"headtooltip" Text
v
unqtDot (Height Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"height" Double
v
unqtDot (ID Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"id" Text
v
unqtDot (Image Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"image" Text
v
unqtDot (ImagePath Paths
v) = Text -> Paths -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"imagepath" Paths
v
unqtDot (ImageScale ScaleType
v) = Text -> ScaleType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"imagescale" ScaleType
v
unqtDot (InputScale Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"inputscale" Double
v
unqtDot (Label Label
v) = Text -> Label -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"label" Label
v
unqtDot (LabelURL Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelURL" Text
v
unqtDot (LabelScheme LabelScheme
v) = Text -> LabelScheme -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"label_scheme" LabelScheme
v
unqtDot (LabelAngle Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelangle" Double
v
unqtDot (LabelDistance Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labeldistance" Double
v
unqtDot (LabelFloat Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelfloat" Bool
v
unqtDot (LabelFontColor Color
v) = Text -> Color -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelfontcolor" Color
v
unqtDot (LabelFontName Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelfontname" Text
v
unqtDot (LabelFontSize Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelfontsize" Double
v
unqtDot (LabelJust Justification
v) = Text -> Justification -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labeljust" Justification
v
unqtDot (LabelLoc VerticalPlacement
v) = Text -> VerticalPlacement -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labelloc" VerticalPlacement
v
unqtDot (LabelTarget Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labeltarget" Text
v
unqtDot (LabelTooltip Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"labeltooltip" Text
v
unqtDot (Landscape Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"landscape" Bool
v
unqtDot (Layer LayerRange
v) = Text -> LayerRange -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"layer" LayerRange
v
unqtDot (LayerListSep LayerListSep
v) = Text -> LayerListSep -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"layerlistsep" LayerListSep
v
unqtDot (Layers LayerList
v) = Text -> LayerList -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"layers" LayerList
v
unqtDot (LayerSelect LayerRange
v) = Text -> LayerRange -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"layerselect" LayerRange
v
unqtDot (LayerSep LayerSep
v) = Text -> LayerSep -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"layersep" LayerSep
v
unqtDot (Layout GraphvizCommand
v) = Text -> GraphvizCommand -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"layout" GraphvizCommand
v
unqtDot (Len Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"len" Double
v
unqtDot (Levels Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"levels" Int
v
unqtDot (LevelsGap Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"levelsgap" Double
v
unqtDot (LHead Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"lhead" Text
v
unqtDot (LHeight Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"LHeight" Double
v
unqtDot (LPos Point
v) = Text -> Point -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"lp" Point
v
unqtDot (LTail Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"ltail" Text
v
unqtDot (LWidth Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"lwidth" Double
v
unqtDot (Margin DPoint
v) = Text -> DPoint -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"margin" DPoint
v
unqtDot (MaxIter Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"maxiter" Int
v
unqtDot (MCLimit Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"mclimit" Double
v
unqtDot (MinDist Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"mindist" Double
v
unqtDot (MinLen Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"minlen" Int
v
unqtDot (Mode ModeType
v) = Text -> ModeType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"mode" ModeType
v
unqtDot (Model Model
v) = Text -> Model -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"model" Model
v
unqtDot (Mosek Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"mosek" Bool
v
unqtDot (NodeSep Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"nodesep" Double
v
unqtDot (NoJustify Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"nojustify" Bool
v
unqtDot (Normalize Normalized
v) = Text -> Normalized -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"normalize" Normalized
v
unqtDot (NoTranslate Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"notranslate" Bool
v
unqtDot (Nslimit Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"nslimit" Double
v
unqtDot (Nslimit1 Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"nslimit1" Double
v
unqtDot (Ordering Order
v) = Text -> Order -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"ordering" Order
v
unqtDot (Orientation Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"orientation" Double
v
unqtDot (OutputOrder OutputMode
v) = Text -> OutputMode -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"outputorder" OutputMode
v
unqtDot (Overlap Overlap
v) = Text -> Overlap -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"overlap" Overlap
v
unqtDot (OverlapScaling Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"overlap_scaling" Double
v
unqtDot (OverlapShrink Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"overlap_shrink" Bool
v
unqtDot (Pack Pack
v) = Text -> Pack -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"pack" Pack
v
unqtDot (PackMode PackMode
v) = Text -> PackMode -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"packmode" PackMode
v
unqtDot (Pad DPoint
v) = Text -> DPoint -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"pad" DPoint
v
unqtDot (Page Point
v) = Text -> Point -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"page" Point
v
unqtDot (PageDir PageDir
v) = Text -> PageDir -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"pagedir" PageDir
v
unqtDot (PenColor Color
v) = Text -> Color -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"pencolor" Color
v
unqtDot (PenWidth Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"penwidth" Double
v
unqtDot (Peripheries Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"peripheries" Int
v
unqtDot (Pin Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"pin" Bool
v
unqtDot (Pos Pos
v) = Text -> Pos -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"pos" Pos
v
unqtDot (QuadTree QuadType
v) = Text -> QuadType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"quadtree" QuadType
v
unqtDot (Quantum Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"quantum" Double
v
unqtDot (Rank RankType
v) = Text -> RankType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"rank" RankType
v
unqtDot (RankDir RankDir
v) = Text -> RankDir -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"rankdir" RankDir
v
unqtDot (RankSep [Double]
v) = Text -> [Double] -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"ranksep" [Double]
v
unqtDot (Ratio Ratios
v) = Text -> Ratios -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"ratio" Ratios
v
unqtDot (Rects [Rect]
v) = Text -> [Rect] -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"rects" [Rect]
v
unqtDot (Regular Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"regular" Bool
v
unqtDot (ReMinCross Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"remincross" Bool
v
unqtDot (RepulsiveForce Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"repulsiveforce" Double
v
unqtDot (Root Root
v) = Text -> Root -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"root" Root
v
unqtDot (Rotate Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"rotate" Int
v
unqtDot (Rotation Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"rotation" Double
v
unqtDot (SameHead Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"samehead" Text
v
unqtDot (SameTail Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"sametail" Text
v
unqtDot (SamplePoints Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"samplepoints" Int
v
unqtDot (Scale DPoint
v) = Text -> DPoint -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"scale" DPoint
v
unqtDot (SearchSize Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"searchsize" Int
v
unqtDot (Sep DPoint
v) = Text -> DPoint -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"sep" DPoint
v
unqtDot (Shape Shape
v) = Text -> Shape -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"shape" Shape
v
unqtDot (ShowBoxes Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"showboxes" Int
v
unqtDot (Sides Int
v) = Text -> Int -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"sides" Int
v
unqtDot (Size GraphSize
v) = Text -> GraphSize -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"size" GraphSize
v
unqtDot (Skew Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"skew" Double
v
unqtDot (Smoothing SmoothType
v) = Text -> SmoothType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"smoothing" SmoothType
v
unqtDot (SortV Word16
v) = Text -> Word16 -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"sortv" Word16
v
unqtDot (Splines EdgeType
v) = Text -> EdgeType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"splines" EdgeType
v
unqtDot (Start StartType
v) = Text -> StartType -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"start" StartType
v
unqtDot (Style [StyleItem]
v) = Text -> [StyleItem] -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"style" [StyleItem]
v
unqtDot (StyleSheet Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"stylesheet" Text
v
unqtDot (TailURL Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tailURL" Text
v
unqtDot (Tail_LP Point
v) = Text -> Point -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tail_lp" Point
v
unqtDot (TailClip Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tailclip" Bool
v
unqtDot (TailLabel Label
v) = Text -> Label -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"taillabel" Label
v
unqtDot (TailPort PortPos
v) = Text -> PortPos -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tailport" PortPos
v
unqtDot (TailTarget Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tailtarget" Text
v
unqtDot (TailTooltip Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tailtooltip" Text
v
unqtDot (Target Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"target" Text
v
unqtDot (Tooltip Text
v) = Text -> Text -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"tooltip" Text
v
unqtDot (TrueColor Bool
v) = Text -> Bool -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"truecolor" Bool
v
unqtDot (Vertices [Point]
v) = Text -> [Point] -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"vertices" [Point]
v
unqtDot (ViewPort ViewPort
v) = Text -> ViewPort -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"viewport" ViewPort
v
unqtDot (VoroMargin Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"voro_margin" Double
v
unqtDot (Weight Number
v) = Text -> Number -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"weight" Number
v
unqtDot (Width Double
v) = Text -> Double -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"width" Double
v
unqtDot (XDotVersion Version
v) = Text -> Version -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"xdotversion" Version
v
unqtDot (XLabel Label
v) = Text -> Label -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"xlabel" Label
v
unqtDot (XLP Point
v) = Text -> Point -> DotCode
forall a. PrintDot a => Text -> a -> DotCode
printField Text
"xlp" Point
v
unqtDot (UnknownAttribute Text
a Text
v) = Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
a DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> DotCode
forall (m :: * -> *). Applicative m => m Doc
equals DotCode -> DotCode -> DotCode
forall a. Semigroup a => a -> a -> a
<> Text -> DotCode
forall a. PrintDot a => a -> DotCode
toDot Text
v
listToDot :: [Attribute] -> DotCode
listToDot = [Attribute] -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot
instance ParseDot Attribute where
parseUnqt :: Parse Attribute
parseUnqt = [(String, Parse Attribute)] -> Parse Attribute
forall a. [(String, Parse a)] -> Parse a
stringParse ([[(String, Parse Attribute)]] -> [(String, Parse Attribute)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Damping String
"Damping"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
K String
"K"
, (Text -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Text -> Attribute
URL [String
"URL", String
"href"]
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Area String
"area"
, (ArrowType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ArrowType -> Attribute
ArrowHead String
"arrowhead"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
ArrowSize String
"arrowsize"
, (ArrowType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ArrowType -> Attribute
ArrowTail String
"arrowtail"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
Background String
"_background"
, (Rect -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Rect -> Attribute
BoundingBox String
"bb"
, (ColorList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorList -> Attribute
BgColor String
"bgcolor"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Center String
"center"
, (ClusterMode -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ClusterMode -> Attribute
ClusterRank String
"clusterrank"
, (ColorList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorList -> Attribute
Color String
"color"
, (ColorScheme -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorScheme -> Attribute
ColorScheme String
"colorscheme"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
Comment String
"comment"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Compound String
"compound"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Concentrate String
"concentrate"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Constraint String
"constraint"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Decorate String
"decorate"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
DefaultDist String
"defaultdist"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Dim String
"dim"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Dimen String
"dimen"
, (DirType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DirType -> Attribute
Dir String
"dir"
, (DEConstraints -> Attribute)
-> DEConstraints -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef DEConstraints -> Attribute
DirEdgeConstraints DEConstraints
EdgeConstraints String
"diredgeconstraints"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Distortion String
"distortion"
, (Double -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Double -> Attribute
DPI [String
"dpi", String
"resolution"]
, (Text -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Text -> Attribute
EdgeURL [String
"edgeURL", String
"edgehref"]
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
EdgeTarget String
"edgetarget"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
EdgeTooltip String
"edgetooltip"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Epsilon String
"epsilon"
, (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
ESep String
"esep"
, (ColorList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorList -> Attribute
FillColor String
"fillcolor"
, (NodeSize -> Attribute)
-> NodeSize -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef NodeSize -> Attribute
FixedSize NodeSize
SetNodeSize String
"fixedsize"
, (Color -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Color -> Attribute
FontColor String
"fontcolor"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
FontName String
"fontname"
, (SVGFontNames -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField SVGFontNames -> Attribute
FontNames String
"fontnames"
, (Paths -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Paths -> Attribute
FontPath String
"fontpath"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
FontSize String
"fontsize"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
ForceLabels String
"forcelabels"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
GradientAngle String
"gradientangle"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
Group String
"group"
, (Text -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Text -> Attribute
HeadURL [String
"headURL", String
"headhref"]
, (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
Head_LP String
"head_lp"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
HeadClip String
"headclip"
, (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
HeadLabel String
"headlabel"
, (PortPos -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PortPos -> Attribute
HeadPort String
"headport"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
HeadTarget String
"headtarget"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
HeadTooltip String
"headtooltip"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Height String
"height"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
ID String
"id"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
Image String
"image"
, (Paths -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Paths -> Attribute
ImagePath String
"imagepath"
, (ScaleType -> Attribute)
-> ScaleType -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef ScaleType -> Attribute
ImageScale ScaleType
UniformScale String
"imagescale"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
InputScale String
"inputscale"
, (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
Label String
"label"
, (Text -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Text -> Attribute
LabelURL [String
"labelURL", String
"labelhref"]
, (LabelScheme -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LabelScheme -> Attribute
LabelScheme String
"label_scheme"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LabelAngle String
"labelangle"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LabelDistance String
"labeldistance"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
LabelFloat String
"labelfloat"
, (Color -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Color -> Attribute
LabelFontColor String
"labelfontcolor"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
LabelFontName String
"labelfontname"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LabelFontSize String
"labelfontsize"
, (Justification -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Justification -> Attribute
LabelJust String
"labeljust"
, (VerticalPlacement -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField VerticalPlacement -> Attribute
LabelLoc String
"labelloc"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
LabelTarget String
"labeltarget"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
LabelTooltip String
"labeltooltip"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Landscape String
"landscape"
, (LayerRange -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerRange -> Attribute
Layer String
"layer"
, (LayerListSep -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerListSep -> Attribute
LayerListSep String
"layerlistsep"
, (LayerList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerList -> Attribute
Layers String
"layers"
, (LayerRange -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerRange -> Attribute
LayerSelect String
"layerselect"
, (LayerSep -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerSep -> Attribute
LayerSep String
"layersep"
, (GraphvizCommand -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField GraphvizCommand -> Attribute
Layout String
"layout"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Len String
"len"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Levels String
"levels"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LevelsGap String
"levelsgap"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
LHead String
"lhead"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LHeight String
"LHeight"
, (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
LPos String
"lp"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
LTail String
"ltail"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LWidth String
"lwidth"
, (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Margin String
"margin"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
MaxIter String
"maxiter"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
MCLimit String
"mclimit"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
MinDist String
"mindist"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
MinLen String
"minlen"
, (ModeType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ModeType -> Attribute
Mode String
"mode"
, (Model -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Model -> Attribute
Model String
"model"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Mosek String
"mosek"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
NodeSep String
"nodesep"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
NoJustify String
"nojustify"
, (Normalized -> Attribute)
-> Normalized -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Normalized -> Attribute
Normalize Normalized
IsNormalized String
"normalize"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
NoTranslate String
"notranslate"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Nslimit String
"nslimit"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Nslimit1 String
"nslimit1"
, (Order -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Order -> Attribute
Ordering String
"ordering"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Orientation String
"orientation"
, (OutputMode -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField OutputMode -> Attribute
OutputOrder String
"outputorder"
, (Overlap -> Attribute)
-> Overlap -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Overlap -> Attribute
Overlap Overlap
KeepOverlaps String
"overlap"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
OverlapScaling String
"overlap_scaling"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
OverlapShrink String
"overlap_shrink"
, (Pack -> Attribute)
-> Pack -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Pack -> Attribute
Pack Pack
DoPack String
"pack"
, (PackMode -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PackMode -> Attribute
PackMode String
"packmode"
, (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Pad String
"pad"
, (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
Page String
"page"
, (PageDir -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PageDir -> Attribute
PageDir String
"pagedir"
, (Color -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Color -> Attribute
PenColor String
"pencolor"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
PenWidth String
"penwidth"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Peripheries String
"peripheries"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Pin String
"pin"
, (Pos -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Pos -> Attribute
Pos String
"pos"
, (QuadType -> Attribute)
-> QuadType -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef QuadType -> Attribute
QuadTree QuadType
NormalQT String
"quadtree"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Quantum String
"quantum"
, (RankType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField RankType -> Attribute
Rank String
"rank"
, (RankDir -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField RankDir -> Attribute
RankDir String
"rankdir"
, ([Double] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [Double] -> Attribute
RankSep String
"ranksep"
, (Ratios -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Ratios -> Attribute
Ratio String
"ratio"
, ([Rect] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [Rect] -> Attribute
Rects String
"rects"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Regular String
"regular"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
ReMinCross String
"remincross"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
RepulsiveForce String
"repulsiveforce"
, (Root -> Attribute)
-> Root -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Root -> Attribute
Root Root
IsCentral String
"root"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Rotate String
"rotate"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Rotation String
"rotation"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
SameHead String
"samehead"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
SameTail String
"sametail"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
SamplePoints String
"samplepoints"
, (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Scale String
"scale"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
SearchSize String
"searchsize"
, (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Sep String
"sep"
, (Shape -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Shape -> Attribute
Shape String
"shape"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
ShowBoxes String
"showboxes"
, (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Sides String
"sides"
, (GraphSize -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField GraphSize -> Attribute
Size String
"size"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Skew String
"skew"
, (SmoothType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField SmoothType -> Attribute
Smoothing String
"smoothing"
, (Word16 -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Word16 -> Attribute
SortV String
"sortv"
, (EdgeType -> Attribute)
-> EdgeType -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef EdgeType -> Attribute
Splines EdgeType
SplineEdges String
"splines"
, (StartType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField StartType -> Attribute
Start String
"start"
, ([StyleItem] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [StyleItem] -> Attribute
Style String
"style"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
StyleSheet String
"stylesheet"
, (Text -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Text -> Attribute
TailURL [String
"tailURL", String
"tailhref"]
, (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
Tail_LP String
"tail_lp"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
TailClip String
"tailclip"
, (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
TailLabel String
"taillabel"
, (PortPos -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PortPos -> Attribute
TailPort String
"tailport"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
TailTarget String
"tailtarget"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
TailTooltip String
"tailtooltip"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
Target String
"target"
, (Text -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Text -> Attribute
Tooltip String
"tooltip"
, (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
TrueColor String
"truecolor"
, ([Point] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [Point] -> Attribute
Vertices String
"vertices"
, (ViewPort -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ViewPort -> Attribute
ViewPort String
"viewport"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
VoroMargin String
"voro_margin"
, (Number -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Number -> Attribute
Weight String
"weight"
, (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Width String
"width"
, (Version -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Version -> Attribute
XDotVersion String
"xdotversion"
, (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
XLabel String
"xlabel"
, (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
XLP String
"xlp"
])
Parse Attribute -> Parse Attribute -> Parse Attribute
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
do Text
attrName <- Parse Text
stringBlock
String -> (Text -> Attribute) -> Parse Attribute
forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
liftEqParse (String
"UnknownAttribute (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
attrName String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")")
(Text -> Text -> Attribute
UnknownAttribute Text
attrName)
parse :: Parse Attribute
parse = Parse Attribute
forall a. ParseDot a => Parse a
parseUnqt
parseList :: Parse [Attribute]
parseList = Parse [Attribute]
forall a. ParseDot a => Parse [a]
parseUnqtList
usedByGraphs :: Attribute -> Bool
usedByGraphs :: Attribute -> Bool
usedByGraphs Damping{} = Bool
True
usedByGraphs K{} = Bool
True
usedByGraphs URL{} = Bool
True
usedByGraphs Background{} = Bool
True
usedByGraphs BoundingBox{} = Bool
True
usedByGraphs BgColor{} = Bool
True
usedByGraphs Center{} = Bool
True
usedByGraphs ClusterRank{} = Bool
True
usedByGraphs ColorScheme{} = Bool
True
usedByGraphs Comment{} = Bool
True
usedByGraphs Compound{} = Bool
True
usedByGraphs Concentrate{} = Bool
True
usedByGraphs DefaultDist{} = Bool
True
usedByGraphs Dim{} = Bool
True
usedByGraphs Dimen{} = Bool
True
usedByGraphs DirEdgeConstraints{} = Bool
True
usedByGraphs DPI{} = Bool
True
usedByGraphs Epsilon{} = Bool
True
usedByGraphs ESep{} = Bool
True
usedByGraphs FontColor{} = Bool
True
usedByGraphs FontName{} = Bool
True
usedByGraphs FontNames{} = Bool
True
usedByGraphs FontPath{} = Bool
True
usedByGraphs FontSize{} = Bool
True
usedByGraphs ForceLabels{} = Bool
True
usedByGraphs GradientAngle{} = Bool
True
usedByGraphs ID{} = Bool
True
usedByGraphs ImagePath{} = Bool
True
usedByGraphs Label{} = Bool
True
usedByGraphs LabelScheme{} = Bool
True
usedByGraphs LabelJust{} = Bool
True
usedByGraphs LabelLoc{} = Bool
True
usedByGraphs Landscape{} = Bool
True
usedByGraphs LayerListSep{} = Bool
True
usedByGraphs Layers{} = Bool
True
usedByGraphs LayerSelect{} = Bool
True
usedByGraphs LayerSep{} = Bool
True
usedByGraphs Layout{} = Bool
True
usedByGraphs Levels{} = Bool
True
usedByGraphs LevelsGap{} = Bool
True
usedByGraphs LHeight{} = Bool
True
usedByGraphs LPos{} = Bool
True
usedByGraphs LWidth{} = Bool
True
usedByGraphs Margin{} = Bool
True
usedByGraphs MaxIter{} = Bool
True
usedByGraphs MCLimit{} = Bool
True
usedByGraphs MinDist{} = Bool
True
usedByGraphs Mode{} = Bool
True
usedByGraphs Model{} = Bool
True
usedByGraphs Mosek{} = Bool
True
usedByGraphs NodeSep{} = Bool
True
usedByGraphs NoJustify{} = Bool
True
usedByGraphs Normalize{} = Bool
True
usedByGraphs NoTranslate{} = Bool
True
usedByGraphs Nslimit{} = Bool
True
usedByGraphs Nslimit1{} = Bool
True
usedByGraphs Ordering{} = Bool
True
usedByGraphs OutputOrder{} = Bool
True
usedByGraphs Overlap{} = Bool
True
usedByGraphs OverlapScaling{} = Bool
True
usedByGraphs OverlapShrink{} = Bool
True
usedByGraphs Pack{} = Bool
True
usedByGraphs PackMode{} = Bool
True
usedByGraphs Pad{} = Bool
True
usedByGraphs Page{} = Bool
True
usedByGraphs PageDir{} = Bool
True
usedByGraphs QuadTree{} = Bool
True
usedByGraphs Quantum{} = Bool
True
usedByGraphs RankDir{} = Bool
True
usedByGraphs RankSep{} = Bool
True
usedByGraphs Ratio{} = Bool
True
usedByGraphs ReMinCross{} = Bool
True
usedByGraphs RepulsiveForce{} = Bool
True
usedByGraphs Root{} = Bool
True
usedByGraphs Rotate{} = Bool
True
usedByGraphs Rotation{} = Bool
True
usedByGraphs Scale{} = Bool
True
usedByGraphs SearchSize{} = Bool
True
usedByGraphs Sep{} = Bool
True
usedByGraphs ShowBoxes{} = Bool
True
usedByGraphs Size{} = Bool
True
usedByGraphs Smoothing{} = Bool
True
usedByGraphs SortV{} = Bool
True
usedByGraphs Splines{} = Bool
True
usedByGraphs Start{} = Bool
True
usedByGraphs Style{} = Bool
True
usedByGraphs StyleSheet{} = Bool
True
usedByGraphs Target{} = Bool
True
usedByGraphs TrueColor{} = Bool
True
usedByGraphs ViewPort{} = Bool
True
usedByGraphs VoroMargin{} = Bool
True
usedByGraphs XDotVersion{} = Bool
True
usedByGraphs UnknownAttribute{} = Bool
True
usedByGraphs Attribute
_ = Bool
False
usedByClusters :: Attribute -> Bool
usedByClusters :: Attribute -> Bool
usedByClusters K{} = Bool
True
usedByClusters URL{} = Bool
True
usedByClusters Area{} = Bool
True
usedByClusters BgColor{} = Bool
True
usedByClusters Color{} = Bool
True
usedByClusters ColorScheme{} = Bool
True
usedByClusters FillColor{} = Bool
True
usedByClusters FontColor{} = Bool
True
usedByClusters FontName{} = Bool
True
usedByClusters FontSize{} = Bool
True
usedByClusters GradientAngle{} = Bool
True
usedByClusters Label{} = Bool
True
usedByClusters LabelJust{} = Bool
True
usedByClusters LabelLoc{} = Bool
True
usedByClusters Layer{} = Bool
True
usedByClusters LHeight{} = Bool
True
usedByClusters LPos{} = Bool
True
usedByClusters LWidth{} = Bool
True
usedByClusters Margin{} = Bool
True
usedByClusters NoJustify{} = Bool
True
usedByClusters PenColor{} = Bool
True
usedByClusters PenWidth{} = Bool
True
usedByClusters Peripheries{} = Bool
True
usedByClusters Rank{} = Bool
True
usedByClusters SortV{} = Bool
True
usedByClusters Style{} = Bool
True
usedByClusters Target{} = Bool
True
usedByClusters Tooltip{} = Bool
True
usedByClusters UnknownAttribute{} = Bool
True
usedByClusters Attribute
_ = Bool
False
usedBySubGraphs :: Attribute -> Bool
usedBySubGraphs :: Attribute -> Bool
usedBySubGraphs Rank{} = Bool
True
usedBySubGraphs UnknownAttribute{} = Bool
True
usedBySubGraphs Attribute
_ = Bool
False
usedByNodes :: Attribute -> Bool
usedByNodes :: Attribute -> Bool
usedByNodes URL{} = Bool
True
usedByNodes Area{} = Bool
True
usedByNodes Color{} = Bool
True
usedByNodes ColorScheme{} = Bool
True
usedByNodes Comment{} = Bool
True
usedByNodes Distortion{} = Bool
True
usedByNodes FillColor{} = Bool
True
usedByNodes FixedSize{} = Bool
True
usedByNodes FontColor{} = Bool
True
usedByNodes FontName{} = Bool
True
usedByNodes FontSize{} = Bool
True
usedByNodes GradientAngle{} = Bool
True
usedByNodes Group{} = Bool
True
usedByNodes Height{} = Bool
True
usedByNodes ID{} = Bool
True
usedByNodes Image{} = Bool
True
usedByNodes ImageScale{} = Bool
True
usedByNodes InputScale{} = Bool
True
usedByNodes Label{} = Bool
True
usedByNodes LabelLoc{} = Bool
True
usedByNodes Layer{} = Bool
True
usedByNodes Margin{} = Bool
True
usedByNodes NoJustify{} = Bool
True
usedByNodes Ordering{} = Bool
True
usedByNodes Orientation{} = Bool
True
usedByNodes PenWidth{} = Bool
True
usedByNodes Peripheries{} = Bool
True
usedByNodes Pin{} = Bool
True
usedByNodes Pos{} = Bool
True
usedByNodes Rects{} = Bool
True
usedByNodes Regular{} = Bool
True
usedByNodes Root{} = Bool
True
usedByNodes SamplePoints{} = Bool
True
usedByNodes Shape{} = Bool
True
usedByNodes ShowBoxes{} = Bool
True
usedByNodes Sides{} = Bool
True
usedByNodes Skew{} = Bool
True
usedByNodes SortV{} = Bool
True
usedByNodes Style{} = Bool
True
usedByNodes Target{} = Bool
True
usedByNodes Tooltip{} = Bool
True
usedByNodes Vertices{} = Bool
True
usedByNodes Width{} = Bool
True
usedByNodes XLabel{} = Bool
True
usedByNodes XLP{} = Bool
True
usedByNodes UnknownAttribute{} = Bool
True
usedByNodes Attribute
_ = Bool
False
usedByEdges :: Attribute -> Bool
usedByEdges :: Attribute -> Bool
usedByEdges URL{} = Bool
True
usedByEdges ArrowHead{} = Bool
True
usedByEdges ArrowSize{} = Bool
True
usedByEdges ArrowTail{} = Bool
True
usedByEdges Color{} = Bool
True
usedByEdges ColorScheme{} = Bool
True
usedByEdges Comment{} = Bool
True
usedByEdges Constraint{} = Bool
True
usedByEdges Decorate{} = Bool
True
usedByEdges Dir{} = Bool
True
usedByEdges EdgeURL{} = Bool
True
usedByEdges EdgeTarget{} = Bool
True
usedByEdges EdgeTooltip{} = Bool
True
usedByEdges FillColor{} = Bool
True
usedByEdges FontColor{} = Bool
True
usedByEdges FontName{} = Bool
True
usedByEdges FontSize{} = Bool
True
usedByEdges HeadURL{} = Bool
True
usedByEdges Head_LP{} = Bool
True
usedByEdges HeadClip{} = Bool
True
usedByEdges HeadLabel{} = Bool
True
usedByEdges HeadPort{} = Bool
True
usedByEdges HeadTarget{} = Bool
True
usedByEdges HeadTooltip{} = Bool
True
usedByEdges ID{} = Bool
True
usedByEdges Label{} = Bool
True
usedByEdges LabelURL{} = Bool
True
usedByEdges LabelAngle{} = Bool
True
usedByEdges LabelDistance{} = Bool
True
usedByEdges LabelFloat{} = Bool
True
usedByEdges LabelFontColor{} = Bool
True
usedByEdges LabelFontName{} = Bool
True
usedByEdges LabelFontSize{} = Bool
True
usedByEdges LabelTarget{} = Bool
True
usedByEdges LabelTooltip{} = Bool
True
usedByEdges Layer{} = Bool
True
usedByEdges Len{} = Bool
True
usedByEdges LHead{} = Bool
True
usedByEdges LPos{} = Bool
True
usedByEdges LTail{} = Bool
True
usedByEdges MinLen{} = Bool
True
usedByEdges NoJustify{} = Bool
True
usedByEdges PenWidth{} = Bool
True
usedByEdges Pos{} = Bool
True
usedByEdges SameHead{} = Bool
True
usedByEdges SameTail{} = Bool
True
usedByEdges ShowBoxes{} = Bool
True
usedByEdges Style{} = Bool
True
usedByEdges TailURL{} = Bool
True
usedByEdges Tail_LP{} = Bool
True
usedByEdges TailClip{} = Bool
True
usedByEdges TailLabel{} = Bool
True
usedByEdges TailPort{} = Bool
True
usedByEdges TailTarget{} = Bool
True
usedByEdges TailTooltip{} = Bool
True
usedByEdges Target{} = Bool
True
usedByEdges Tooltip{} = Bool
True
usedByEdges Weight{} = Bool
True
usedByEdges XLabel{} = Bool
True
usedByEdges XLP{} = Bool
True
usedByEdges UnknownAttribute{} = Bool
True
usedByEdges Attribute
_ = Bool
False
sameAttribute :: Attribute -> Attribute -> Bool
sameAttribute :: Attribute -> Attribute -> Bool
sameAttribute Damping{} Damping{} = Bool
True
sameAttribute K{} K{} = Bool
True
sameAttribute URL{} URL{} = Bool
True
sameAttribute Area{} Area{} = Bool
True
sameAttribute ArrowHead{} ArrowHead{} = Bool
True
sameAttribute ArrowSize{} ArrowSize{} = Bool
True
sameAttribute ArrowTail{} ArrowTail{} = Bool
True
sameAttribute Background{} Background{} = Bool
True
sameAttribute BoundingBox{} BoundingBox{} = Bool
True
sameAttribute BgColor{} BgColor{} = Bool
True
sameAttribute Center{} Center{} = Bool
True
sameAttribute ClusterRank{} ClusterRank{} = Bool
True
sameAttribute Color{} Color{} = Bool
True
sameAttribute ColorScheme{} ColorScheme{} = Bool
True
sameAttribute Comment{} Comment{} = Bool
True
sameAttribute Compound{} Compound{} = Bool
True
sameAttribute Concentrate{} Concentrate{} = Bool
True
sameAttribute Constraint{} Constraint{} = Bool
True
sameAttribute Decorate{} Decorate{} = Bool
True
sameAttribute DefaultDist{} DefaultDist{} = Bool
True
sameAttribute Dim{} Dim{} = Bool
True
sameAttribute Dimen{} Dimen{} = Bool
True
sameAttribute Dir{} Dir{} = Bool
True
sameAttribute DirEdgeConstraints{} DirEdgeConstraints{} = Bool
True
sameAttribute Distortion{} Distortion{} = Bool
True
sameAttribute DPI{} DPI{} = Bool
True
sameAttribute EdgeURL{} EdgeURL{} = Bool
True
sameAttribute EdgeTarget{} EdgeTarget{} = Bool
True
sameAttribute EdgeTooltip{} EdgeTooltip{} = Bool
True
sameAttribute Epsilon{} Epsilon{} = Bool
True
sameAttribute ESep{} ESep{} = Bool
True
sameAttribute FillColor{} FillColor{} = Bool
True
sameAttribute FixedSize{} FixedSize{} = Bool
True
sameAttribute FontColor{} FontColor{} = Bool
True
sameAttribute FontName{} FontName{} = Bool
True
sameAttribute FontNames{} FontNames{} = Bool
True
sameAttribute FontPath{} FontPath{} = Bool
True
sameAttribute FontSize{} FontSize{} = Bool
True
sameAttribute ForceLabels{} ForceLabels{} = Bool
True
sameAttribute GradientAngle{} GradientAngle{} = Bool
True
sameAttribute Group{} Group{} = Bool
True
sameAttribute HeadURL{} HeadURL{} = Bool
True
sameAttribute Head_LP{} Head_LP{} = Bool
True
sameAttribute HeadClip{} HeadClip{} = Bool
True
sameAttribute HeadLabel{} HeadLabel{} = Bool
True
sameAttribute HeadPort{} HeadPort{} = Bool
True
sameAttribute HeadTarget{} HeadTarget{} = Bool
True
sameAttribute HeadTooltip{} HeadTooltip{} = Bool
True
sameAttribute Height{} Height{} = Bool
True
sameAttribute ID{} ID{} = Bool
True
sameAttribute Image{} Image{} = Bool
True
sameAttribute ImagePath{} ImagePath{} = Bool
True
sameAttribute ImageScale{} ImageScale{} = Bool
True
sameAttribute InputScale{} InputScale{} = Bool
True
sameAttribute Label{} Label{} = Bool
True
sameAttribute LabelURL{} LabelURL{} = Bool
True
sameAttribute LabelScheme{} LabelScheme{} = Bool
True
sameAttribute LabelAngle{} LabelAngle{} = Bool
True
sameAttribute LabelDistance{} LabelDistance{} = Bool
True
sameAttribute LabelFloat{} LabelFloat{} = Bool
True
sameAttribute LabelFontColor{} LabelFontColor{} = Bool
True
sameAttribute LabelFontName{} LabelFontName{} = Bool
True
sameAttribute LabelFontSize{} LabelFontSize{} = Bool
True
sameAttribute LabelJust{} LabelJust{} = Bool
True
sameAttribute LabelLoc{} LabelLoc{} = Bool
True
sameAttribute LabelTarget{} LabelTarget{} = Bool
True
sameAttribute LabelTooltip{} LabelTooltip{} = Bool
True
sameAttribute Landscape{} Landscape{} = Bool
True
sameAttribute Layer{} Layer{} = Bool
True
sameAttribute LayerListSep{} LayerListSep{} = Bool
True
sameAttribute Layers{} Layers{} = Bool
True
sameAttribute LayerSelect{} LayerSelect{} = Bool
True
sameAttribute LayerSep{} LayerSep{} = Bool
True
sameAttribute Layout{} Layout{} = Bool
True
sameAttribute Len{} Len{} = Bool
True
sameAttribute Levels{} Levels{} = Bool
True
sameAttribute LevelsGap{} LevelsGap{} = Bool
True
sameAttribute LHead{} LHead{} = Bool
True
sameAttribute LHeight{} LHeight{} = Bool
True
sameAttribute LPos{} LPos{} = Bool
True
sameAttribute LTail{} LTail{} = Bool
True
sameAttribute LWidth{} LWidth{} = Bool
True
sameAttribute Margin{} Margin{} = Bool
True
sameAttribute MaxIter{} MaxIter{} = Bool
True
sameAttribute MCLimit{} MCLimit{} = Bool
True
sameAttribute MinDist{} MinDist{} = Bool
True
sameAttribute MinLen{} MinLen{} = Bool
True
sameAttribute Mode{} Mode{} = Bool
True
sameAttribute Model{} Model{} = Bool
True
sameAttribute Mosek{} Mosek{} = Bool
True
sameAttribute NodeSep{} NodeSep{} = Bool
True
sameAttribute NoJustify{} NoJustify{} = Bool
True
sameAttribute Normalize{} Normalize{} = Bool
True
sameAttribute NoTranslate{} NoTranslate{} = Bool
True
sameAttribute Nslimit{} Nslimit{} = Bool
True
sameAttribute Nslimit1{} Nslimit1{} = Bool
True
sameAttribute Ordering{} Ordering{} = Bool
True
sameAttribute Orientation{} Orientation{} = Bool
True
sameAttribute OutputOrder{} OutputOrder{} = Bool
True
sameAttribute Overlap{} Overlap{} = Bool
True
sameAttribute OverlapScaling{} OverlapScaling{} = Bool
True
sameAttribute OverlapShrink{} OverlapShrink{} = Bool
True
sameAttribute Pack{} Pack{} = Bool
True
sameAttribute PackMode{} PackMode{} = Bool
True
sameAttribute Pad{} Pad{} = Bool
True
sameAttribute Page{} Page{} = Bool
True
sameAttribute PageDir{} PageDir{} = Bool
True
sameAttribute PenColor{} PenColor{} = Bool
True
sameAttribute PenWidth{} PenWidth{} = Bool
True
sameAttribute Peripheries{} Peripheries{} = Bool
True
sameAttribute Pin{} Pin{} = Bool
True
sameAttribute Pos{} Pos{} = Bool
True
sameAttribute QuadTree{} QuadTree{} = Bool
True
sameAttribute Quantum{} Quantum{} = Bool
True
sameAttribute Rank{} Rank{} = Bool
True
sameAttribute RankDir{} RankDir{} = Bool
True
sameAttribute RankSep{} RankSep{} = Bool
True
sameAttribute Ratio{} Ratio{} = Bool
True
sameAttribute Rects{} Rects{} = Bool
True
sameAttribute Regular{} Regular{} = Bool
True
sameAttribute ReMinCross{} ReMinCross{} = Bool
True
sameAttribute RepulsiveForce{} RepulsiveForce{} = Bool
True
sameAttribute Root{} Root{} = Bool
True
sameAttribute Rotate{} Rotate{} = Bool
True
sameAttribute Rotation{} Rotation{} = Bool
True
sameAttribute SameHead{} SameHead{} = Bool
True
sameAttribute SameTail{} SameTail{} = Bool
True
sameAttribute SamplePoints{} SamplePoints{} = Bool
True
sameAttribute Scale{} Scale{} = Bool
True
sameAttribute SearchSize{} SearchSize{} = Bool
True
sameAttribute Sep{} Sep{} = Bool
True
sameAttribute Shape{} Shape{} = Bool
True
sameAttribute ShowBoxes{} ShowBoxes{} = Bool
True
sameAttribute Sides{} Sides{} = Bool
True
sameAttribute Size{} Size{} = Bool
True
sameAttribute Skew{} Skew{} = Bool
True
sameAttribute Smoothing{} Smoothing{} = Bool
True
sameAttribute SortV{} SortV{} = Bool
True
sameAttribute Splines{} Splines{} = Bool
True
sameAttribute Start{} Start{} = Bool
True
sameAttribute Style{} Style{} = Bool
True
sameAttribute StyleSheet{} StyleSheet{} = Bool
True
sameAttribute TailURL{} TailURL{} = Bool
True
sameAttribute Tail_LP{} Tail_LP{} = Bool
True
sameAttribute TailClip{} TailClip{} = Bool
True
sameAttribute TailLabel{} TailLabel{} = Bool
True
sameAttribute TailPort{} TailPort{} = Bool
True
sameAttribute TailTarget{} TailTarget{} = Bool
True
sameAttribute TailTooltip{} TailTooltip{} = Bool
True
sameAttribute Target{} Target{} = Bool
True
sameAttribute Tooltip{} Tooltip{} = Bool
True
sameAttribute TrueColor{} TrueColor{} = Bool
True
sameAttribute Vertices{} Vertices{} = Bool
True
sameAttribute ViewPort{} ViewPort{} = Bool
True
sameAttribute VoroMargin{} VoroMargin{} = Bool
True
sameAttribute Weight{} Weight{} = Bool
True
sameAttribute Width{} Width{} = Bool
True
sameAttribute XDotVersion{} XDotVersion{} = Bool
True
sameAttribute XLabel{} XLabel{} = Bool
True
sameAttribute XLP{} XLP{} = Bool
True
sameAttribute (UnknownAttribute Text
a1 Text
_) (UnknownAttribute Text
a2 Text
_) = Text
a1 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
a2
sameAttribute Attribute
_ Attribute
_ = Bool
False
defaultAttributeValue :: Attribute -> Maybe Attribute
defaultAttributeValue :: Attribute -> Maybe Attribute
defaultAttributeValue Damping{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Damping Double
0.99
defaultAttributeValue K{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
K Double
0.3
defaultAttributeValue URL{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
URL Text
""
defaultAttributeValue Area{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Area Double
1.0
defaultAttributeValue ArrowHead{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ArrowType -> Attribute
ArrowHead ArrowType
normal
defaultAttributeValue ArrowSize{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
ArrowSize Double
1.0
defaultAttributeValue ArrowTail{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ArrowType -> Attribute
ArrowTail ArrowType
normal
defaultAttributeValue Background{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
Background Text
""
defaultAttributeValue BgColor{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorList -> Attribute
BgColor []
defaultAttributeValue Center{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Center Bool
False
defaultAttributeValue ClusterRank{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ClusterMode -> Attribute
ClusterRank ClusterMode
Local
defaultAttributeValue Color{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorList -> Attribute
Color [X11Color -> WeightedColor
forall nc. NamedColor nc => nc -> WeightedColor
toWColor X11Color
Black]
defaultAttributeValue ColorScheme{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorScheme -> Attribute
ColorScheme ColorScheme
X11
defaultAttributeValue Comment{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
Comment Text
""
defaultAttributeValue Compound{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Compound Bool
False
defaultAttributeValue Concentrate{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Concentrate Bool
False
defaultAttributeValue Constraint{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Constraint Bool
True
defaultAttributeValue Decorate{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Decorate Bool
False
defaultAttributeValue Dim{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Dim Int
2
defaultAttributeValue Dimen{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Dimen Int
2
defaultAttributeValue DirEdgeConstraints{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DEConstraints -> Attribute
DirEdgeConstraints DEConstraints
NoConstraints
defaultAttributeValue Distortion{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Distortion Double
0.0
defaultAttributeValue DPI{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
DPI Double
96.0
defaultAttributeValue EdgeURL{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
EdgeURL Text
""
defaultAttributeValue EdgeTooltip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
EdgeTooltip Text
""
defaultAttributeValue ESep{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DPoint -> Attribute
ESep (Double -> DPoint
DVal Double
3)
defaultAttributeValue FillColor{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorList -> Attribute
FillColor [X11Color -> WeightedColor
forall nc. NamedColor nc => nc -> WeightedColor
toWColor X11Color
Black]
defaultAttributeValue FixedSize{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ NodeSize -> Attribute
FixedSize NodeSize
GrowAsNeeded
defaultAttributeValue FontColor{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Color -> Attribute
FontColor (X11Color -> Color
X11Color X11Color
Black)
defaultAttributeValue FontName{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
FontName Text
"Times-Roman"
defaultAttributeValue FontNames{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ SVGFontNames -> Attribute
FontNames SVGFontNames
SvgNames
defaultAttributeValue FontSize{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
FontSize Double
14.0
defaultAttributeValue ForceLabels{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
ForceLabels Bool
True
defaultAttributeValue GradientAngle{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
GradientAngle Int
0
defaultAttributeValue Group{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
Group Text
""
defaultAttributeValue HeadURL{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
HeadURL Text
""
defaultAttributeValue HeadClip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
HeadClip Bool
True
defaultAttributeValue HeadLabel{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
HeadLabel (Text -> Label
StrLabel Text
"")
defaultAttributeValue HeadPort{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PortPos -> Attribute
HeadPort (CompassPoint -> PortPos
CompassPoint CompassPoint
CenterPoint)
defaultAttributeValue HeadTarget{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
HeadTarget Text
""
defaultAttributeValue HeadTooltip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
HeadTooltip Text
""
defaultAttributeValue Height{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Height Double
0.5
defaultAttributeValue ID{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
ID Text
""
defaultAttributeValue Image{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
Image Text
""
defaultAttributeValue ImagePath{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Paths -> Attribute
ImagePath ([String] -> Paths
Paths [])
defaultAttributeValue ImageScale{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ScaleType -> Attribute
ImageScale ScaleType
NoScale
defaultAttributeValue Label{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
Label (Text -> Label
StrLabel Text
"")
defaultAttributeValue LabelURL{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
LabelURL Text
""
defaultAttributeValue LabelScheme{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LabelScheme -> Attribute
LabelScheme LabelScheme
NotEdgeLabel
defaultAttributeValue LabelAngle{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LabelAngle (-Double
25.0)
defaultAttributeValue LabelDistance{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LabelDistance Double
1.0
defaultAttributeValue LabelFloat{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
LabelFloat Bool
False
defaultAttributeValue LabelFontColor{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Color -> Attribute
LabelFontColor (X11Color -> Color
X11Color X11Color
Black)
defaultAttributeValue LabelFontName{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
LabelFontName Text
"Times-Roman"
defaultAttributeValue LabelFontSize{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LabelFontSize Double
14.0
defaultAttributeValue LabelJust{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Justification -> Attribute
LabelJust Justification
JCenter
defaultAttributeValue LabelLoc{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ VerticalPlacement -> Attribute
LabelLoc VerticalPlacement
VTop
defaultAttributeValue LabelTarget{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
LabelTarget Text
""
defaultAttributeValue LabelTooltip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
LabelTooltip Text
""
defaultAttributeValue Landscape{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Landscape Bool
False
defaultAttributeValue Layer{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerRange -> Attribute
Layer []
defaultAttributeValue LayerListSep{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerListSep -> Attribute
LayerListSep (Text -> LayerListSep
LLSep Text
",")
defaultAttributeValue Layers{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerList -> Attribute
Layers ([LayerID] -> LayerList
LL [])
defaultAttributeValue LayerSelect{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerRange -> Attribute
LayerSelect []
defaultAttributeValue LayerSep{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerSep -> Attribute
LayerSep (Text -> LayerSep
LSep Text
" :\t")
defaultAttributeValue Levels{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Levels Int
forall a. Bounded a => a
maxBound
defaultAttributeValue LevelsGap{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LevelsGap Double
0.0
defaultAttributeValue LHead{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
LHead Text
""
defaultAttributeValue LTail{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
LTail Text
""
defaultAttributeValue MCLimit{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
MCLimit Double
1.0
defaultAttributeValue MinDist{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
MinDist Double
1.0
defaultAttributeValue MinLen{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
MinLen Int
1
defaultAttributeValue Mode{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ModeType -> Attribute
Mode ModeType
Major
defaultAttributeValue Model{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Model -> Attribute
Model Model
ShortPath
defaultAttributeValue Mosek{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Mosek Bool
False
defaultAttributeValue NodeSep{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
NodeSep Double
0.25
defaultAttributeValue NoJustify{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
NoJustify Bool
False
defaultAttributeValue Normalize{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Normalized -> Attribute
Normalize Normalized
NotNormalized
defaultAttributeValue NoTranslate{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
NoTranslate Bool
False
defaultAttributeValue Orientation{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Orientation Double
0.0
defaultAttributeValue OutputOrder{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ OutputMode -> Attribute
OutputOrder OutputMode
BreadthFirst
defaultAttributeValue Overlap{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Overlap -> Attribute
Overlap Overlap
KeepOverlaps
defaultAttributeValue OverlapScaling{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
OverlapScaling (-Double
4)
defaultAttributeValue OverlapShrink{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
OverlapShrink Bool
True
defaultAttributeValue Pack{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Pack -> Attribute
Pack Pack
DontPack
defaultAttributeValue PackMode{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PackMode -> Attribute
PackMode PackMode
PackNode
defaultAttributeValue Pad{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DPoint -> Attribute
Pad (Double -> DPoint
DVal Double
0.0555)
defaultAttributeValue PageDir{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PageDir -> Attribute
PageDir PageDir
Bl
defaultAttributeValue PenColor{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Color -> Attribute
PenColor (X11Color -> Color
X11Color X11Color
Black)
defaultAttributeValue PenWidth{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
PenWidth Double
1.0
defaultAttributeValue Peripheries{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Peripheries Int
1
defaultAttributeValue Pin{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Pin Bool
False
defaultAttributeValue QuadTree{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ QuadType -> Attribute
QuadTree QuadType
NormalQT
defaultAttributeValue Quantum{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Quantum Double
0
defaultAttributeValue RankDir{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ RankDir -> Attribute
RankDir RankDir
FromTop
defaultAttributeValue Regular{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Regular Bool
False
defaultAttributeValue ReMinCross{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
ReMinCross Bool
False
defaultAttributeValue RepulsiveForce{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
RepulsiveForce Double
1.0
defaultAttributeValue Root{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Root -> Attribute
Root (Text -> Root
NodeName Text
"")
defaultAttributeValue Rotate{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Rotate Int
0
defaultAttributeValue Rotation{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Rotation Double
0
defaultAttributeValue SameHead{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
SameHead Text
""
defaultAttributeValue SameTail{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
SameTail Text
""
defaultAttributeValue SearchSize{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
SearchSize Int
30
defaultAttributeValue Sep{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DPoint -> Attribute
Sep (Double -> DPoint
DVal Double
4)
defaultAttributeValue Shape{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Shape -> Attribute
Shape Shape
Ellipse
defaultAttributeValue ShowBoxes{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
ShowBoxes Int
0
defaultAttributeValue Sides{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Sides Int
4
defaultAttributeValue Skew{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Skew Double
0.0
defaultAttributeValue Smoothing{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ SmoothType -> Attribute
Smoothing SmoothType
NoSmooth
defaultAttributeValue SortV{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Word16 -> Attribute
SortV Word16
0
defaultAttributeValue StyleSheet{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
StyleSheet Text
""
defaultAttributeValue TailURL{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
TailURL Text
""
defaultAttributeValue TailClip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
TailClip Bool
True
defaultAttributeValue TailLabel{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
TailLabel (Text -> Label
StrLabel Text
"")
defaultAttributeValue TailPort{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PortPos -> Attribute
TailPort (CompassPoint -> PortPos
CompassPoint CompassPoint
CenterPoint)
defaultAttributeValue TailTarget{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
TailTarget Text
""
defaultAttributeValue TailTooltip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
TailTooltip Text
""
defaultAttributeValue Target{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
Target Text
""
defaultAttributeValue Tooltip{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Text -> Attribute
Tooltip Text
""
defaultAttributeValue VoroMargin{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
VoroMargin Double
0.05
defaultAttributeValue Weight{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Number -> Attribute
Weight (Int -> Number
Int Int
1)
defaultAttributeValue Width{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Width Double
0.75
defaultAttributeValue XLabel{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
XLabel (Text -> Label
StrLabel Text
"")
defaultAttributeValue Attribute
_ = Maybe Attribute
forall a. Maybe a
Nothing
validUnknown :: AttributeName -> Bool
validUnknown :: Text -> Bool
validUnknown Text
txt = Text -> Text
T.toLower Text
txt Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.notMember` Set Text
names
Bool -> Bool -> Bool
&& Text -> Bool
isIDString Text
txt
where
names :: Set Text
names = ([Text] -> Set Text
forall a. Ord a => [a] -> Set a
S.fromList ([Text] -> Set Text) -> ([Text] -> [Text]) -> [Text] -> Set Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
T.toLower
([Text] -> Set Text) -> [Text] -> Set Text
forall a b. (a -> b) -> a -> b
$ [ Text
"Damping"
, Text
"K"
, Text
"URL"
, Text
"href"
, Text
"area"
, Text
"arrowhead"
, Text
"arrowsize"
, Text
"arrowtail"
, Text
"_background"
, Text
"bb"
, Text
"bgcolor"
, Text
"center"
, Text
"clusterrank"
, Text
"color"
, Text
"colorscheme"
, Text
"comment"
, Text
"compound"
, Text
"concentrate"
, Text
"constraint"
, Text
"decorate"
, Text
"defaultdist"
, Text
"dim"
, Text
"dimen"
, Text
"dir"
, Text
"diredgeconstraints"
, Text
"distortion"
, Text
"dpi"
, Text
"resolution"
, Text
"edgeURL"
, Text
"edgehref"
, Text
"edgetarget"
, Text
"edgetooltip"
, Text
"epsilon"
, Text
"esep"
, Text
"fillcolor"
, Text
"fixedsize"
, Text
"fontcolor"
, Text
"fontname"
, Text
"fontnames"
, Text
"fontpath"
, Text
"fontsize"
, Text
"forcelabels"
, Text
"gradientangle"
, Text
"group"
, Text
"headURL"
, Text
"headhref"
, Text
"head_lp"
, Text
"headclip"
, Text
"headlabel"
, Text
"headport"
, Text
"headtarget"
, Text
"headtooltip"
, Text
"height"
, Text
"id"
, Text
"image"
, Text
"imagepath"
, Text
"imagescale"
, Text
"inputscale"
, Text
"label"
, Text
"labelURL"
, Text
"labelhref"
, Text
"label_scheme"
, Text
"labelangle"
, Text
"labeldistance"
, Text
"labelfloat"
, Text
"labelfontcolor"
, Text
"labelfontname"
, Text
"labelfontsize"
, Text
"labeljust"
, Text
"labelloc"
, Text
"labeltarget"
, Text
"labeltooltip"
, Text
"landscape"
, Text
"layer"
, Text
"layerlistsep"
, Text
"layers"
, Text
"layerselect"
, Text
"layersep"
, Text
"layout"
, Text
"len"
, Text
"levels"
, Text
"levelsgap"
, Text
"lhead"
, Text
"LHeight"
, Text
"lp"
, Text
"ltail"
, Text
"lwidth"
, Text
"margin"
, Text
"maxiter"
, Text
"mclimit"
, Text
"mindist"
, Text
"minlen"
, Text
"mode"
, Text
"model"
, Text
"mosek"
, Text
"nodesep"
, Text
"nojustify"
, Text
"normalize"
, Text
"notranslate"
, Text
"nslimit"
, Text
"nslimit1"
, Text
"ordering"
, Text
"orientation"
, Text
"outputorder"
, Text
"overlap"
, Text
"overlap_scaling"
, Text
"overlap_shrink"
, Text
"pack"
, Text
"packmode"
, Text
"pad"
, Text
"page"
, Text
"pagedir"
, Text
"pencolor"
, Text
"penwidth"
, Text
"peripheries"
, Text
"pin"
, Text
"pos"
, Text
"quadtree"
, Text
"quantum"
, Text
"rank"
, Text
"rankdir"
, Text
"ranksep"
, Text
"ratio"
, Text
"rects"
, Text
"regular"
, Text
"remincross"
, Text
"repulsiveforce"
, Text
"root"
, Text
"rotate"
, Text
"rotation"
, Text
"samehead"
, Text
"sametail"
, Text
"samplepoints"
, Text
"scale"
, Text
"searchsize"
, Text
"sep"
, Text
"shape"
, Text
"showboxes"
, Text
"sides"
, Text
"size"
, Text
"skew"
, Text
"smoothing"
, Text
"sortv"
, Text
"splines"
, Text
"start"
, Text
"style"
, Text
"stylesheet"
, Text
"tailURL"
, Text
"tailhref"
, Text
"tail_lp"
, Text
"tailclip"
, Text
"taillabel"
, Text
"tailport"
, Text
"tailtarget"
, Text
"tailtooltip"
, Text
"target"
, Text
"tooltip"
, Text
"truecolor"
, Text
"vertices"
, Text
"viewport"
, Text
"voro_margin"
, Text
"weight"
, Text
"width"
, Text
"xdotversion"
, Text
"xlabel"
, Text
"xlp"
, Text
"charset"
])
Set Text -> Set Text -> Set Text
forall a. Ord a => Set a -> Set a -> Set a
`S.union`
Set Text
keywords
rmUnwantedAttributes :: Attributes -> Attributes
rmUnwantedAttributes :: [Attribute] -> [Attribute]
rmUnwantedAttributes = (Attribute -> Bool) -> [Attribute] -> [Attribute]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Attribute -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Attribute -> Bool) -> Bool) -> [Attribute -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
`any` [Attribute -> Bool]
tests) (((Attribute -> Bool) -> Bool) -> Bool)
-> (Attribute -> (Attribute -> Bool) -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Attribute -> Bool) -> Attribute -> Bool)
-> Attribute -> (Attribute -> Bool) -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Attribute -> Bool) -> Attribute -> Bool
forall a b. (a -> b) -> a -> b
($))
where
tests :: [Attribute -> Bool]
tests = [Attribute -> Bool
isDefault, Attribute -> Bool
isColorScheme]
isDefault :: Attribute -> Bool
isDefault Attribute
a = Bool -> (Attribute -> Bool) -> Maybe Attribute -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Attribute
aAttribute -> Attribute -> Bool
forall a. Eq a => a -> a -> Bool
==) (Maybe Attribute -> Bool) -> Maybe Attribute -> Bool
forall a b. (a -> b) -> a -> b
$ Attribute -> Maybe Attribute
defaultAttributeValue Attribute
a
isColorScheme :: Attribute -> Bool
isColorScheme ColorScheme{} = Bool
True
isColorScheme Attribute
_ = Bool
False
parseField :: (ParseDot a) => (a -> Attribute) -> String
-> [(String, Parse Attribute)]
parseField :: (a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField a -> Attribute
c String
fld = [(String
fld, String -> (a -> Attribute) -> Parse Attribute
forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
liftEqParse String
fld a -> Attribute
c)]
parseFields :: (ParseDot a) => (a -> Attribute) -> [String]
-> [(String, Parse Attribute)]
parseFields :: (a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields a -> Attribute
c = (String -> [(String, Parse Attribute)])
-> [String] -> [(String, Parse Attribute)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((a -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField a -> Attribute
c)
parseFieldBool :: (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool :: (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool = ((Bool -> Attribute)
-> Bool -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
`parseFieldDef` Bool
True)
parseFieldDef :: (ParseDot a) => (a -> Attribute) -> a -> String
-> [(String, Parse Attribute)]
parseFieldDef :: (a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef a -> Attribute
c a
d String
fld = [(String
fld, Parse Attribute
p)]
where
p :: Parse Attribute
p = String -> (a -> Attribute) -> Parse Attribute
forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
liftEqParse String
fld a -> Attribute
c
Parse Attribute -> Parse Attribute -> Parse Attribute
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
do Maybe Char
nxt <- Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState Char -> Parser GraphvizState (Maybe Char))
-> Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Parser GraphvizState Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
restIDString
Parse Attribute -> Parse Attribute -> Bool -> Parse Attribute
forall a. a -> a -> Bool -> a
bool (String -> Parse Attribute
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Not actually the field you were after")
(Attribute -> Parse Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return (Attribute -> Parse Attribute) -> Attribute -> Parse Attribute
forall a b. (a -> b) -> a -> b
$ a -> Attribute
c a
d)
(Maybe Char -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Char
nxt)
liftEqParse :: (ParseDot a) => String -> (a -> Attribute) -> Parse Attribute
liftEqParse :: String -> (a -> Attribute) -> Parse Attribute
liftEqParse String
k a -> Attribute
c = do Bool
pStrict <- (GraphvizState -> Bool) -> Parser GraphvizState Bool
forall (m :: * -> *) a.
GraphvizStateM m =>
(GraphvizState -> a) -> m a
getsGS GraphvizState -> Bool
parseStrictly
let adjErr :: Parser GraphvizState a -> ShowS -> Parser GraphvizState a
adjErr = (Parser GraphvizState a -> ShowS -> Parser GraphvizState a)
-> (Parser GraphvizState a -> ShowS -> Parser GraphvizState a)
-> Bool
-> Parser GraphvizState a
-> ShowS
-> Parser GraphvizState a
forall a. a -> a -> Bool -> a
bool Parser GraphvizState a -> ShowS -> Parser GraphvizState a
forall (p :: * -> *) a. Commitment p => p a -> ShowS -> p a
adjustErr Parser GraphvizState a -> ShowS -> Parser GraphvizState a
forall (p :: * -> *) a. PolyParse p => p a -> ShowS -> p a
adjustErrBad Bool
pStrict
Parse ()
parseEq
Parse () -> Parse Attribute -> Parse Attribute
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ( Parse Attribute -> Parse Attribute
hasDef ((a -> Attribute) -> Parser GraphvizState a -> Parse Attribute
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Attribute
c Parser GraphvizState a
forall a. ParseDot a => Parse a
parse)
Parse Attribute -> ShowS -> Parse Attribute
forall a. Parser GraphvizState a -> ShowS -> Parser GraphvizState a
`adjErr`
((String
"Unable to parse key=value with key of " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
k
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n\t") String -> ShowS
forall a. [a] -> [a] -> [a]
++)
)
where
hasDef :: Parse Attribute -> Parse Attribute
hasDef Parse Attribute
p = Parse Attribute
-> (Attribute -> Parse Attribute)
-> Maybe Attribute
-> Parse Attribute
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Parse Attribute
p (Parse Attribute -> Parse Attribute -> Parse Attribute
forall s a. Parser s a -> Parser s a -> Parser s a
onFail Parse Attribute
p (Parse Attribute -> Parse Attribute)
-> (Attribute -> Parse Attribute) -> Attribute -> Parse Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attribute -> String -> Parse Attribute
forall a. a -> String -> Parse a
`stringRep` String
"\"\""))
(Maybe Attribute -> Parse Attribute)
-> (Attribute -> Maybe Attribute) -> Attribute -> Parse Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attribute -> Maybe Attribute
defaultAttributeValue (Attribute -> Parse Attribute) -> Attribute -> Parse Attribute
forall a b. (a -> b) -> a -> b
$ a -> Attribute
c a
forall a. HasCallStack => a
undefined
type CustomAttribute = Attribute
customAttribute :: AttributeName -> Text -> CustomAttribute
customAttribute :: Text -> Text -> Attribute
customAttribute = Text -> Text -> Attribute
UnknownAttribute
isCustom :: Attribute -> Bool
isCustom :: Attribute -> Bool
isCustom UnknownAttribute{} = Bool
True
isCustom Attribute
_ = Bool
False
isSpecifiedCustom :: AttributeName -> Attribute -> Bool
isSpecifiedCustom :: Text -> Attribute -> Bool
isSpecifiedCustom Text
nm (UnknownAttribute Text
nm' Text
_) = Text
nm Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
nm'
isSpecifiedCustom Text
_ Attribute
_ = Bool
False
customValue :: CustomAttribute -> Text
customValue :: Attribute -> Text
customValue (UnknownAttribute Text
_ Text
v) = Text
v
customValue Attribute
attr = GraphvizException -> Text
forall a e. Exception e => e -> a
throw (GraphvizException -> Text)
-> (Text -> GraphvizException) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GraphvizException
NotCustomAttr (String -> GraphvizException)
-> (Text -> String) -> Text -> GraphvizException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
(Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Attribute -> Text
forall a. PrintDot a => a -> Text
printIt Attribute
attr
customName :: CustomAttribute -> AttributeName
customName :: Attribute -> Text
customName (UnknownAttribute Text
nm Text
_) = Text
nm
customName Attribute
attr = GraphvizException -> Text
forall a e. Exception e => e -> a
throw (GraphvizException -> Text)
-> (Text -> GraphvizException) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GraphvizException
NotCustomAttr (String -> GraphvizException)
-> (Text -> String) -> Text -> GraphvizException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
(Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Attribute -> Text
forall a. PrintDot a => a -> Text
printIt Attribute
attr
findCustoms :: Attributes -> ([CustomAttribute], Attributes)
findCustoms :: [Attribute] -> ([Attribute], [Attribute])
findCustoms = (Attribute -> Bool) -> [Attribute] -> ([Attribute], [Attribute])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Attribute -> Bool
isCustom
findSpecifiedCustom :: AttributeName -> Attributes
-> Maybe (CustomAttribute, Attributes)
findSpecifiedCustom :: Text -> [Attribute] -> Maybe (Attribute, [Attribute])
findSpecifiedCustom Text
nm [Attribute]
attrs
= case (Attribute -> Bool) -> [Attribute] -> ([Attribute], [Attribute])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Text -> Attribute -> Bool
isSpecifiedCustom Text
nm) [Attribute]
attrs of
([Attribute]
bf,Attribute
cust:[Attribute]
aft) -> (Attribute, [Attribute]) -> Maybe (Attribute, [Attribute])
forall a. a -> Maybe a
Just (Attribute
cust, [Attribute]
bf [Attribute] -> [Attribute] -> [Attribute]
forall a. [a] -> [a] -> [a]
++ [Attribute]
aft)
([Attribute], [Attribute])
_ -> Maybe (Attribute, [Attribute])
forall a. Maybe a
Nothing
deleteCustomAttributes :: Attributes -> Attributes
deleteCustomAttributes :: [Attribute] -> [Attribute]
deleteCustomAttributes = (Attribute -> Bool) -> [Attribute] -> [Attribute]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Attribute -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attribute -> Bool
isCustom)
deleteSpecifiedCustom :: AttributeName -> Attributes -> Attributes
deleteSpecifiedCustom :: Text -> [Attribute] -> [Attribute]
deleteSpecifiedCustom Text
nm = (Attribute -> Bool) -> [Attribute] -> [Attribute]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Attribute -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Attribute -> Bool
isSpecifiedCustom Text
nm)