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