{-# LANGUAGE CPP, OverloadedStrings #-}

{- |
   Module      : Data.GraphViz.Attributes.Complete
   Description : Definition of the Graphviz attributes.
   Copyright   : (c) Matthew Sackman, Ivan Lazar Miljenovic
   License     : 3-Clause BSD-style
   Maintainer  : Ivan.Miljenovic@gmail.com

   If you are just using graphviz to create basic Dot graphs, then you
   probably want to use "Data.GraphViz.Attributes" rather than this
   module.

   This module defines the various attributes that different parts of
   a Graphviz graph can have.  These attributes are based on the
   documentation found at:
     <http://graphviz.org/doc/info/attrs.html>

   For more information on usage, etc. please see that document.

   A summary of known current constraints\/limitations\/differences:

   * Note that for an edge, in /Dot/ parlance if the edge goes from
     /A/ to /B/, then /A/ is the tail node and /B/ is the head node
     (since /A/ is at the tail end of the arrow).

   * @ColorList@, @DoubleList@ and @PointfList@ are defined as actual
     lists (@'LayerList'@ needs a newtype for other reasons).  All of these
     are assumed to be non-empty lists.

   * For the various @*Color@ attributes that take in a list of
     'Color' values, usually only one color is used.  The @Color@
     attribute for edges allows multiple values; for other attributes,
     two values are supported for gradient fills in Graphviz >=
     2.29.0.

   * Style is implemented as a list of 'StyleItem' values; note that
     empty lists are not allowed.

   * A lot of values have a possible value of @none@.  These now
     have custom constructors.  In fact, most constructors have been
     expanded upon to give an idea of what they represent rather than
     using generic terms.

   * 'Rect' uses two 'Point' values to denote the lower-left and
     top-right corners.

   * The two 'LabelLoc' attributes have been combined.

   * @SplineType@ has been replaced with @['Spline']@.

   * Only polygon-based 'Shape's are available.

   * Not every 'Attribute' is fully documented/described.  However,
     all those which have specific allowed values should be covered.

   * Deprecated 'Overlap' algorithms are not defined.  Furthermore,
     the ability to specify an integer prefix for use with the fdp layout
     is /not/ supported.

   * The global @Orientation@ attribute is not defined, as it is
     difficult to distinguish from the node-based 'Orientation'
     'Attribute'; also, its behaviour is duplicated by 'Rotate'.

   * The @charset@ attribute is not available, as graphviz only
     supports UTF-8 encoding (as it is not currently feasible nor needed to
     also support Latin1 encoding).

   * In Graphviz, when a node or edge has a list of attributes, the
     colorscheme which is used to identify a color can be set /after/
     that color (e.g. @[colorscheme=x11,color=grey,colorscheme=svg]@
     uses the svg colorscheme's definition of grey, which is different
     from the x11 one.  Instead, graphviz parses them in order.

 -}
module Data.GraphViz.Attributes.Complete
       ( -- * The actual /Dot/ attributes.
         -- $attributes
         Attribute(..)
       , Attributes
       , sameAttribute
       , defaultAttributeValue
       , rmUnwantedAttributes
         -- ** Validity functions on @Attribute@ values.
       , usedByGraphs
       , usedBySubGraphs
       , usedByClusters
       , usedByNodes
       , usedByEdges
       , validUnknown

         -- ** Custom attributes.
       , AttributeName
       , CustomAttribute
       , customAttribute
       , isCustom
       , isSpecifiedCustom
       , customValue
       , customName
       , findCustoms
       , findSpecifiedCustom
       , deleteCustomAttributes
       , deleteSpecifiedCustom

         -- * Value types for @Attribute@s.
       , module Data.GraphViz.Attributes.Colors

         -- ** Generic types
       , Number (..)

         -- ** Labels
       , EscString
       , Label(..)
       , VerticalPlacement(..)
       , LabelScheme(..)
       , SVGFontNames(..)
         -- *** Types representing the Dot grammar for records.
       , RecordFields
       , RecordField(..)
       , Rect(..)
       , Justification(..)

         -- ** Nodes
       , Shape(..)
       , Paths(..)
       , ScaleType(..)
       , NodeSize(..)

         -- ** Edges
       , DirType(..)
       , EdgeType(..)
         -- *** Modifying where edges point
       , PortName(..)
       , PortPos(..)
       , CompassPoint(..)
         -- *** Arrows
       , ArrowType(..)
       , ArrowShape(..)
       , ArrowModifier(..)
       , ArrowFill(..)
       , ArrowSide(..)
         -- **** @ArrowModifier@ values
       , noMods
       , openMod

         -- ** Positioning
       , Point(..)
       , createPoint
       , Pos(..)
       , Spline(..)
       , DPoint(..)
       , Normalized (..)

         -- ** Layout
       , GraphvizCommand(..)
       , GraphSize(..)
       , ClusterMode(..)
       , Model(..)
       , Overlap(..)
       , Root(..)
       , Order(..)
       , OutputMode(..)
       , Pack(..)
       , PackMode(..)
       , PageDir(..)
       , QuadType(..)
       , RankType(..)
       , RankDir(..)
       , StartType(..)
       , ViewPort(..)
       , FocusType(..)
       , Ratios(..)

         -- ** Modes
       , ModeType(..)
       , DEConstraints(..)

         -- ** Layers
       , LayerSep(..)
       , LayerListSep(..)
       , LayerRange
       , LayerRangeElem(..)
       , LayerID(..)
       , LayerList(..)

         -- ** Stylistic
       , 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

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

{- $attributes

   These attributes have been implemented in a /permissive/ manner:
   that is, rather than split them up based on which type of value
   they are allowed, they have all been included in the one data type,
   with functions to determine if they are indeed valid for what
   they're being applied to.

   To interpret the /Valid for/ listings:

     [@G@] Valid for Graphs.

     [@C@] Valid for Clusters.

     [@S@] Valid for Sub-Graphs (and also Clusters).

     [@N@] Valid for Nodes.

     [@E@] Valid for Edges.

   The /Default/ listings are those that the various Graphviz commands
   use if that 'Attribute' isn't specified (in cases where this is
   /none/, this is equivalent to a 'Nothing' value; that is, no value
   is used).  The /Parsing Default/ listings represent what value is
   used (i.e. corresponds to 'True') when the 'Attribute' name is
   listed on its own in /Dot/ source code.

   Please note that the 'UnknownAttribute' 'Attribute' is defined
   primarily for backwards-compatibility purposes.  It is possible to use
   it directly for custom purposes; for more information, please see
   'CustomAttribute'.  The 'deleteCustomAttributes' can be used to delete
   these values.

 -}

-- | Attributes are used to customise the layout and design of Dot
--   graphs.  Care must be taken to ensure that the attribute you use
--   is valid, as not all attributes can be used everywhere.
data Attribute
  = Damping Double                      -- ^ /Valid for/: G; /Default/: @0.99@; /Minimum/: @0.0@; /Notes/: 'Neato' only
  | K Double                            -- ^ /Valid for/: GC; /Default/: @0.3@; /Minimum/: @0@; /Notes/: 'Sfdp', 'Fdp' only
  | URL EscString                       -- ^ /Valid for/: ENGC; /Default/: none; /Notes/: svg, postscript, map only
  | Area Double                         -- ^ /Valid for/: NC; /Default/: @1.0@; /Minimum/: @>0@; /Notes/: 'Patchwork' only, requires Graphviz >= 2.30.0
  | ArrowHead ArrowType                 -- ^ /Valid for/: E; /Default/: @'normal'@
  | ArrowSize Double                    -- ^ /Valid for/: E; /Default/: @1.0@; /Minimum/: @0.0@
  | ArrowTail ArrowType                 -- ^ /Valid for/: E; /Default/: @'normal'@
  | Background Text                     -- ^ /Valid for/: G; /Default/: none; /Notes/: xdot only
  | BoundingBox Rect                    -- ^ /Valid for/: G; /Notes/: write only
  | BgColor ColorList                   -- ^ /Valid for/: GC; /Default/: @[]@
  | Center Bool                         -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'
  | ClusterRank ClusterMode             -- ^ /Valid for/: G; /Default/: @'Local'@; /Notes/: 'Dot' only
  | Color ColorList                     -- ^ /Valid for/: ENC; /Default/: @['WC' ('X11Color' 'Black') Nothing]@
  | ColorScheme ColorScheme             -- ^ /Valid for/: ENCG; /Default/: @'X11'@
  | Comment Text                        -- ^ /Valid for/: ENG; /Default/: @\"\"@
  | Compound Bool                       -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'; /Notes/: 'Dot' only
  | Concentrate Bool                    -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'
  | Constraint Bool                     -- ^ /Valid for/: E; /Default/: @'True'@; /Parsing Default/: 'True'; /Notes/: 'Dot' only
  | Decorate Bool                       -- ^ /Valid for/: E; /Default/: @'False'@; /Parsing Default/: 'True'
  | DefaultDist Double                  -- ^ /Valid for/: G; /Default/: @1+(avg. len)*sqrt(abs(V))@ (unable to statically define); /Minimum/: The value of 'Epsilon'.; /Notes/: 'Neato' only, only if @'Pack' 'DontPack'@
  | Dim Int                             -- ^ /Valid for/: G; /Default/: @2@; /Minimum/: @2@; /Notes/: maximum of @10@; 'Sfdp', 'Fdp', 'Neato' only
  | Dimen Int                           -- ^ /Valid for/: G; /Default/: @2@; /Minimum/: @2@; /Notes/: maximum of @10@; 'Sfdp', 'Fdp', 'Neato' only
  | Dir DirType                         -- ^ /Valid for/: E; /Default/: @'Forward'@ (directed), @'NoDir'@ (undirected)
  | DirEdgeConstraints DEConstraints    -- ^ /Valid for/: G; /Default/: @'NoConstraints'@; /Parsing Default/: 'EdgeConstraints'; /Notes/: 'Neato' only
  | Distortion Double                   -- ^ /Valid for/: N; /Default/: @0.0@; /Minimum/: @-100.0@
  | DPI Double                          -- ^ /Valid for/: G; /Default/: @96.0@, @0.0@; /Notes/: svg, bitmap output only; \"resolution\" is a synonym
  | EdgeURL EscString                   -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, map only
  | EdgeTarget EscString                -- ^ /Valid for/: E; /Default/: none; /Notes/: svg, map only
  | EdgeTooltip EscString               -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, cmap only
  | Epsilon Double                      -- ^ /Valid for/: G; /Default/: @.0001 * # nodes@ (@mode == 'KK'@), @.0001@ (@mode == 'Major'@); /Notes/: 'Neato' only
  | ESep DPoint                         -- ^ /Valid for/: G; /Default/: @'DVal' 3@; /Notes/: not 'Dot'
  | FillColor ColorList                 -- ^ /Valid for/: NEC; /Default/: @['WC' ('X11Color' 'LightGray') Nothing]@ (nodes), @['WC' ('X11Color' 'Black') Nothing]@ (clusters)
  | FixedSize NodeSize                  -- ^ /Valid for/: N; /Default/: @'GrowAsNeeded'@; /Parsing Default/: 'SetNodeSize'
  | FontColor Color                     -- ^ /Valid for/: ENGC; /Default/: @'X11Color' 'Black'@
  | FontName Text                       -- ^ /Valid for/: ENGC; /Default/: @\"Times-Roman\"@
  | FontNames SVGFontNames              -- ^ /Valid for/: G; /Default/: @'SvgNames'@; /Notes/: svg only
  | FontPath Paths                      -- ^ /Valid for/: G; /Default/: system dependent
  | FontSize Double                     -- ^ /Valid for/: ENGC; /Default/: @14.0@; /Minimum/: @1.0@
  | ForceLabels Bool                    -- ^ /Valid for/: G; /Default/: @'True'@; /Parsing Default/: 'True'; /Notes/: only for 'XLabel' attributes, requires Graphviz >= 2.29.0
  | GradientAngle Int                   -- ^ /Valid for/: NCG; /Default/: 0; /Notes/: requires Graphviz >= 2.29.0
  | Group Text                          -- ^ /Valid for/: N; /Default/: @\"\"@; /Notes/: 'Dot' only
  | HeadURL EscString                   -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, map only
  | Head_LP Point                       -- ^ /Valid for/: E; /Notes/: write only, requires Graphviz >= 2.30.0
  | HeadClip Bool                       -- ^ /Valid for/: E; /Default/: @'True'@; /Parsing Default/: 'True'
  | HeadLabel Label                     -- ^ /Valid for/: E; /Default/: @'StrLabel' \"\"@
  | HeadPort PortPos                    -- ^ /Valid for/: E; /Default/: @'CompassPoint' 'CenterPoint'@
  | HeadTarget EscString                -- ^ /Valid for/: E; /Default/: none; /Notes/: svg, map only
  | HeadTooltip EscString               -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, cmap only
  | Height Double                       -- ^ /Valid for/: N; /Default/: @0.5@; /Minimum/: @0.02@
  | ID EscString                        -- ^ /Valid for/: GNE; /Default/: @\"\"@; /Notes/: svg, postscript, map only
  | Image Text                          -- ^ /Valid for/: N; /Default/: @\"\"@
  | ImagePath Paths                     -- ^ /Valid for/: G; /Default/: @'Paths' []@; /Notes/: Printing and parsing is OS-specific, requires Graphviz >= 2.29.0
  | ImageScale ScaleType                -- ^ /Valid for/: N; /Default/: @'NoScale'@; /Parsing Default/: 'UniformScale'
  | InputScale Double                   -- ^ /Valid for/: N; /Default/: none; /Notes/: 'Fdp', 'Neato' only, a value of @0@ is equivalent to being @72@, requires Graphviz >= 2.36.0
  | Label Label                         -- ^ /Valid for/: ENGC; /Default/: @'StrLabel' \"\\N\"@ (nodes), @'StrLabel' \"\"@ (otherwise)
  | LabelURL EscString                  -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, map only
  | LabelScheme LabelScheme             -- ^ /Valid for/: G; /Default/: @'NotEdgeLabel'@; /Notes/: 'Sfdp' only, requires Graphviz >= 2.28.0
  | LabelAngle Double                   -- ^ /Valid for/: E; /Default/: @-25.0@; /Minimum/: @-180.0@
  | LabelDistance Double                -- ^ /Valid for/: E; /Default/: @1.0@; /Minimum/: @0.0@
  | LabelFloat Bool                     -- ^ /Valid for/: E; /Default/: @'False'@; /Parsing Default/: 'True'
  | LabelFontColor Color                -- ^ /Valid for/: E; /Default/: @'X11Color' 'Black'@
  | LabelFontName Text                  -- ^ /Valid for/: E; /Default/: @\"Times-Roman\"@
  | LabelFontSize Double                -- ^ /Valid for/: E; /Default/: @14.0@; /Minimum/: @1.0@
  | LabelJust Justification             -- ^ /Valid for/: GC; /Default/: @'JCenter'@
  | LabelLoc VerticalPlacement          -- ^ /Valid for/: GCN; /Default/: @'VTop'@ (clusters), @'VBottom'@ (root graphs), @'VCenter'@ (nodes)
  | LabelTarget EscString               -- ^ /Valid for/: E; /Default/: none; /Notes/: svg, map only
  | LabelTooltip EscString              -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, cmap only
  | Landscape Bool                      -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'
  | Layer LayerRange                    -- ^ /Valid for/: ENC; /Default/: @[]@
  | LayerListSep LayerListSep           -- ^ /Valid for/: G; /Default/: @'LLSep' \",\"@; /Notes/: requires Graphviz >= 2.30.0
  | Layers LayerList                    -- ^ /Valid for/: G; /Default/: @'LL' []@
  | LayerSelect LayerRange              -- ^ /Valid for/: G; /Default/: @[]@
  | LayerSep LayerSep                   -- ^ /Valid for/: G; /Default/: @'LSep' \" :\t\"@
  | Layout GraphvizCommand              -- ^ /Valid for/: G
  | Len Double                          -- ^ /Valid for/: E; /Default/: @1.0@ ('Neato'), @0.3@ ('Fdp'); /Notes/: 'Fdp', 'Neato' only
  | Levels Int                          -- ^ /Valid for/: G; /Default/: @'maxBound'@; /Minimum/: @0@; /Notes/: 'Sfdp' only
  | LevelsGap Double                    -- ^ /Valid for/: G; /Default/: @0.0@; /Notes/: 'Neato' only
  | LHead Text                          -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: 'Dot' only
  | LHeight Double                      -- ^ /Valid for/: GC; /Notes/: write only, requires Graphviz >= 2.28.0
  | LPos Point                          -- ^ /Valid for/: EGC; /Notes/: write only
  | LTail Text                          -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: 'Dot' only
  | LWidth Double                       -- ^ /Valid for/: GC; /Notes/: write only, requires Graphviz >= 2.28.0
  | Margin DPoint                       -- ^ /Valid for/: NGC; /Default/: device dependent
  | MaxIter Int                         -- ^ /Valid for/: G; /Default/: @100 * # nodes@ (@mode == 'KK'@), @200@ (@mode == 'Major'@), @600@ ('Fdp'); /Notes/: 'Fdp', 'Neato' only
  | MCLimit Double                      -- ^ /Valid for/: G; /Default/: @1.0@; /Notes/: 'Dot' only
  | MinDist Double                      -- ^ /Valid for/: G; /Default/: @1.0@; /Minimum/: @0.0@; /Notes/: 'Circo' only
  | MinLen Int                          -- ^ /Valid for/: E; /Default/: @1@; /Minimum/: @0@; /Notes/: 'Dot' only
  | Mode ModeType                       -- ^ /Valid for/: G; /Default/: @'Major'@ (actually @'Spring'@ for 'Sfdp', but this isn't used as a default in this library); /Notes/: 'Neato', 'Sfdp' only
  | Model Model                         -- ^ /Valid for/: G; /Default/: @'ShortPath'@; /Notes/: 'Neato' only
  | Mosek Bool                          -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'; /Notes/: 'Neato' only; requires the Mosek software
  | NodeSep Double                      -- ^ /Valid for/: G; /Default/: @0.25@; /Minimum/: @0.02@
  | NoJustify Bool                      -- ^ /Valid for/: GCNE; /Default/: @'False'@; /Parsing Default/: 'True'
  | Normalize Normalized                -- ^ /Valid for/: G; /Default/: @'NotNormalized'@; /Parsing Default/: 'IsNormalized'; /Notes/: not 'Dot'
  | NoTranslate Bool                    -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'; /Notes/: 'Neato' only, requires Graphviz >= 2.38.0
  | Nslimit Double                      -- ^ /Valid for/: G; /Notes/: 'Dot' only
  | Nslimit1 Double                     -- ^ /Valid for/: G; /Notes/: 'Dot' only
  | Ordering Order                      -- ^ /Valid for/: GN; /Default/: none; /Notes/: 'Dot' only
  | Orientation Double                  -- ^ /Valid for/: N; /Default/: @0.0@; /Minimum/: @360.0@
  | OutputOrder OutputMode              -- ^ /Valid for/: G; /Default/: @'BreadthFirst'@
  | Overlap Overlap                     -- ^ /Valid for/: G; /Default/: @'KeepOverlaps'@; /Parsing Default/: 'KeepOverlaps'; /Notes/: not 'Dot'
  | OverlapScaling Double               -- ^ /Valid for/: G; /Default/: @-4@; /Minimum/: @-1.0e10@; /Notes/: 'PrismOverlap' only
  | OverlapShrink Bool                  -- ^ /Valid for/: G; /Default/: @'True'@; /Parsing Default/: 'True'; /Notes/: 'PrismOverlap' only, requires Graphviz >= 2.36.0
  | Pack Pack                           -- ^ /Valid for/: G; /Default/: @'DontPack'@; /Parsing Default/: 'DoPack'
  | PackMode PackMode                   -- ^ /Valid for/: G; /Default/: @'PackNode'@
  | Pad DPoint                          -- ^ /Valid for/: G; /Default/: @'DVal' 0.0555@ (4 points)
  | Page Point                          -- ^ /Valid for/: G
  | PageDir PageDir                     -- ^ /Valid for/: G; /Default/: @'Bl'@
  | PenColor Color                      -- ^ /Valid for/: C; /Default/: @'X11Color' 'Black'@
  | PenWidth Double                     -- ^ /Valid for/: CNE; /Default/: @1.0@; /Minimum/: @0.0@
  | Peripheries Int                     -- ^ /Valid for/: NC; /Default/: shape default (nodes), @1@ (clusters); /Minimum/: 0
  | Pin Bool                            -- ^ /Valid for/: N; /Default/: @'False'@; /Parsing Default/: 'True'; /Notes/: 'Fdp', 'Neato' only
  | Pos Pos                             -- ^ /Valid for/: EN
  | QuadTree QuadType                   -- ^ /Valid for/: G; /Default/: @'NormalQT'@; /Parsing Default/: 'NormalQT'; /Notes/: 'Sfdp' only
  | Quantum Double                      -- ^ /Valid for/: G; /Default/: @0.0@; /Minimum/: @0.0@
  | Rank RankType                       -- ^ /Valid for/: S; /Notes/: 'Dot' only
  | RankDir RankDir                     -- ^ /Valid for/: G; /Default/: @'FromTop'@; /Notes/: 'Dot' only
  | RankSep [Double]                    -- ^ /Valid for/: G; /Default/: @[0.5]@ ('Dot'), @[1.0]@ ('Twopi'); /Minimum/: @[0.02]@; /Notes/: 'Twopi', 'Dot' only
  | Ratio Ratios                        -- ^ /Valid for/: G
  | Rects [Rect]                        -- ^ /Valid for/: N; /Notes/: write only
  | Regular Bool                        -- ^ /Valid for/: N; /Default/: @'False'@; /Parsing Default/: 'True'
  | ReMinCross Bool                     -- ^ /Valid for/: G; /Default/: @'False'@; /Parsing Default/: 'True'; /Notes/: 'Dot' only
  | RepulsiveForce Double               -- ^ /Valid for/: G; /Default/: @1.0@; /Minimum/: @0.0@; /Notes/: 'Sfdp' only
  | Root Root                           -- ^ /Valid for/: GN; /Default/: @'NodeName' \"\"@ (graphs), @'NotCentral'@ (nodes); /Parsing Default/: 'IsCentral'; /Notes/: 'Circo', 'Twopi' only
  | Rotate Int                          -- ^ /Valid for/: G; /Default/: @0@
  | Rotation Double                     -- ^ /Valid for/: G; /Default/: @0@; /Notes/: 'Sfdp' only, requires Graphviz >= 2.28.0
  | SameHead Text                       -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: 'Dot' only
  | SameTail Text                       -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: 'Dot' only
  | SamplePoints Int                    -- ^ /Valid for/: N; /Default/: @8@ (output), @20@ (overlap and image maps)
  | Scale DPoint                        -- ^ /Valid for/: G; /Notes/: Not 'Dot', requires Graphviz >= 2.28.0 (>= 2.38.0 for anything except 'TwoPi')
  | SearchSize Int                      -- ^ /Valid for/: G; /Default/: @30@; /Notes/: 'Dot' only
  | Sep DPoint                          -- ^ /Valid for/: G; /Default/: @'DVal' 4@; /Notes/: not 'Dot'
  | Shape Shape                         -- ^ /Valid for/: N; /Default/: @'Ellipse'@
  | ShowBoxes Int                       -- ^ /Valid for/: ENG; /Default/: @0@; /Minimum/: @0@; /Notes/: 'Dot' only; used for debugging by printing PostScript guide boxes
  | Sides Int                           -- ^ /Valid for/: N; /Default/: @4@; /Minimum/: @0@
  | Size GraphSize                      -- ^ /Valid for/: G
  | Skew Double                         -- ^ /Valid for/: N; /Default/: @0.0@; /Minimum/: @-100.0@
  | Smoothing SmoothType                -- ^ /Valid for/: G; /Default/: @'NoSmooth'@; /Notes/: 'Sfdp' only
  | SortV Word16                        -- ^ /Valid for/: GCN; /Default/: @0@; /Minimum/: @0@
  | Splines EdgeType                    -- ^ /Valid for/: G; /Default/: @'SplineEdges'@ ('Dot'), @'LineEdges'@ (other); /Parsing Default/: 'SplineEdges'
  | Start StartType                     -- ^ /Valid for/: G; /Default/: @'StartStyleSeed' 'RandomStyle' seed@ for some unknown fixed seed.; /Notes/: 'Fdp', 'Neato' only
  | Style [StyleItem]                   -- ^ /Valid for/: ENCG
  | StyleSheet Text                     -- ^ /Valid for/: G; /Default/: @\"\"@; /Notes/: svg only
  | TailURL EscString                   -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, map only
  | Tail_LP Point                       -- ^ /Valid for/: E; /Notes/: write only, requires Graphviz >= 2.30.0
  | TailClip Bool                       -- ^ /Valid for/: E; /Default/: @'True'@; /Parsing Default/: 'True'
  | TailLabel Label                     -- ^ /Valid for/: E; /Default/: @'StrLabel' \"\"@
  | TailPort PortPos                    -- ^ /Valid for/: E; /Default/: @'CompassPoint' 'CenterPoint'@
  | TailTarget EscString                -- ^ /Valid for/: E; /Default/: none; /Notes/: svg, map only
  | TailTooltip EscString               -- ^ /Valid for/: E; /Default/: @\"\"@; /Notes/: svg, cmap only
  | Target EscString                    -- ^ /Valid for/: ENGC; /Default/: none; /Notes/: svg, map only
  | Tooltip EscString                   -- ^ /Valid for/: NEC; /Default/: @\"\"@; /Notes/: svg, cmap only
  | TrueColor Bool                      -- ^ /Valid for/: G; /Parsing Default/: 'True'; /Notes/: bitmap output only
  | Vertices [Point]                    -- ^ /Valid for/: N; /Notes/: write only
  | ViewPort ViewPort                   -- ^ /Valid for/: G; /Default/: none
  | VoroMargin Double                   -- ^ /Valid for/: G; /Default/: @0.05@; /Minimum/: @0.0@; /Notes/: not 'Dot'
  | Weight Number                       -- ^ /Valid for/: E; /Default/: @'Int' 1@; /Minimum/: @'Int' 0@ ('Dot'), @'Int' 1@ ('Neato','Fdp','Sfdp'); /Notes/: as of Graphviz 2.30: weights for dot need to be 'Int's
  | Width Double                        -- ^ /Valid for/: N; /Default/: @0.75@; /Minimum/: @0.01@
  | XDotVersion Version                 -- ^ /Valid for/: G; /Notes/: xdot only, requires Graphviz >= 2.34.0, equivalent to specifying version of xdot to be used
  | XLabel Label                        -- ^ /Valid for/: EN; /Default/: @'StrLabel' \"\"@; /Notes/: requires Graphviz >= 2.29.0
  | XLP Point                           -- ^ /Valid for/: EN; /Notes/: write only, requires Graphviz >= 2.29.0
  | UnknownAttribute AttributeName Text -- ^ /Valid for/: Assumed valid for all; the fields are 'Attribute' name and value respectively.
  deriving (Attribute -> Attribute -> Bool
(Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool) -> Eq Attribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c== :: Attribute -> Attribute -> Bool
Eq, Eq Attribute
Eq Attribute
-> (Attribute -> Attribute -> Ordering)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Attribute)
-> (Attribute -> Attribute -> Attribute)
-> Ord Attribute
Attribute -> Attribute -> Bool
Attribute -> Attribute -> Ordering
Attribute -> Attribute -> Attribute
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Attribute -> Attribute -> Attribute
$cmin :: Attribute -> Attribute -> Attribute
max :: Attribute -> Attribute -> Attribute
$cmax :: Attribute -> Attribute -> Attribute
>= :: Attribute -> Attribute -> Bool
$c>= :: Attribute -> Attribute -> Bool
> :: Attribute -> Attribute -> Bool
$c> :: Attribute -> Attribute -> Bool
<= :: Attribute -> Attribute -> Bool
$c<= :: Attribute -> Attribute -> Bool
< :: Attribute -> Attribute -> Bool
$c< :: Attribute -> Attribute -> Bool
compare :: Attribute -> Attribute -> Ordering
$ccompare :: Attribute -> Attribute -> Ordering
Ord, Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
(Int -> Attribute -> ShowS)
-> (Attribute -> String)
-> ([Attribute] -> ShowS)
-> Show Attribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> String
$cshow :: Attribute -> String
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show, ReadPrec [Attribute]
ReadPrec Attribute
Int -> ReadS Attribute
ReadS [Attribute]
(Int -> ReadS Attribute)
-> ReadS [Attribute]
-> ReadPrec Attribute
-> ReadPrec [Attribute]
-> Read Attribute
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Attribute]
$creadListPrec :: ReadPrec [Attribute]
readPrec :: ReadPrec Attribute
$creadPrec :: ReadPrec Attribute
readList :: ReadS [Attribute]
$creadList :: ReadS [Attribute]
readsPrec :: Int -> ReadS Attribute
$creadsPrec :: Int -> ReadS Attribute
Read)

type Attributes = [Attribute]

-- | The name for an UnknownAttribute; must satisfy  'validUnknown'.
type AttributeName = Text

instance PrintDot Attribute where
  unqtDot :: Attribute -> 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 :: [Attribute] -> DotCode
listToDot = [Attribute] -> DotCode
forall a. PrintDot a => [a] -> DotCode
unqtListToDot

instance ParseDot Attribute where
  parseUnqt :: Parse Attribute
parseUnqt = [(String, Parse Attribute)] -> Parse Attribute
forall a. [(String, Parse a)] -> Parse a
stringParse ([[(String, Parse Attribute)]] -> [(String, Parse Attribute)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Damping String
"Damping"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
K String
"K"
                                  , (AttributeName -> Attribute)
-> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields AttributeName -> Attribute
URL [String
"URL", String
"href"]
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Area String
"area"
                                  , (ArrowType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ArrowType -> Attribute
ArrowHead String
"arrowhead"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
ArrowSize String
"arrowsize"
                                  , (ArrowType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ArrowType -> Attribute
ArrowTail String
"arrowtail"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
Background String
"_background"
                                  , (Rect -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Rect -> Attribute
BoundingBox String
"bb"
                                  , (ColorList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorList -> Attribute
BgColor String
"bgcolor"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Center String
"center"
                                  , (ClusterMode -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ClusterMode -> Attribute
ClusterRank String
"clusterrank"
                                  , (ColorList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorList -> Attribute
Color String
"color"
                                  , (ColorScheme -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorScheme -> Attribute
ColorScheme String
"colorscheme"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
Comment String
"comment"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Compound String
"compound"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Concentrate String
"concentrate"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Constraint String
"constraint"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Decorate String
"decorate"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
DefaultDist String
"defaultdist"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Dim String
"dim"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Dimen String
"dimen"
                                  , (DirType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DirType -> Attribute
Dir String
"dir"
                                  , (DEConstraints -> Attribute)
-> DEConstraints -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef DEConstraints -> Attribute
DirEdgeConstraints DEConstraints
EdgeConstraints String
"diredgeconstraints"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Distortion String
"distortion"
                                  , (Double -> Attribute) -> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields Double -> Attribute
DPI [String
"dpi", String
"resolution"]
                                  , (AttributeName -> Attribute)
-> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields AttributeName -> Attribute
EdgeURL [String
"edgeURL", String
"edgehref"]
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
EdgeTarget String
"edgetarget"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
EdgeTooltip String
"edgetooltip"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Epsilon String
"epsilon"
                                  , (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
ESep String
"esep"
                                  , (ColorList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ColorList -> Attribute
FillColor String
"fillcolor"
                                  , (NodeSize -> Attribute)
-> NodeSize -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef NodeSize -> Attribute
FixedSize NodeSize
SetNodeSize String
"fixedsize"
                                  , (Color -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Color -> Attribute
FontColor String
"fontcolor"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
FontName String
"fontname"
                                  , (SVGFontNames -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField SVGFontNames -> Attribute
FontNames String
"fontnames"
                                  , (Paths -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Paths -> Attribute
FontPath String
"fontpath"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
FontSize String
"fontsize"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
ForceLabels String
"forcelabels"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
GradientAngle String
"gradientangle"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
Group String
"group"
                                  , (AttributeName -> Attribute)
-> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields AttributeName -> Attribute
HeadURL [String
"headURL", String
"headhref"]
                                  , (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
Head_LP String
"head_lp"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
HeadClip String
"headclip"
                                  , (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
HeadLabel String
"headlabel"
                                  , (PortPos -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PortPos -> Attribute
HeadPort String
"headport"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
HeadTarget String
"headtarget"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
HeadTooltip String
"headtooltip"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Height String
"height"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
ID String
"id"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
Image String
"image"
                                  , (Paths -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Paths -> Attribute
ImagePath String
"imagepath"
                                  , (ScaleType -> Attribute)
-> ScaleType -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef ScaleType -> Attribute
ImageScale ScaleType
UniformScale String
"imagescale"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
InputScale String
"inputscale"
                                  , (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
Label String
"label"
                                  , (AttributeName -> Attribute)
-> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields AttributeName -> Attribute
LabelURL [String
"labelURL", String
"labelhref"]
                                  , (LabelScheme -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LabelScheme -> Attribute
LabelScheme String
"label_scheme"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LabelAngle String
"labelangle"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LabelDistance String
"labeldistance"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
LabelFloat String
"labelfloat"
                                  , (Color -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Color -> Attribute
LabelFontColor String
"labelfontcolor"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
LabelFontName String
"labelfontname"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LabelFontSize String
"labelfontsize"
                                  , (Justification -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Justification -> Attribute
LabelJust String
"labeljust"
                                  , (VerticalPlacement -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField VerticalPlacement -> Attribute
LabelLoc String
"labelloc"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
LabelTarget String
"labeltarget"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
LabelTooltip String
"labeltooltip"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Landscape String
"landscape"
                                  , (LayerRange -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerRange -> Attribute
Layer String
"layer"
                                  , (LayerListSep -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerListSep -> Attribute
LayerListSep String
"layerlistsep"
                                  , (LayerList -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerList -> Attribute
Layers String
"layers"
                                  , (LayerRange -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerRange -> Attribute
LayerSelect String
"layerselect"
                                  , (LayerSep -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField LayerSep -> Attribute
LayerSep String
"layersep"
                                  , (GraphvizCommand -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField GraphvizCommand -> Attribute
Layout String
"layout"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Len String
"len"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Levels String
"levels"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LevelsGap String
"levelsgap"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
LHead String
"lhead"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LHeight String
"LHeight"
                                  , (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
LPos String
"lp"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
LTail String
"ltail"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
LWidth String
"lwidth"
                                  , (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Margin String
"margin"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
MaxIter String
"maxiter"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
MCLimit String
"mclimit"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
MinDist String
"mindist"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
MinLen String
"minlen"
                                  , (ModeType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ModeType -> Attribute
Mode String
"mode"
                                  , (Model -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Model -> Attribute
Model String
"model"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Mosek String
"mosek"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
NodeSep String
"nodesep"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
NoJustify String
"nojustify"
                                  , (Normalized -> Attribute)
-> Normalized -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Normalized -> Attribute
Normalize Normalized
IsNormalized String
"normalize"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
NoTranslate String
"notranslate"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Nslimit String
"nslimit"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Nslimit1 String
"nslimit1"
                                  , (Order -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Order -> Attribute
Ordering String
"ordering"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Orientation String
"orientation"
                                  , (OutputMode -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField OutputMode -> Attribute
OutputOrder String
"outputorder"
                                  , (Overlap -> Attribute)
-> Overlap -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Overlap -> Attribute
Overlap Overlap
KeepOverlaps String
"overlap"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
OverlapScaling String
"overlap_scaling"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
OverlapShrink String
"overlap_shrink"
                                  , (Pack -> Attribute)
-> Pack -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Pack -> Attribute
Pack Pack
DoPack String
"pack"
                                  , (PackMode -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PackMode -> Attribute
PackMode String
"packmode"
                                  , (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Pad String
"pad"
                                  , (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
Page String
"page"
                                  , (PageDir -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PageDir -> Attribute
PageDir String
"pagedir"
                                  , (Color -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Color -> Attribute
PenColor String
"pencolor"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
PenWidth String
"penwidth"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Peripheries String
"peripheries"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Pin String
"pin"
                                  , (Pos -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Pos -> Attribute
Pos String
"pos"
                                  , (QuadType -> Attribute)
-> QuadType -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef QuadType -> Attribute
QuadTree QuadType
NormalQT String
"quadtree"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Quantum String
"quantum"
                                  , (RankType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField RankType -> Attribute
Rank String
"rank"
                                  , (RankDir -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField RankDir -> Attribute
RankDir String
"rankdir"
                                  , ([Double] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [Double] -> Attribute
RankSep String
"ranksep"
                                  , (Ratios -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Ratios -> Attribute
Ratio String
"ratio"
                                  , ([Rect] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [Rect] -> Attribute
Rects String
"rects"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
Regular String
"regular"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
ReMinCross String
"remincross"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
RepulsiveForce String
"repulsiveforce"
                                  , (Root -> Attribute)
-> Root -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef Root -> Attribute
Root Root
IsCentral String
"root"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Rotate String
"rotate"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Rotation String
"rotation"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
SameHead String
"samehead"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
SameTail String
"sametail"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
SamplePoints String
"samplepoints"
                                  , (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Scale String
"scale"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
SearchSize String
"searchsize"
                                  , (DPoint -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField DPoint -> Attribute
Sep String
"sep"
                                  , (Shape -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Shape -> Attribute
Shape String
"shape"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
ShowBoxes String
"showboxes"
                                  , (Int -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Int -> Attribute
Sides String
"sides"
                                  , (GraphSize -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField GraphSize -> Attribute
Size String
"size"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Skew String
"skew"
                                  , (SmoothType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField SmoothType -> Attribute
Smoothing String
"smoothing"
                                  , (Word16 -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Word16 -> Attribute
SortV String
"sortv"
                                  , (EdgeType -> Attribute)
-> EdgeType -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef EdgeType -> Attribute
Splines EdgeType
SplineEdges String
"splines"
                                  , (StartType -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField StartType -> Attribute
Start String
"start"
                                  , ([StyleItem] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [StyleItem] -> Attribute
Style String
"style"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
StyleSheet String
"stylesheet"
                                  , (AttributeName -> Attribute)
-> [String] -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields AttributeName -> Attribute
TailURL [String
"tailURL", String
"tailhref"]
                                  , (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
Tail_LP String
"tail_lp"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
TailClip String
"tailclip"
                                  , (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
TailLabel String
"taillabel"
                                  , (PortPos -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField PortPos -> Attribute
TailPort String
"tailport"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
TailTarget String
"tailtarget"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
TailTooltip String
"tailtooltip"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
Target String
"target"
                                  , (AttributeName -> Attribute)
-> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField AttributeName -> Attribute
Tooltip String
"tooltip"
                                  , (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool Bool -> Attribute
TrueColor String
"truecolor"
                                  , ([Point] -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField [Point] -> Attribute
Vertices String
"vertices"
                                  , (ViewPort -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField ViewPort -> Attribute
ViewPort String
"viewport"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
VoroMargin String
"voro_margin"
                                  , (Number -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Number -> Attribute
Weight String
"weight"
                                  , (Double -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Double -> Attribute
Width String
"width"
                                  , (Version -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Version -> Attribute
XDotVersion String
"xdotversion"
                                  , (Label -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Label -> Attribute
XLabel String
"xlabel"
                                  , (Point -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField Point -> Attribute
XLP String
"xlp"
                                  ])
              Parse Attribute -> Parse Attribute -> Parse Attribute
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
              do AttributeName
attrName <- Parse AttributeName
stringBlock
                 String -> (AttributeName -> Attribute) -> Parse Attribute
forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
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 -> Attribute
UnknownAttribute AttributeName
attrName)

  parse :: Parse Attribute
parse = Parse Attribute
forall a. ParseDot a => Parse a
parseUnqt

  parseList :: Parse [Attribute]
parseList = Parse [Attribute]
forall a. ParseDot a => Parse [a]
parseUnqtList

-- | Determine if this 'Attribute' is valid for use with Graphs.
usedByGraphs                      :: Attribute -> Bool
usedByGraphs :: Attribute -> Bool
usedByGraphs Damping{}            = Bool
True
usedByGraphs K{}                  = Bool
True
usedByGraphs URL{}                = Bool
True
usedByGraphs Background{}         = Bool
True
usedByGraphs BoundingBox{}        = Bool
True
usedByGraphs BgColor{}            = Bool
True
usedByGraphs Center{}             = Bool
True
usedByGraphs ClusterRank{}        = Bool
True
usedByGraphs ColorScheme{}        = Bool
True
usedByGraphs Comment{}            = Bool
True
usedByGraphs Compound{}           = Bool
True
usedByGraphs Concentrate{}        = Bool
True
usedByGraphs DefaultDist{}        = Bool
True
usedByGraphs Dim{}                = Bool
True
usedByGraphs Dimen{}              = Bool
True
usedByGraphs DirEdgeConstraints{} = Bool
True
usedByGraphs DPI{}                = Bool
True
usedByGraphs Epsilon{}            = Bool
True
usedByGraphs ESep{}               = Bool
True
usedByGraphs FontColor{}          = Bool
True
usedByGraphs FontName{}           = Bool
True
usedByGraphs FontNames{}          = Bool
True
usedByGraphs FontPath{}           = Bool
True
usedByGraphs FontSize{}           = Bool
True
usedByGraphs ForceLabels{}        = Bool
True
usedByGraphs GradientAngle{}      = Bool
True
usedByGraphs ID{}                 = Bool
True
usedByGraphs ImagePath{}          = Bool
True
usedByGraphs Label{}              = Bool
True
usedByGraphs LabelScheme{}        = Bool
True
usedByGraphs LabelJust{}          = Bool
True
usedByGraphs LabelLoc{}           = Bool
True
usedByGraphs Landscape{}          = Bool
True
usedByGraphs LayerListSep{}       = Bool
True
usedByGraphs Layers{}             = Bool
True
usedByGraphs LayerSelect{}        = Bool
True
usedByGraphs LayerSep{}           = Bool
True
usedByGraphs Layout{}             = Bool
True
usedByGraphs Levels{}             = Bool
True
usedByGraphs LevelsGap{}          = Bool
True
usedByGraphs LHeight{}            = Bool
True
usedByGraphs LPos{}               = Bool
True
usedByGraphs LWidth{}             = Bool
True
usedByGraphs Margin{}             = Bool
True
usedByGraphs MaxIter{}            = Bool
True
usedByGraphs MCLimit{}            = Bool
True
usedByGraphs MinDist{}            = Bool
True
usedByGraphs Mode{}               = Bool
True
usedByGraphs Model{}              = Bool
True
usedByGraphs Mosek{}              = Bool
True
usedByGraphs NodeSep{}            = Bool
True
usedByGraphs NoJustify{}          = Bool
True
usedByGraphs Normalize{}          = Bool
True
usedByGraphs NoTranslate{}        = Bool
True
usedByGraphs Nslimit{}            = Bool
True
usedByGraphs Nslimit1{}           = Bool
True
usedByGraphs Ordering{}           = Bool
True
usedByGraphs OutputOrder{}        = Bool
True
usedByGraphs Overlap{}            = Bool
True
usedByGraphs OverlapScaling{}     = Bool
True
usedByGraphs OverlapShrink{}      = Bool
True
usedByGraphs Pack{}               = Bool
True
usedByGraphs PackMode{}           = Bool
True
usedByGraphs Pad{}                = Bool
True
usedByGraphs Page{}               = Bool
True
usedByGraphs PageDir{}            = Bool
True
usedByGraphs QuadTree{}           = Bool
True
usedByGraphs Quantum{}            = Bool
True
usedByGraphs RankDir{}            = Bool
True
usedByGraphs RankSep{}            = Bool
True
usedByGraphs Ratio{}              = Bool
True
usedByGraphs ReMinCross{}         = Bool
True
usedByGraphs RepulsiveForce{}     = Bool
True
usedByGraphs Root{}               = Bool
True
usedByGraphs Rotate{}             = Bool
True
usedByGraphs Rotation{}           = Bool
True
usedByGraphs Scale{}              = Bool
True
usedByGraphs SearchSize{}         = Bool
True
usedByGraphs Sep{}                = Bool
True
usedByGraphs ShowBoxes{}          = Bool
True
usedByGraphs Size{}               = Bool
True
usedByGraphs Smoothing{}          = Bool
True
usedByGraphs SortV{}              = Bool
True
usedByGraphs Splines{}            = Bool
True
usedByGraphs Start{}              = Bool
True
usedByGraphs Style{}              = Bool
True
usedByGraphs StyleSheet{}         = Bool
True
usedByGraphs Target{}             = Bool
True
usedByGraphs TrueColor{}          = Bool
True
usedByGraphs ViewPort{}           = Bool
True
usedByGraphs VoroMargin{}         = Bool
True
usedByGraphs XDotVersion{}        = Bool
True
usedByGraphs UnknownAttribute{}   = Bool
True
usedByGraphs Attribute
_                    = Bool
False

-- | Determine if this 'Attribute' is valid for use with Clusters.
usedByClusters                    :: Attribute -> Bool
usedByClusters :: Attribute -> Bool
usedByClusters K{}                = Bool
True
usedByClusters URL{}              = Bool
True
usedByClusters Area{}             = Bool
True
usedByClusters BgColor{}          = Bool
True
usedByClusters Color{}            = Bool
True
usedByClusters ColorScheme{}      = Bool
True
usedByClusters FillColor{}        = Bool
True
usedByClusters FontColor{}        = Bool
True
usedByClusters FontName{}         = Bool
True
usedByClusters FontSize{}         = Bool
True
usedByClusters GradientAngle{}    = Bool
True
usedByClusters Label{}            = Bool
True
usedByClusters LabelJust{}        = Bool
True
usedByClusters LabelLoc{}         = Bool
True
usedByClusters Layer{}            = Bool
True
usedByClusters LHeight{}          = Bool
True
usedByClusters LPos{}             = Bool
True
usedByClusters LWidth{}           = Bool
True
usedByClusters Margin{}           = Bool
True
usedByClusters NoJustify{}        = Bool
True
usedByClusters PenColor{}         = Bool
True
usedByClusters PenWidth{}         = Bool
True
usedByClusters Peripheries{}      = Bool
True
usedByClusters Rank{}             = Bool
True
usedByClusters SortV{}            = Bool
True
usedByClusters Style{}            = Bool
True
usedByClusters Target{}           = Bool
True
usedByClusters Tooltip{}          = Bool
True
usedByClusters UnknownAttribute{} = Bool
True
usedByClusters Attribute
_                  = Bool
False

-- | Determine if this 'Attribute' is valid for use with SubGraphs.
usedBySubGraphs                    :: Attribute -> Bool
usedBySubGraphs :: Attribute -> Bool
usedBySubGraphs Rank{}             = Bool
True
usedBySubGraphs UnknownAttribute{} = Bool
True
usedBySubGraphs Attribute
_                  = Bool
False

-- | Determine if this 'Attribute' is valid for use with Nodes.
usedByNodes                    :: Attribute -> Bool
usedByNodes :: Attribute -> Bool
usedByNodes URL{}              = Bool
True
usedByNodes Area{}             = Bool
True
usedByNodes Color{}            = Bool
True
usedByNodes ColorScheme{}      = Bool
True
usedByNodes Comment{}          = Bool
True
usedByNodes Distortion{}       = Bool
True
usedByNodes FillColor{}        = Bool
True
usedByNodes FixedSize{}        = Bool
True
usedByNodes FontColor{}        = Bool
True
usedByNodes FontName{}         = Bool
True
usedByNodes FontSize{}         = Bool
True
usedByNodes GradientAngle{}    = Bool
True
usedByNodes Group{}            = Bool
True
usedByNodes Height{}           = Bool
True
usedByNodes ID{}               = Bool
True
usedByNodes Image{}            = Bool
True
usedByNodes ImageScale{}       = Bool
True
usedByNodes InputScale{}       = Bool
True
usedByNodes Label{}            = Bool
True
usedByNodes LabelLoc{}         = Bool
True
usedByNodes Layer{}            = Bool
True
usedByNodes Margin{}           = Bool
True
usedByNodes NoJustify{}        = Bool
True
usedByNodes Ordering{}         = Bool
True
usedByNodes Orientation{}      = Bool
True
usedByNodes PenWidth{}         = Bool
True
usedByNodes Peripheries{}      = Bool
True
usedByNodes Pin{}              = Bool
True
usedByNodes Pos{}              = Bool
True
usedByNodes Rects{}            = Bool
True
usedByNodes Regular{}          = Bool
True
usedByNodes Root{}             = Bool
True
usedByNodes SamplePoints{}     = Bool
True
usedByNodes Shape{}            = Bool
True
usedByNodes ShowBoxes{}        = Bool
True
usedByNodes Sides{}            = Bool
True
usedByNodes Skew{}             = Bool
True
usedByNodes SortV{}            = Bool
True
usedByNodes Style{}            = Bool
True
usedByNodes Target{}           = Bool
True
usedByNodes Tooltip{}          = Bool
True
usedByNodes Vertices{}         = Bool
True
usedByNodes Width{}            = Bool
True
usedByNodes XLabel{}           = Bool
True
usedByNodes XLP{}              = Bool
True
usedByNodes UnknownAttribute{} = Bool
True
usedByNodes Attribute
_                  = Bool
False

-- | Determine if this 'Attribute' is valid for use with Edges.
usedByEdges                    :: Attribute -> Bool
usedByEdges :: Attribute -> Bool
usedByEdges URL{}              = Bool
True
usedByEdges ArrowHead{}        = Bool
True
usedByEdges ArrowSize{}        = Bool
True
usedByEdges ArrowTail{}        = Bool
True
usedByEdges Color{}            = Bool
True
usedByEdges ColorScheme{}      = Bool
True
usedByEdges Comment{}          = Bool
True
usedByEdges Constraint{}       = Bool
True
usedByEdges Decorate{}         = Bool
True
usedByEdges Dir{}              = Bool
True
usedByEdges EdgeURL{}          = Bool
True
usedByEdges EdgeTarget{}       = Bool
True
usedByEdges EdgeTooltip{}      = Bool
True
usedByEdges FillColor{}        = Bool
True
usedByEdges FontColor{}        = Bool
True
usedByEdges FontName{}         = Bool
True
usedByEdges FontSize{}         = Bool
True
usedByEdges HeadURL{}          = Bool
True
usedByEdges Head_LP{}          = Bool
True
usedByEdges HeadClip{}         = Bool
True
usedByEdges HeadLabel{}        = Bool
True
usedByEdges HeadPort{}         = Bool
True
usedByEdges HeadTarget{}       = Bool
True
usedByEdges HeadTooltip{}      = Bool
True
usedByEdges ID{}               = Bool
True
usedByEdges Label{}            = Bool
True
usedByEdges LabelURL{}         = Bool
True
usedByEdges LabelAngle{}       = Bool
True
usedByEdges LabelDistance{}    = Bool
True
usedByEdges LabelFloat{}       = Bool
True
usedByEdges LabelFontColor{}   = Bool
True
usedByEdges LabelFontName{}    = Bool
True
usedByEdges LabelFontSize{}    = Bool
True
usedByEdges LabelTarget{}      = Bool
True
usedByEdges LabelTooltip{}     = Bool
True
usedByEdges Layer{}            = Bool
True
usedByEdges Len{}              = Bool
True
usedByEdges LHead{}            = Bool
True
usedByEdges LPos{}             = Bool
True
usedByEdges LTail{}            = Bool
True
usedByEdges MinLen{}           = Bool
True
usedByEdges NoJustify{}        = Bool
True
usedByEdges PenWidth{}         = Bool
True
usedByEdges Pos{}              = Bool
True
usedByEdges SameHead{}         = Bool
True
usedByEdges SameTail{}         = Bool
True
usedByEdges ShowBoxes{}        = Bool
True
usedByEdges Style{}            = Bool
True
usedByEdges TailURL{}          = Bool
True
usedByEdges Tail_LP{}          = Bool
True
usedByEdges TailClip{}         = Bool
True
usedByEdges TailLabel{}        = Bool
True
usedByEdges TailPort{}         = Bool
True
usedByEdges TailTarget{}       = Bool
True
usedByEdges TailTooltip{}      = Bool
True
usedByEdges Target{}           = Bool
True
usedByEdges Tooltip{}          = Bool
True
usedByEdges Weight{}           = Bool
True
usedByEdges XLabel{}           = Bool
True
usedByEdges XLP{}              = Bool
True
usedByEdges UnknownAttribute{} = Bool
True
usedByEdges Attribute
_                  = Bool
False

-- | Determine if two 'Attributes' are the same type of 'Attribute'.
sameAttribute                                                 :: Attribute -> Attribute -> Bool
sameAttribute :: Attribute -> Attribute -> Bool
sameAttribute Damping{}               Damping{}               = Bool
True
sameAttribute K{}                     K{}                     = Bool
True
sameAttribute URL{}                   URL{}                   = Bool
True
sameAttribute Area{}                  Area{}                  = Bool
True
sameAttribute ArrowHead{}             ArrowHead{}             = Bool
True
sameAttribute ArrowSize{}             ArrowSize{}             = Bool
True
sameAttribute ArrowTail{}             ArrowTail{}             = Bool
True
sameAttribute Background{}            Background{}            = Bool
True
sameAttribute BoundingBox{}           BoundingBox{}           = Bool
True
sameAttribute BgColor{}               BgColor{}               = Bool
True
sameAttribute Center{}                Center{}                = Bool
True
sameAttribute ClusterRank{}           ClusterRank{}           = Bool
True
sameAttribute Color{}                 Color{}                 = Bool
True
sameAttribute ColorScheme{}           ColorScheme{}           = Bool
True
sameAttribute Comment{}               Comment{}               = Bool
True
sameAttribute Compound{}              Compound{}              = Bool
True
sameAttribute Concentrate{}           Concentrate{}           = Bool
True
sameAttribute Constraint{}            Constraint{}            = Bool
True
sameAttribute Decorate{}              Decorate{}              = Bool
True
sameAttribute DefaultDist{}           DefaultDist{}           = Bool
True
sameAttribute Dim{}                   Dim{}                   = Bool
True
sameAttribute Dimen{}                 Dimen{}                 = Bool
True
sameAttribute Dir{}                   Dir{}                   = Bool
True
sameAttribute DirEdgeConstraints{}    DirEdgeConstraints{}    = Bool
True
sameAttribute Distortion{}            Distortion{}            = Bool
True
sameAttribute DPI{}                   DPI{}                   = Bool
True
sameAttribute EdgeURL{}               EdgeURL{}               = Bool
True
sameAttribute EdgeTarget{}            EdgeTarget{}            = Bool
True
sameAttribute EdgeTooltip{}           EdgeTooltip{}           = Bool
True
sameAttribute Epsilon{}               Epsilon{}               = Bool
True
sameAttribute ESep{}                  ESep{}                  = Bool
True
sameAttribute FillColor{}             FillColor{}             = Bool
True
sameAttribute FixedSize{}             FixedSize{}             = Bool
True
sameAttribute FontColor{}             FontColor{}             = Bool
True
sameAttribute FontName{}              FontName{}              = Bool
True
sameAttribute FontNames{}             FontNames{}             = Bool
True
sameAttribute FontPath{}              FontPath{}              = Bool
True
sameAttribute FontSize{}              FontSize{}              = Bool
True
sameAttribute ForceLabels{}           ForceLabels{}           = Bool
True
sameAttribute GradientAngle{}         GradientAngle{}         = Bool
True
sameAttribute Group{}                 Group{}                 = Bool
True
sameAttribute HeadURL{}               HeadURL{}               = Bool
True
sameAttribute Head_LP{}               Head_LP{}               = Bool
True
sameAttribute HeadClip{}              HeadClip{}              = Bool
True
sameAttribute HeadLabel{}             HeadLabel{}             = Bool
True
sameAttribute HeadPort{}              HeadPort{}              = Bool
True
sameAttribute HeadTarget{}            HeadTarget{}            = Bool
True
sameAttribute HeadTooltip{}           HeadTooltip{}           = Bool
True
sameAttribute Height{}                Height{}                = Bool
True
sameAttribute ID{}                    ID{}                    = Bool
True
sameAttribute Image{}                 Image{}                 = Bool
True
sameAttribute ImagePath{}             ImagePath{}             = Bool
True
sameAttribute ImageScale{}            ImageScale{}            = Bool
True
sameAttribute InputScale{}            InputScale{}            = Bool
True
sameAttribute Label{}                 Label{}                 = Bool
True
sameAttribute LabelURL{}              LabelURL{}              = Bool
True
sameAttribute LabelScheme{}           LabelScheme{}           = Bool
True
sameAttribute LabelAngle{}            LabelAngle{}            = Bool
True
sameAttribute LabelDistance{}         LabelDistance{}         = Bool
True
sameAttribute LabelFloat{}            LabelFloat{}            = Bool
True
sameAttribute LabelFontColor{}        LabelFontColor{}        = Bool
True
sameAttribute LabelFontName{}         LabelFontName{}         = Bool
True
sameAttribute LabelFontSize{}         LabelFontSize{}         = Bool
True
sameAttribute LabelJust{}             LabelJust{}             = Bool
True
sameAttribute LabelLoc{}              LabelLoc{}              = Bool
True
sameAttribute LabelTarget{}           LabelTarget{}           = Bool
True
sameAttribute LabelTooltip{}          LabelTooltip{}          = Bool
True
sameAttribute Landscape{}             Landscape{}             = Bool
True
sameAttribute Layer{}                 Layer{}                 = Bool
True
sameAttribute LayerListSep{}          LayerListSep{}          = Bool
True
sameAttribute Layers{}                Layers{}                = Bool
True
sameAttribute LayerSelect{}           LayerSelect{}           = Bool
True
sameAttribute LayerSep{}              LayerSep{}              = Bool
True
sameAttribute Layout{}                Layout{}                = Bool
True
sameAttribute Len{}                   Len{}                   = Bool
True
sameAttribute Levels{}                Levels{}                = Bool
True
sameAttribute LevelsGap{}             LevelsGap{}             = Bool
True
sameAttribute LHead{}                 LHead{}                 = Bool
True
sameAttribute LHeight{}               LHeight{}               = Bool
True
sameAttribute LPos{}                  LPos{}                  = Bool
True
sameAttribute LTail{}                 LTail{}                 = Bool
True
sameAttribute LWidth{}                LWidth{}                = Bool
True
sameAttribute Margin{}                Margin{}                = Bool
True
sameAttribute MaxIter{}               MaxIter{}               = Bool
True
sameAttribute MCLimit{}               MCLimit{}               = Bool
True
sameAttribute MinDist{}               MinDist{}               = Bool
True
sameAttribute MinLen{}                MinLen{}                = Bool
True
sameAttribute Mode{}                  Mode{}                  = Bool
True
sameAttribute Model{}                 Model{}                 = Bool
True
sameAttribute Mosek{}                 Mosek{}                 = Bool
True
sameAttribute NodeSep{}               NodeSep{}               = Bool
True
sameAttribute NoJustify{}             NoJustify{}             = Bool
True
sameAttribute Normalize{}             Normalize{}             = Bool
True
sameAttribute NoTranslate{}           NoTranslate{}           = Bool
True
sameAttribute Nslimit{}               Nslimit{}               = Bool
True
sameAttribute Nslimit1{}              Nslimit1{}              = Bool
True
sameAttribute Ordering{}              Ordering{}              = Bool
True
sameAttribute Orientation{}           Orientation{}           = Bool
True
sameAttribute OutputOrder{}           OutputOrder{}           = Bool
True
sameAttribute Overlap{}               Overlap{}               = Bool
True
sameAttribute OverlapScaling{}        OverlapScaling{}        = Bool
True
sameAttribute OverlapShrink{}         OverlapShrink{}         = Bool
True
sameAttribute Pack{}                  Pack{}                  = Bool
True
sameAttribute PackMode{}              PackMode{}              = Bool
True
sameAttribute Pad{}                   Pad{}                   = Bool
True
sameAttribute Page{}                  Page{}                  = Bool
True
sameAttribute PageDir{}               PageDir{}               = Bool
True
sameAttribute PenColor{}              PenColor{}              = Bool
True
sameAttribute PenWidth{}              PenWidth{}              = Bool
True
sameAttribute Peripheries{}           Peripheries{}           = Bool
True
sameAttribute Pin{}                   Pin{}                   = Bool
True
sameAttribute Pos{}                   Pos{}                   = Bool
True
sameAttribute QuadTree{}              QuadTree{}              = Bool
True
sameAttribute Quantum{}               Quantum{}               = Bool
True
sameAttribute Rank{}                  Rank{}                  = Bool
True
sameAttribute RankDir{}               RankDir{}               = Bool
True
sameAttribute RankSep{}               RankSep{}               = Bool
True
sameAttribute Ratio{}                 Ratio{}                 = Bool
True
sameAttribute Rects{}                 Rects{}                 = Bool
True
sameAttribute Regular{}               Regular{}               = Bool
True
sameAttribute ReMinCross{}            ReMinCross{}            = Bool
True
sameAttribute RepulsiveForce{}        RepulsiveForce{}        = Bool
True
sameAttribute Root{}                  Root{}                  = Bool
True
sameAttribute Rotate{}                Rotate{}                = Bool
True
sameAttribute Rotation{}              Rotation{}              = Bool
True
sameAttribute SameHead{}              SameHead{}              = Bool
True
sameAttribute SameTail{}              SameTail{}              = Bool
True
sameAttribute SamplePoints{}          SamplePoints{}          = Bool
True
sameAttribute Scale{}                 Scale{}                 = Bool
True
sameAttribute SearchSize{}            SearchSize{}            = Bool
True
sameAttribute Sep{}                   Sep{}                   = Bool
True
sameAttribute Shape{}                 Shape{}                 = Bool
True
sameAttribute ShowBoxes{}             ShowBoxes{}             = Bool
True
sameAttribute Sides{}                 Sides{}                 = Bool
True
sameAttribute Size{}                  Size{}                  = Bool
True
sameAttribute Skew{}                  Skew{}                  = Bool
True
sameAttribute Smoothing{}             Smoothing{}             = Bool
True
sameAttribute SortV{}                 SortV{}                 = Bool
True
sameAttribute Splines{}               Splines{}               = Bool
True
sameAttribute Start{}                 Start{}                 = Bool
True
sameAttribute Style{}                 Style{}                 = Bool
True
sameAttribute StyleSheet{}            StyleSheet{}            = Bool
True
sameAttribute TailURL{}               TailURL{}               = Bool
True
sameAttribute Tail_LP{}               Tail_LP{}               = Bool
True
sameAttribute TailClip{}              TailClip{}              = Bool
True
sameAttribute TailLabel{}             TailLabel{}             = Bool
True
sameAttribute TailPort{}              TailPort{}              = Bool
True
sameAttribute TailTarget{}            TailTarget{}            = Bool
True
sameAttribute TailTooltip{}           TailTooltip{}           = Bool
True
sameAttribute Target{}                Target{}                = Bool
True
sameAttribute Tooltip{}               Tooltip{}               = Bool
True
sameAttribute TrueColor{}             TrueColor{}             = Bool
True
sameAttribute Vertices{}              Vertices{}              = Bool
True
sameAttribute ViewPort{}              ViewPort{}              = Bool
True
sameAttribute VoroMargin{}            VoroMargin{}            = Bool
True
sameAttribute Weight{}                Weight{}                = Bool
True
sameAttribute Width{}                 Width{}                 = Bool
True
sameAttribute XDotVersion{}           XDotVersion{}           = Bool
True
sameAttribute XLabel{}                XLabel{}                = Bool
True
sameAttribute XLP{}                   XLP{}                   = Bool
True
sameAttribute (UnknownAttribute AttributeName
a1 AttributeName
_) (UnknownAttribute AttributeName
a2 AttributeName
_) = AttributeName
a1 AttributeName -> AttributeName -> Bool
forall a. Eq a => a -> a -> Bool
== AttributeName
a2
sameAttribute Attribute
_                       Attribute
_                       = Bool
False

-- | Return the default value for a specific 'Attribute' if possible; graph/cluster values are preferred over node/edge values.
defaultAttributeValue                      :: Attribute -> Maybe Attribute
defaultAttributeValue :: Attribute -> Maybe Attribute
defaultAttributeValue Damping{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Damping Double
0.99
defaultAttributeValue K{}                  = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
K Double
0.3
defaultAttributeValue URL{}                = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
URL AttributeName
""
defaultAttributeValue Area{}               = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Area Double
1.0
defaultAttributeValue ArrowHead{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ArrowType -> Attribute
ArrowHead ArrowType
normal
defaultAttributeValue ArrowSize{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
ArrowSize Double
1.0
defaultAttributeValue ArrowTail{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ArrowType -> Attribute
ArrowTail ArrowType
normal
defaultAttributeValue Background{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
Background AttributeName
""
defaultAttributeValue BgColor{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorList -> Attribute
BgColor []
defaultAttributeValue Center{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Center Bool
False
defaultAttributeValue ClusterRank{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ClusterMode -> Attribute
ClusterRank ClusterMode
Local
defaultAttributeValue Color{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorList -> Attribute
Color [X11Color -> WeightedColor
forall nc. NamedColor nc => nc -> WeightedColor
toWColor X11Color
Black]
defaultAttributeValue ColorScheme{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorScheme -> Attribute
ColorScheme ColorScheme
X11
defaultAttributeValue Comment{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
Comment AttributeName
""
defaultAttributeValue Compound{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Compound Bool
False
defaultAttributeValue Concentrate{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Concentrate Bool
False
defaultAttributeValue Constraint{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Constraint Bool
True
defaultAttributeValue Decorate{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Decorate Bool
False
defaultAttributeValue Dim{}                = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Dim Int
2
defaultAttributeValue Dimen{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Dimen Int
2
defaultAttributeValue DirEdgeConstraints{} = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DEConstraints -> Attribute
DirEdgeConstraints DEConstraints
NoConstraints
defaultAttributeValue Distortion{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Distortion Double
0.0
defaultAttributeValue DPI{}                = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
DPI Double
96.0
defaultAttributeValue EdgeURL{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
EdgeURL AttributeName
""
defaultAttributeValue EdgeTooltip{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
EdgeTooltip AttributeName
""
defaultAttributeValue ESep{}               = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DPoint -> Attribute
ESep (Double -> DPoint
DVal Double
3)
defaultAttributeValue FillColor{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ColorList -> Attribute
FillColor [X11Color -> WeightedColor
forall nc. NamedColor nc => nc -> WeightedColor
toWColor X11Color
Black]
defaultAttributeValue FixedSize{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ NodeSize -> Attribute
FixedSize NodeSize
GrowAsNeeded
defaultAttributeValue FontColor{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Color -> Attribute
FontColor (X11Color -> Color
X11Color X11Color
Black)
defaultAttributeValue FontName{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
FontName AttributeName
"Times-Roman"
defaultAttributeValue FontNames{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ SVGFontNames -> Attribute
FontNames SVGFontNames
SvgNames
defaultAttributeValue FontSize{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
FontSize Double
14.0
defaultAttributeValue ForceLabels{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
ForceLabels Bool
True
defaultAttributeValue GradientAngle{}      = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
GradientAngle Int
0
defaultAttributeValue Group{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
Group AttributeName
""
defaultAttributeValue HeadURL{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
HeadURL AttributeName
""
defaultAttributeValue HeadClip{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
HeadClip Bool
True
defaultAttributeValue HeadLabel{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
HeadLabel (AttributeName -> Label
StrLabel AttributeName
"")
defaultAttributeValue HeadPort{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PortPos -> Attribute
HeadPort (CompassPoint -> PortPos
CompassPoint CompassPoint
CenterPoint)
defaultAttributeValue HeadTarget{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
HeadTarget AttributeName
""
defaultAttributeValue HeadTooltip{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
HeadTooltip AttributeName
""
defaultAttributeValue Height{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Height Double
0.5
defaultAttributeValue ID{}                 = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
ID AttributeName
""
defaultAttributeValue Image{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
Image AttributeName
""
defaultAttributeValue ImagePath{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Paths -> Attribute
ImagePath ([String] -> Paths
Paths [])
defaultAttributeValue ImageScale{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ScaleType -> Attribute
ImageScale ScaleType
NoScale
defaultAttributeValue Label{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
Label (AttributeName -> Label
StrLabel AttributeName
"")
defaultAttributeValue LabelURL{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
LabelURL AttributeName
""
defaultAttributeValue LabelScheme{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LabelScheme -> Attribute
LabelScheme LabelScheme
NotEdgeLabel
defaultAttributeValue LabelAngle{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LabelAngle (-Double
25.0)
defaultAttributeValue LabelDistance{}      = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LabelDistance Double
1.0
defaultAttributeValue LabelFloat{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
LabelFloat Bool
False
defaultAttributeValue LabelFontColor{}     = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Color -> Attribute
LabelFontColor (X11Color -> Color
X11Color X11Color
Black)
defaultAttributeValue LabelFontName{}      = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
LabelFontName AttributeName
"Times-Roman"
defaultAttributeValue LabelFontSize{}      = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LabelFontSize Double
14.0
defaultAttributeValue LabelJust{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Justification -> Attribute
LabelJust Justification
JCenter
defaultAttributeValue LabelLoc{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ VerticalPlacement -> Attribute
LabelLoc VerticalPlacement
VTop
defaultAttributeValue LabelTarget{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
LabelTarget AttributeName
""
defaultAttributeValue LabelTooltip{}       = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
LabelTooltip AttributeName
""
defaultAttributeValue Landscape{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Landscape Bool
False
defaultAttributeValue Layer{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerRange -> Attribute
Layer []
defaultAttributeValue LayerListSep{}       = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerListSep -> Attribute
LayerListSep (AttributeName -> LayerListSep
LLSep AttributeName
",")
defaultAttributeValue Layers{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerList -> Attribute
Layers ([LayerID] -> LayerList
LL [])
defaultAttributeValue LayerSelect{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerRange -> Attribute
LayerSelect []
defaultAttributeValue LayerSep{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ LayerSep -> Attribute
LayerSep (AttributeName -> LayerSep
LSep AttributeName
" :\t")
defaultAttributeValue Levels{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Levels Int
forall a. Bounded a => a
maxBound
defaultAttributeValue LevelsGap{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
LevelsGap Double
0.0
defaultAttributeValue LHead{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
LHead AttributeName
""
defaultAttributeValue LTail{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
LTail AttributeName
""
defaultAttributeValue MCLimit{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
MCLimit Double
1.0
defaultAttributeValue MinDist{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
MinDist Double
1.0
defaultAttributeValue MinLen{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
MinLen Int
1
defaultAttributeValue Mode{}               = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ ModeType -> Attribute
Mode ModeType
Major
defaultAttributeValue Model{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Model -> Attribute
Model Model
ShortPath
defaultAttributeValue Mosek{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Mosek Bool
False
defaultAttributeValue NodeSep{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
NodeSep Double
0.25
defaultAttributeValue NoJustify{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
NoJustify Bool
False
defaultAttributeValue Normalize{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Normalized -> Attribute
Normalize Normalized
NotNormalized
defaultAttributeValue NoTranslate{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
NoTranslate Bool
False
defaultAttributeValue Orientation{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Orientation Double
0.0
defaultAttributeValue OutputOrder{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ OutputMode -> Attribute
OutputOrder OutputMode
BreadthFirst
defaultAttributeValue Overlap{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Overlap -> Attribute
Overlap Overlap
KeepOverlaps
defaultAttributeValue OverlapScaling{}     = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
OverlapScaling (-Double
4)
defaultAttributeValue OverlapShrink{}      = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
OverlapShrink Bool
True
defaultAttributeValue Pack{}               = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Pack -> Attribute
Pack Pack
DontPack
defaultAttributeValue PackMode{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PackMode -> Attribute
PackMode PackMode
PackNode
defaultAttributeValue Pad{}                = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DPoint -> Attribute
Pad (Double -> DPoint
DVal Double
0.0555)
defaultAttributeValue PageDir{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PageDir -> Attribute
PageDir PageDir
Bl
defaultAttributeValue PenColor{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Color -> Attribute
PenColor (X11Color -> Color
X11Color X11Color
Black)
defaultAttributeValue PenWidth{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
PenWidth Double
1.0
defaultAttributeValue Peripheries{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Peripheries Int
1
defaultAttributeValue Pin{}                = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Pin Bool
False
defaultAttributeValue QuadTree{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ QuadType -> Attribute
QuadTree QuadType
NormalQT
defaultAttributeValue Quantum{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Quantum Double
0
defaultAttributeValue RankDir{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ RankDir -> Attribute
RankDir RankDir
FromTop
defaultAttributeValue Regular{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
Regular Bool
False
defaultAttributeValue ReMinCross{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
ReMinCross Bool
False
defaultAttributeValue RepulsiveForce{}     = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
RepulsiveForce Double
1.0
defaultAttributeValue Root{}               = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Root -> Attribute
Root (AttributeName -> Root
NodeName AttributeName
"")
defaultAttributeValue Rotate{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Rotate Int
0
defaultAttributeValue Rotation{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Rotation Double
0
defaultAttributeValue SameHead{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
SameHead AttributeName
""
defaultAttributeValue SameTail{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
SameTail AttributeName
""
defaultAttributeValue SearchSize{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
SearchSize Int
30
defaultAttributeValue Sep{}                = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ DPoint -> Attribute
Sep (Double -> DPoint
DVal Double
4)
defaultAttributeValue Shape{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Shape -> Attribute
Shape Shape
Ellipse
defaultAttributeValue ShowBoxes{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
ShowBoxes Int
0
defaultAttributeValue Sides{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Int -> Attribute
Sides Int
4
defaultAttributeValue Skew{}               = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Skew Double
0.0
defaultAttributeValue Smoothing{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ SmoothType -> Attribute
Smoothing SmoothType
NoSmooth
defaultAttributeValue SortV{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Word16 -> Attribute
SortV Word16
0
defaultAttributeValue StyleSheet{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
StyleSheet AttributeName
""
defaultAttributeValue TailURL{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
TailURL AttributeName
""
defaultAttributeValue TailClip{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Bool -> Attribute
TailClip Bool
True
defaultAttributeValue TailLabel{}          = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
TailLabel (AttributeName -> Label
StrLabel AttributeName
"")
defaultAttributeValue TailPort{}           = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ PortPos -> Attribute
TailPort (CompassPoint -> PortPos
CompassPoint CompassPoint
CenterPoint)
defaultAttributeValue TailTarget{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
TailTarget AttributeName
""
defaultAttributeValue TailTooltip{}        = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
TailTooltip AttributeName
""
defaultAttributeValue Target{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
Target AttributeName
""
defaultAttributeValue Tooltip{}            = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ AttributeName -> Attribute
Tooltip AttributeName
""
defaultAttributeValue VoroMargin{}         = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
VoroMargin Double
0.05
defaultAttributeValue Weight{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Number -> Attribute
Weight (Int -> Number
Int Int
1)
defaultAttributeValue Width{}              = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Double -> Attribute
Width Double
0.75
defaultAttributeValue XLabel{}             = Attribute -> Maybe Attribute
forall a. a -> Maybe a
Just (Attribute -> Maybe Attribute) -> Attribute -> Maybe Attribute
forall a b. (a -> b) -> a -> b
$ Label -> Attribute
XLabel (AttributeName -> Label
StrLabel AttributeName
"")
defaultAttributeValue Attribute
_                    = Maybe Attribute
forall a. Maybe a
Nothing

-- | Determine if the provided 'Text' value is a valid name for an 'UnknownAttribute'.
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" -- Defined upstream, just not used here.
               ])
            Set AttributeName -> Set AttributeName -> Set AttributeName
forall a. Ord a => Set a -> Set a -> Set a
`S.union`
            Set AttributeName
keywords
{- Delete to here -}

-- | Remove attributes that we don't want to consider:
--
--   * Those that are defaults
--   * colorscheme (as the colors embed it anyway)
rmUnwantedAttributes :: Attributes -> Attributes
rmUnwantedAttributes :: [Attribute] -> [Attribute]
rmUnwantedAttributes = (Attribute -> Bool) -> [Attribute] -> [Attribute]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Attribute -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((Attribute -> Bool) -> Bool) -> [Attribute -> Bool] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
`any` [Attribute -> Bool]
tests) (((Attribute -> Bool) -> Bool) -> Bool)
-> (Attribute -> (Attribute -> Bool) -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Attribute -> Bool) -> Attribute -> Bool)
-> Attribute -> (Attribute -> Bool) -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Attribute -> Bool) -> Attribute -> Bool
forall a b. (a -> b) -> a -> b
($))
  where
    tests :: [Attribute -> Bool]
tests = [Attribute -> Bool
isDefault, Attribute -> Bool
isColorScheme]

    isDefault :: Attribute -> Bool
isDefault Attribute
a = Bool -> (Attribute -> Bool) -> Maybe Attribute -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Attribute
aAttribute -> Attribute -> Bool
forall a. Eq a => a -> a -> Bool
==) (Maybe Attribute -> Bool) -> Maybe Attribute -> Bool
forall a b. (a -> b) -> a -> b
$ Attribute -> Maybe Attribute
defaultAttributeValue Attribute
a

    isColorScheme :: Attribute -> Bool
isColorScheme ColorScheme{} = Bool
True
    isColorScheme Attribute
_             = Bool
False

-- -----------------------------------------------------------------------------
-- These parsing combinators are defined here for customisation purposes.

parseField       :: (ParseDot a) => (a -> Attribute) -> String
                    -> [(String, Parse Attribute)]
parseField :: forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField a -> Attribute
c String
fld = [(String
fld, String -> (a -> Attribute) -> Parse Attribute
forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
liftEqParse String
fld a -> Attribute
c)]

parseFields   :: (ParseDot a) => (a -> Attribute) -> [String]
                 -> [(String, Parse Attribute)]
parseFields :: forall a.
ParseDot a =>
(a -> Attribute) -> [String] -> [(String, Parse Attribute)]
parseFields a -> Attribute
c = (String -> [(String, Parse Attribute)])
-> [String] -> [(String, Parse Attribute)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((a -> Attribute) -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> String -> [(String, Parse Attribute)]
parseField a -> Attribute
c)

parseFieldBool :: (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool :: (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool = ((Bool -> Attribute)
-> Bool -> String -> [(String, Parse Attribute)]
forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
`parseFieldDef` Bool
True)

-- | For 'Bool'-like data structures where the presence of the field
--   name without a value implies a default value.
parseFieldDef         :: (ParseDot a) => (a -> Attribute) -> a -> String
                         -> [(String, Parse Attribute)]
parseFieldDef :: forall a.
ParseDot a =>
(a -> Attribute) -> a -> String -> [(String, Parse Attribute)]
parseFieldDef a -> Attribute
c a
d String
fld = [(String
fld, Parse Attribute
p)]
  where
    p :: Parse Attribute
p = String -> (a -> Attribute) -> Parse Attribute
forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
liftEqParse String
fld a -> Attribute
c
        Parse Attribute -> Parse Attribute -> Parse Attribute
forall s a. Parser s a -> Parser s a -> Parser s a
`onFail`
        do Maybe Char
nxt <- Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser GraphvizState Char -> Parser GraphvizState (Maybe Char))
-> Parser GraphvizState Char -> Parser GraphvizState (Maybe Char)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Parser GraphvizState Char
forall s. (Char -> Bool) -> Parser s Char
satisfy Char -> Bool
restIDString
           Parse Attribute -> Parse Attribute -> Bool -> Parse Attribute
forall a. a -> a -> Bool -> a
bool (String -> Parse Attribute
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Not actually the field you were after")
                (Attribute -> Parse Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return (Attribute -> Parse Attribute) -> Attribute -> Parse Attribute
forall a b. (a -> b) -> a -> b
$ a -> Attribute
c a
d)
                (Maybe Char -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Char
nxt)

-- | Attempt to parse the @\"=value\"@ part of a @key=value@ pair.  If
--   there is an equal sign but the @value@ part doesn't parse, throw
--   an un-recoverable error.
liftEqParse :: (ParseDot a) => String -> (a -> Attribute) -> Parse Attribute
liftEqParse :: forall a.
ParseDot a =>
String -> (a -> Attribute) -> Parse Attribute
liftEqParse String
k a -> Attribute
c = do Bool
pStrict <- (GraphvizState -> Bool) -> Parser GraphvizState Bool
forall (m :: * -> *) a.
GraphvizStateM m =>
(GraphvizState -> a) -> m a
getsGS GraphvizState -> Bool
parseStrictly
                     let adjErr :: Parser GraphvizState a -> ShowS -> Parser GraphvizState a
adjErr = (Parser GraphvizState a -> ShowS -> Parser GraphvizState a)
-> (Parser GraphvizState a -> ShowS -> Parser GraphvizState a)
-> Bool
-> Parser GraphvizState a
-> ShowS
-> Parser GraphvizState a
forall a. a -> a -> Bool -> a
bool Parser GraphvizState a -> ShowS -> Parser GraphvizState a
forall (p :: * -> *) a. Commitment p => p a -> ShowS -> p a
adjustErr Parser GraphvizState a -> ShowS -> Parser GraphvizState a
forall (p :: * -> *) a. PolyParse p => p a -> ShowS -> p a
adjustErrBad Bool
pStrict
                     Parse ()
parseEq
                       Parse () -> Parse Attribute -> Parse Attribute
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ( Parse Attribute -> Parse Attribute
hasDef ((a -> Attribute) -> Parser GraphvizState a -> Parse Attribute
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Attribute
c Parser GraphvizState a
forall a. ParseDot a => Parse a
parse)
                            Parse Attribute -> ShowS -> Parse Attribute
forall {a}.
Parser GraphvizState a -> ShowS -> Parser GraphvizState a
`adjErr`
                            ((String
"Unable to parse key=value with key of " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
k
                              String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n\t") String -> ShowS
forall a. [a] -> [a] -> [a]
++)
                          )
  where
    hasDef :: Parse Attribute -> Parse Attribute
hasDef Parse Attribute
p = Parse Attribute
-> (Attribute -> Parse Attribute)
-> Maybe Attribute
-> Parse Attribute
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Parse Attribute
p (Parse Attribute -> Parse Attribute -> Parse Attribute
forall s a. Parser s a -> Parser s a -> Parser s a
onFail Parse Attribute
p (Parse Attribute -> Parse Attribute)
-> (Attribute -> Parse Attribute) -> Attribute -> Parse Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Attribute -> String -> Parse Attribute
forall a. a -> String -> Parse a
`stringRep` String
"\"\""))
               (Maybe Attribute -> Parse Attribute)
-> (Attribute -> Maybe Attribute) -> Attribute -> Parse Attribute
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attribute -> Maybe Attribute
defaultAttributeValue (Attribute -> Parse Attribute) -> Attribute -> Parse Attribute
forall a b. (a -> b) -> a -> b
$ a -> Attribute
c a
forall a. HasCallStack => a
undefined

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

{- | If performing any custom pre-/post-processing on Dot code, you
     may wish to utilise some custom 'Attributes'.  These are wrappers
     around the 'UnknownAttribute' constructor (and thus 'CustomAttribute'
     is just an alias for 'Attribute').

     You should ensure that 'validUnknown' is 'True' for any potential
     custom attribute name.

-}
type CustomAttribute = Attribute

-- | Create a custom attribute.
customAttribute :: AttributeName -> Text -> CustomAttribute
customAttribute :: AttributeName -> AttributeName -> Attribute
customAttribute = AttributeName -> AttributeName -> Attribute
UnknownAttribute

-- | Determines whether or not this is a custom attribute.
isCustom                    :: Attribute -> Bool
isCustom :: Attribute -> Bool
isCustom UnknownAttribute{} = Bool
True
isCustom Attribute
_                  = Bool
False

isSpecifiedCustom :: AttributeName -> Attribute -> Bool
isSpecifiedCustom :: AttributeName -> Attribute -> Bool
isSpecifiedCustom AttributeName
nm (UnknownAttribute AttributeName
nm' AttributeName
_) = AttributeName
nm AttributeName -> AttributeName -> Bool
forall a. Eq a => a -> a -> Bool
== AttributeName
nm'
isSpecifiedCustom AttributeName
_  Attribute
_                        = Bool
False

-- | The value of a custom attribute.  Will throw a
--   'GraphvizException' if the provided 'Attribute' isn't a custom
--   one.
customValue :: CustomAttribute -> Text
customValue :: Attribute -> AttributeName
customValue (UnknownAttribute AttributeName
_ AttributeName
v) = AttributeName
v
customValue Attribute
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
$ Attribute -> AttributeName
forall a. PrintDot a => a -> AttributeName
printIt Attribute
attr

-- | The name of a custom attribute.  Will throw a
--   'GraphvizException' if the provided 'Attribute' isn't a custom
--   one.
customName :: CustomAttribute -> AttributeName
customName :: Attribute -> AttributeName
customName (UnknownAttribute AttributeName
nm AttributeName
_) = AttributeName
nm
customName Attribute
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
$ Attribute -> AttributeName
forall a. PrintDot a => a -> AttributeName
printIt Attribute
attr

-- | Returns all custom attributes and the list of non-custom Attributes.
findCustoms :: Attributes -> ([CustomAttribute], Attributes)
findCustoms :: [Attribute] -> ([Attribute], [Attribute])
findCustoms = (Attribute -> Bool) -> [Attribute] -> ([Attribute], [Attribute])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Attribute -> Bool
isCustom

-- | Find the (first instance of the) specified custom attribute and
--   returns it along with all other Attributes.
findSpecifiedCustom :: AttributeName -> Attributes
                       -> Maybe (CustomAttribute, Attributes)
findSpecifiedCustom :: AttributeName -> [Attribute] -> Maybe (Attribute, [Attribute])
findSpecifiedCustom AttributeName
nm [Attribute]
attrs
  = case (Attribute -> Bool) -> [Attribute] -> ([Attribute], [Attribute])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (AttributeName -> Attribute -> Bool
isSpecifiedCustom AttributeName
nm) [Attribute]
attrs of
      ([Attribute]
bf,Attribute
cust:[Attribute]
aft) -> (Attribute, [Attribute]) -> Maybe (Attribute, [Attribute])
forall a. a -> Maybe a
Just (Attribute
cust, [Attribute]
bf [Attribute] -> [Attribute] -> [Attribute]
forall a. [a] -> [a] -> [a]
++ [Attribute]
aft)
      ([Attribute], [Attribute])
_             -> Maybe (Attribute, [Attribute])
forall a. Maybe a
Nothing

-- | Delete all custom attributes (actually, this will delete all
--   'UnknownAttribute' values; as such it can also be used to remove
--   legacy attributes).
deleteCustomAttributes :: Attributes -> Attributes
deleteCustomAttributes :: [Attribute] -> [Attribute]
deleteCustomAttributes = (Attribute -> Bool) -> [Attribute] -> [Attribute]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Attribute -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attribute -> Bool
isCustom)

-- | Removes all instances of the specified custom attribute.
deleteSpecifiedCustom :: AttributeName -> Attributes -> Attributes
deleteSpecifiedCustom :: AttributeName -> [Attribute] -> [Attribute]
deleteSpecifiedCustom AttributeName
nm = (Attribute -> Bool) -> [Attribute] -> [Attribute]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Attribute -> Bool) -> Attribute -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AttributeName -> Attribute -> Bool
isSpecifiedCustom AttributeName
nm)