module Data.GraphViz.Attributes.Complete
(
Attribute(..)
, Attributes
, sameAttribute
, defaultAttributeValue
, rmUnwantedAttributes
, usedByGraphs
, usedBySubGraphs
, usedByClusters
, usedByNodes
, usedByEdges
, validUnknown
, AttributeName
, CustomAttribute
, customAttribute
, isCustom
, isSpecifiedCustom
, customValue
, customName
, findCustoms
, findSpecifiedCustom
, deleteCustomAttributes
, deleteSpecifiedCustom
, module Data.GraphViz.Attributes.Colors
, EscString
, Label(..)
, VerticalPlacement(..)
, LabelScheme(..)
, SVGFontNames(..)
, RecordFields
, RecordField(..)
, Rect(..)
, Justification(..)
, Shape(..)
, Paths(..)
, ScaleType(..)
, DirType(..)
, EdgeType(..)
, PortName(..)
, PortPos(..)
, CompassPoint(..)
, ArrowType(..)
, ArrowShape(..)
, ArrowModifier(..)
, ArrowFill(..)
, ArrowSide(..)
, noMods
, openMod
, Point(..)
, createPoint
, Pos(..)
, Spline(..)
, DPoint(..)
, GraphvizCommand(..)
, GraphSize(..)
, AspectType(..)
, ClusterMode(..)
, Model(..)
, Overlap(..)
, Root(..)
, Order(..)
, OutputMode(..)
, Pack(..)
, PackMode(..)
, PageDir(..)
, QuadType(..)
, RankType(..)
, RankDir(..)
, StartType(..)
, ViewPort(..)
, FocusType(..)
, Ratios(..)
, ModeType(..)
, DEConstraints(..)
, LayerSep(..)
, LayerListSep(..)
, LayerRange
, LayerRangeElem(..)
, LayerID(..)
, LayerList(..)
, SmoothType(..)
, STStyle(..)
, StyleItem(..)
, StyleName(..)
) where
import Data.GraphViz.Attributes.Colors
import Data.GraphViz.Attributes.Colors.X11(X11Color(Black))
import qualified Data.GraphViz.Attributes.HTML as Html
import Data.GraphViz.Attributes.Internal
import Data.GraphViz.Util
import Data.GraphViz.Parsing
import Data.GraphViz.Printing
import Data.GraphViz.State(getLayerSep, setLayerSep, getLayerListSep, setLayerListSep)
import Data.GraphViz.Exception(GraphvizException(NotCustomAttr), throw)
import Data.List(partition, intercalate)
import Data.Maybe(isJust, isNothing)
import Data.Word(Word16)
import qualified Data.Set as S
import qualified Data.Text.Lazy as T
import Data.Text.Lazy(Text)
import System.FilePath(searchPathSeparator, splitSearchPath)
data Attribute
= Damping Double
| K Double
| URL EscString
| Area Double
| ArrowHead ArrowType
| ArrowSize Double
| ArrowTail ArrowType
| Aspect AspectType
| BoundingBox Rect
| BgColor ColorList
| Center Bool
| ClusterRank ClusterMode
| Color ColorList
| ColorScheme ColorScheme
| Comment Text
| Compound Bool
| Concentrate Bool
| Constraint Bool
| Decorate Bool
| DefaultDist Double
| Dim Int
| Dimen Int
| Dir DirType
| DirEdgeConstraints DEConstraints
| Distortion Double
| DPI Double
| EdgeURL EscString
| EdgeTarget EscString
| EdgeTooltip EscString
| Epsilon Double
| ESep DPoint
| FillColor ColorList
| FixedSize Bool
| FontColor Color
| FontName Text
| FontNames SVGFontNames
| FontPath Paths
| FontSize Double
| ForceLabels Bool
| GradientAngle Int
| Group Text
| HeadURL EscString
| Head_LP Point
| HeadClip Bool
| HeadLabel Label
| HeadPort PortPos
| HeadTarget EscString
| HeadTooltip EscString
| Height Double
| ID EscString
| Image Text
| ImagePath Paths
| ImageScale ScaleType
| Label Label
| LabelURL EscString
| LabelScheme LabelScheme
| LabelAngle Double
| LabelDistance Double
| LabelFloat Bool
| LabelFontColor Color
| LabelFontName Text
| LabelFontSize Double
| LabelJust Justification
| LabelLoc VerticalPlacement
| LabelTarget EscString
| LabelTooltip EscString
| Landscape Bool
| Layer LayerRange
| LayerListSep LayerListSep
| Layers LayerList
| LayerSelect LayerRange
| LayerSep LayerSep
| Layout GraphvizCommand
| Len Double
| Levels Int
| LevelsGap Double
| LHead Text
| LHeight Double
| LPos Point
| LTail Text
| LWidth Double
| Margin DPoint
| MaxIter Int
| MCLimit Double
| MinDist Double
| MinLen Int
| Mode ModeType
| Model Model
| Mosek Bool
| NodeSep Double
| NoJustify Bool
| Normalize Bool
| Nslimit Double
| Nslimit1 Double
| Ordering Order
| Orientation Double
| OutputOrder OutputMode
| Overlap Overlap
| OverlapScaling Double
| Pack Pack
| PackMode PackMode
| Pad DPoint
| Page Point
| PageDir PageDir
| PenColor Color
| PenWidth Double
| Peripheries Int
| Pin Bool
| Pos Pos
| QuadTree QuadType
| Quantum Double
| Rank RankType
| RankDir RankDir
| RankSep [Double]
| Ratio Ratios
| Rects [Rect]
| Regular Bool
| ReMinCross Bool
| RepulsiveForce Double
| Root Root
| Rotate Int
| Rotation Double
| SameHead Text
| SameTail Text
| SamplePoints Int
| Scale DPoint
| SearchSize Int
| Sep DPoint
| Shape Shape
| ShowBoxes Int
| Sides Int
| Size GraphSize
| Skew Double
| Smoothing SmoothType
| SortV Word16
| Splines EdgeType
| Start StartType
| Style [StyleItem]
| StyleSheet Text
| TailURL EscString
| Tail_LP Point
| TailClip Bool
| TailLabel Label
| TailPort PortPos
| TailTarget EscString
| TailTooltip EscString
| Target EscString
| Tooltip EscString
| TrueColor Bool
| Vertices [Point]
| ViewPort ViewPort
| VoroMargin Double
| Weight Double
| Width Double
| XLabel Label
| XLP Point
| UnknownAttribute AttributeName Text
deriving (Eq, Ord, Show, Read)
type Attributes = [Attribute]
type AttributeName = Text
instance PrintDot Attribute where
unqtDot (Damping v) = printField "Damping" v
unqtDot (K v) = printField "K" v
unqtDot (URL v) = printField "URL" v
unqtDot (Area v) = printField "area" v
unqtDot (ArrowHead v) = printField "arrowhead" v
unqtDot (ArrowSize v) = printField "arrowsize" v
unqtDot (ArrowTail v) = printField "arrowtail" v
unqtDot (Aspect v) = printField "aspect" v
unqtDot (BoundingBox v) = printField "bb" v
unqtDot (BgColor v) = printField "bgcolor" v
unqtDot (Center v) = printField "center" v
unqtDot (ClusterRank v) = printField "clusterrank" v
unqtDot (Color v) = printField "color" v
unqtDot (ColorScheme v) = printField "colorscheme" v
unqtDot (Comment v) = printField "comment" v
unqtDot (Compound v) = printField "compound" v
unqtDot (Concentrate v) = printField "concentrate" v
unqtDot (Constraint v) = printField "constraint" v
unqtDot (Decorate v) = printField "decorate" v
unqtDot (DefaultDist v) = printField "defaultdist" v
unqtDot (Dim v) = printField "dim" v
unqtDot (Dimen v) = printField "dimen" v
unqtDot (Dir v) = printField "dir" v
unqtDot (DirEdgeConstraints v) = printField "diredgeconstraints" v
unqtDot (Distortion v) = printField "distortion" v
unqtDot (DPI v) = printField "dpi" v
unqtDot (EdgeURL v) = printField "edgeURL" v
unqtDot (EdgeTarget v) = printField "edgetarget" v
unqtDot (EdgeTooltip v) = printField "edgetooltip" v
unqtDot (Epsilon v) = printField "epsilon" v
unqtDot (ESep v) = printField "esep" v
unqtDot (FillColor v) = printField "fillcolor" v
unqtDot (FixedSize v) = printField "fixedsize" v
unqtDot (FontColor v) = printField "fontcolor" v
unqtDot (FontName v) = printField "fontname" v
unqtDot (FontNames v) = printField "fontnames" v
unqtDot (FontPath v) = printField "fontpath" v
unqtDot (FontSize v) = printField "fontsize" v
unqtDot (ForceLabels v) = printField "forcelabels" v
unqtDot (GradientAngle v) = printField "gradientangle" v
unqtDot (Group v) = printField "group" v
unqtDot (HeadURL v) = printField "headURL" v
unqtDot (Head_LP v) = printField "head_lp" v
unqtDot (HeadClip v) = printField "headclip" v
unqtDot (HeadLabel v) = printField "headlabel" v
unqtDot (HeadPort v) = printField "headport" v
unqtDot (HeadTarget v) = printField "headtarget" v
unqtDot (HeadTooltip v) = printField "headtooltip" v
unqtDot (Height v) = printField "height" v
unqtDot (ID v) = printField "id" v
unqtDot (Image v) = printField "image" v
unqtDot (ImagePath v) = printField "imagepath" v
unqtDot (ImageScale v) = printField "imagescale" v
unqtDot (Label v) = printField "label" v
unqtDot (LabelURL v) = printField "labelURL" v
unqtDot (LabelScheme v) = printField "label_scheme" v
unqtDot (LabelAngle v) = printField "labelangle" v
unqtDot (LabelDistance v) = printField "labeldistance" v
unqtDot (LabelFloat v) = printField "labelfloat" v
unqtDot (LabelFontColor v) = printField "labelfontcolor" v
unqtDot (LabelFontName v) = printField "labelfontname" v
unqtDot (LabelFontSize v) = printField "labelfontsize" v
unqtDot (LabelJust v) = printField "labeljust" v
unqtDot (LabelLoc v) = printField "labelloc" v
unqtDot (LabelTarget v) = printField "labeltarget" v
unqtDot (LabelTooltip v) = printField "labeltooltip" v
unqtDot (Landscape v) = printField "landscape" v
unqtDot (Layer v) = printField "layer" v
unqtDot (LayerListSep v) = printField "layerlistsep" v
unqtDot (Layers v) = printField "layers" v
unqtDot (LayerSelect v) = printField "layerselect" v
unqtDot (LayerSep v) = printField "layersep" v
unqtDot (Layout v) = printField "layout" v
unqtDot (Len v) = printField "len" v
unqtDot (Levels v) = printField "levels" v
unqtDot (LevelsGap v) = printField "levelsgap" v
unqtDot (LHead v) = printField "lhead" v
unqtDot (LHeight v) = printField "LHeight" v
unqtDot (LPos v) = printField "lp" v
unqtDot (LTail v) = printField "ltail" v
unqtDot (LWidth v) = printField "lwidth" v
unqtDot (Margin v) = printField "margin" v
unqtDot (MaxIter v) = printField "maxiter" v
unqtDot (MCLimit v) = printField "mclimit" v
unqtDot (MinDist v) = printField "mindist" v
unqtDot (MinLen v) = printField "minlen" v
unqtDot (Mode v) = printField "mode" v
unqtDot (Model v) = printField "model" v
unqtDot (Mosek v) = printField "mosek" v
unqtDot (NodeSep v) = printField "nodesep" v
unqtDot (NoJustify v) = printField "nojustify" v
unqtDot (Normalize v) = printField "normalize" v
unqtDot (Nslimit v) = printField "nslimit" v
unqtDot (Nslimit1 v) = printField "nslimit1" v
unqtDot (Ordering v) = printField "ordering" v
unqtDot (Orientation v) = printField "orientation" v
unqtDot (OutputOrder v) = printField "outputorder" v
unqtDot (Overlap v) = printField "overlap" v
unqtDot (OverlapScaling v) = printField "overlap_scaling" v
unqtDot (Pack v) = printField "pack" v
unqtDot (PackMode v) = printField "packmode" v
unqtDot (Pad v) = printField "pad" v
unqtDot (Page v) = printField "page" v
unqtDot (PageDir v) = printField "pagedir" v
unqtDot (PenColor v) = printField "pencolor" v
unqtDot (PenWidth v) = printField "penwidth" v
unqtDot (Peripheries v) = printField "peripheries" v
unqtDot (Pin v) = printField "pin" v
unqtDot (Pos v) = printField "pos" v
unqtDot (QuadTree v) = printField "quadtree" v
unqtDot (Quantum v) = printField "quantum" v
unqtDot (Rank v) = printField "rank" v
unqtDot (RankDir v) = printField "rankdir" v
unqtDot (RankSep v) = printField "ranksep" v
unqtDot (Ratio v) = printField "ratio" v
unqtDot (Rects v) = printField "rects" v
unqtDot (Regular v) = printField "regular" v
unqtDot (ReMinCross v) = printField "remincross" v
unqtDot (RepulsiveForce v) = printField "repulsiveforce" v
unqtDot (Root v) = printField "root" v
unqtDot (Rotate v) = printField "rotate" v
unqtDot (Rotation v) = printField "rotation" v
unqtDot (SameHead v) = printField "samehead" v
unqtDot (SameTail v) = printField "sametail" v
unqtDot (SamplePoints v) = printField "samplepoints" v
unqtDot (Scale v) = printField "scale" v
unqtDot (SearchSize v) = printField "searchsize" v
unqtDot (Sep v) = printField "sep" v
unqtDot (Shape v) = printField "shape" v
unqtDot (ShowBoxes v) = printField "showboxes" v
unqtDot (Sides v) = printField "sides" v
unqtDot (Size v) = printField "size" v
unqtDot (Skew v) = printField "skew" v
unqtDot (Smoothing v) = printField "smoothing" v
unqtDot (SortV v) = printField "sortv" v
unqtDot (Splines v) = printField "splines" v
unqtDot (Start v) = printField "start" v
unqtDot (Style v) = printField "style" v
unqtDot (StyleSheet v) = printField "stylesheet" v
unqtDot (TailURL v) = printField "tailURL" v
unqtDot (Tail_LP v) = printField "tail_lp" v
unqtDot (TailClip v) = printField "tailclip" v
unqtDot (TailLabel v) = printField "taillabel" v
unqtDot (TailPort v) = printField "tailport" v
unqtDot (TailTarget v) = printField "tailtarget" v
unqtDot (TailTooltip v) = printField "tailtooltip" v
unqtDot (Target v) = printField "target" v
unqtDot (Tooltip v) = printField "tooltip" v
unqtDot (TrueColor v) = printField "truecolor" v
unqtDot (Vertices v) = printField "vertices" v
unqtDot (ViewPort v) = printField "viewport" v
unqtDot (VoroMargin v) = printField "voro_margin" v
unqtDot (Weight v) = printField "weight" v
unqtDot (Width v) = printField "width" v
unqtDot (XLabel v) = printField "xlabel" v
unqtDot (XLP v) = printField "xlp" v
unqtDot (UnknownAttribute a v) = toDot a <> equals <> toDot v
listToDot = unqtListToDot
instance ParseDot Attribute where
parseUnqt = stringParse (concat [ parseField Damping "Damping"
, parseField K "K"
, parseFields URL ["URL", "href"]
, parseField Area "area"
, parseField ArrowHead "arrowhead"
, parseField ArrowSize "arrowsize"
, parseField ArrowTail "arrowtail"
, parseField Aspect "aspect"
, parseField BoundingBox "bb"
, parseField BgColor "bgcolor"
, parseFieldBool Center "center"
, parseField ClusterRank "clusterrank"
, parseField Color "color"
, parseField ColorScheme "colorscheme"
, parseField Comment "comment"
, parseFieldBool Compound "compound"
, parseFieldBool Concentrate "concentrate"
, parseFieldBool Constraint "constraint"
, parseFieldBool Decorate "decorate"
, parseField DefaultDist "defaultdist"
, parseField Dim "dim"
, parseField Dimen "dimen"
, parseField Dir "dir"
, parseFieldDef DirEdgeConstraints EdgeConstraints "diredgeconstraints"
, parseField Distortion "distortion"
, parseFields DPI ["dpi", "resolution"]
, parseFields EdgeURL ["edgeURL", "edgehref"]
, parseField EdgeTarget "edgetarget"
, parseField EdgeTooltip "edgetooltip"
, parseField Epsilon "epsilon"
, parseField ESep "esep"
, parseField FillColor "fillcolor"
, parseFieldBool FixedSize "fixedsize"
, parseField FontColor "fontcolor"
, parseField FontName "fontname"
, parseField FontNames "fontnames"
, parseField FontPath "fontpath"
, parseField FontSize "fontsize"
, parseFieldBool ForceLabels "forcelabels"
, parseField GradientAngle "gradientangle"
, parseField Group "group"
, parseFields HeadURL ["headURL", "headhref"]
, parseField Head_LP "head_lp"
, parseFieldBool HeadClip "headclip"
, parseField HeadLabel "headlabel"
, parseField HeadPort "headport"
, parseField HeadTarget "headtarget"
, parseField HeadTooltip "headtooltip"
, parseField Height "height"
, parseField ID "id"
, parseField Image "image"
, parseField ImagePath "imagepath"
, parseFieldDef ImageScale UniformScale "imagescale"
, parseField Label "label"
, parseFields LabelURL ["labelURL", "labelhref"]
, parseField LabelScheme "label_scheme"
, parseField LabelAngle "labelangle"
, parseField LabelDistance "labeldistance"
, parseFieldBool LabelFloat "labelfloat"
, parseField LabelFontColor "labelfontcolor"
, parseField LabelFontName "labelfontname"
, parseField LabelFontSize "labelfontsize"
, parseField LabelJust "labeljust"
, parseField LabelLoc "labelloc"
, parseField LabelTarget "labeltarget"
, parseField LabelTooltip "labeltooltip"
, parseFieldBool Landscape "landscape"
, parseField Layer "layer"
, parseField LayerListSep "layerlistsep"
, parseField Layers "layers"
, parseField LayerSelect "layerselect"
, parseField LayerSep "layersep"
, parseField Layout "layout"
, parseField Len "len"
, parseField Levels "levels"
, parseField LevelsGap "levelsgap"
, parseField LHead "lhead"
, parseField LHeight "LHeight"
, parseField LPos "lp"
, parseField LTail "ltail"
, parseField LWidth "lwidth"
, parseField Margin "margin"
, parseField MaxIter "maxiter"
, parseField MCLimit "mclimit"
, parseField MinDist "mindist"
, parseField MinLen "minlen"
, parseField Mode "mode"
, parseField Model "model"
, parseFieldBool Mosek "mosek"
, parseField NodeSep "nodesep"
, parseFieldBool NoJustify "nojustify"
, parseFieldBool Normalize "normalize"
, parseField Nslimit "nslimit"
, parseField Nslimit1 "nslimit1"
, parseField Ordering "ordering"
, parseField Orientation "orientation"
, parseField OutputOrder "outputorder"
, parseFieldDef Overlap KeepOverlaps "overlap"
, parseField OverlapScaling "overlap_scaling"
, parseFieldDef Pack DoPack "pack"
, parseField PackMode "packmode"
, parseField Pad "pad"
, parseField Page "page"
, parseField PageDir "pagedir"
, parseField PenColor "pencolor"
, parseField PenWidth "penwidth"
, parseField Peripheries "peripheries"
, parseFieldBool Pin "pin"
, parseField Pos "pos"
, parseFieldDef QuadTree NormalQT "quadtree"
, parseField Quantum "quantum"
, parseField Rank "rank"
, parseField RankDir "rankdir"
, parseField RankSep "ranksep"
, parseField Ratio "ratio"
, parseField Rects "rects"
, parseFieldBool Regular "regular"
, parseFieldBool ReMinCross "remincross"
, parseField RepulsiveForce "repulsiveforce"
, parseFieldDef Root IsCentral "root"
, parseField Rotate "rotate"
, parseField Rotation "rotation"
, parseField SameHead "samehead"
, parseField SameTail "sametail"
, parseField SamplePoints "samplepoints"
, parseField Scale "scale"
, parseField SearchSize "searchsize"
, parseField Sep "sep"
, parseField Shape "shape"
, parseField ShowBoxes "showboxes"
, parseField Sides "sides"
, parseField Size "size"
, parseField Skew "skew"
, parseField Smoothing "smoothing"
, parseField SortV "sortv"
, parseFieldDef Splines SplineEdges "splines"
, parseField Start "start"
, parseField Style "style"
, parseField StyleSheet "stylesheet"
, parseFields TailURL ["tailURL", "tailhref"]
, parseField Tail_LP "tail_lp"
, parseFieldBool TailClip "tailclip"
, parseField TailLabel "taillabel"
, parseField TailPort "tailport"
, parseField TailTarget "tailtarget"
, parseField TailTooltip "tailtooltip"
, parseField Target "target"
, parseField Tooltip "tooltip"
, parseFieldBool TrueColor "truecolor"
, parseField Vertices "vertices"
, parseField ViewPort "viewport"
, parseField VoroMargin "voro_margin"
, parseField Weight "weight"
, parseField Width "width"
, parseField XLabel "xlabel"
, parseField XLP "xlp"
])
`onFail`
do attrName <- stringBlock
liftEqParse ("UnknownAttribute (" ++ T.unpack attrName ++ ")")
(UnknownAttribute attrName)
parse = parseUnqt
parseList = parseUnqtList
usedByGraphs :: Attribute -> Bool
usedByGraphs Damping{} = True
usedByGraphs K{} = True
usedByGraphs URL{} = True
usedByGraphs Aspect{} = True
usedByGraphs BoundingBox{} = True
usedByGraphs BgColor{} = True
usedByGraphs Center{} = True
usedByGraphs ClusterRank{} = True
usedByGraphs ColorScheme{} = True
usedByGraphs Comment{} = True
usedByGraphs Compound{} = True
usedByGraphs Concentrate{} = True
usedByGraphs DefaultDist{} = True
usedByGraphs Dim{} = True
usedByGraphs Dimen{} = True
usedByGraphs DirEdgeConstraints{} = True
usedByGraphs DPI{} = True
usedByGraphs Epsilon{} = True
usedByGraphs ESep{} = True
usedByGraphs FontColor{} = True
usedByGraphs FontName{} = True
usedByGraphs FontNames{} = True
usedByGraphs FontPath{} = True
usedByGraphs FontSize{} = True
usedByGraphs ForceLabels{} = True
usedByGraphs GradientAngle{} = True
usedByGraphs ID{} = True
usedByGraphs ImagePath{} = True
usedByGraphs Label{} = True
usedByGraphs LabelScheme{} = True
usedByGraphs LabelJust{} = True
usedByGraphs LabelLoc{} = True
usedByGraphs Landscape{} = True
usedByGraphs LayerListSep{} = True
usedByGraphs Layers{} = True
usedByGraphs LayerSelect{} = True
usedByGraphs LayerSep{} = True
usedByGraphs Layout{} = True
usedByGraphs Levels{} = True
usedByGraphs LevelsGap{} = True
usedByGraphs LHeight{} = True
usedByGraphs LPos{} = True
usedByGraphs LWidth{} = True
usedByGraphs Margin{} = True
usedByGraphs MaxIter{} = True
usedByGraphs MCLimit{} = True
usedByGraphs MinDist{} = True
usedByGraphs Mode{} = True
usedByGraphs Model{} = True
usedByGraphs Mosek{} = True
usedByGraphs NodeSep{} = True
usedByGraphs NoJustify{} = True
usedByGraphs Normalize{} = True
usedByGraphs Nslimit{} = True
usedByGraphs Nslimit1{} = True
usedByGraphs Ordering{} = True
usedByGraphs OutputOrder{} = True
usedByGraphs Overlap{} = True
usedByGraphs OverlapScaling{} = True
usedByGraphs Pack{} = True
usedByGraphs PackMode{} = True
usedByGraphs Pad{} = True
usedByGraphs Page{} = True
usedByGraphs PageDir{} = True
usedByGraphs QuadTree{} = True
usedByGraphs Quantum{} = True
usedByGraphs RankDir{} = True
usedByGraphs RankSep{} = True
usedByGraphs Ratio{} = True
usedByGraphs ReMinCross{} = True
usedByGraphs RepulsiveForce{} = True
usedByGraphs Root{} = True
usedByGraphs Rotate{} = True
usedByGraphs Rotation{} = True
usedByGraphs Scale{} = True
usedByGraphs SearchSize{} = True
usedByGraphs Sep{} = True
usedByGraphs ShowBoxes{} = True
usedByGraphs Size{} = True
usedByGraphs Smoothing{} = True
usedByGraphs SortV{} = True
usedByGraphs Splines{} = True
usedByGraphs Start{} = True
usedByGraphs StyleSheet{} = True
usedByGraphs Target{} = True
usedByGraphs TrueColor{} = True
usedByGraphs ViewPort{} = True
usedByGraphs VoroMargin{} = True
usedByGraphs UnknownAttribute{} = True
usedByGraphs _ = False
usedByClusters :: Attribute -> Bool
usedByClusters K{} = True
usedByClusters URL{} = True
usedByClusters Area{} = True
usedByClusters BgColor{} = True
usedByClusters Color{} = True
usedByClusters ColorScheme{} = True
usedByClusters FillColor{} = True
usedByClusters FontColor{} = True
usedByClusters FontName{} = True
usedByClusters FontSize{} = True
usedByClusters GradientAngle{} = True
usedByClusters Label{} = True
usedByClusters LabelJust{} = True
usedByClusters LabelLoc{} = True
usedByClusters LHeight{} = True
usedByClusters LPos{} = True
usedByClusters LWidth{} = True
usedByClusters NoJustify{} = True
usedByClusters PenColor{} = True
usedByClusters PenWidth{} = True
usedByClusters Peripheries{} = True
usedByClusters Rank{} = True
usedByClusters SortV{} = True
usedByClusters Style{} = True
usedByClusters Target{} = True
usedByClusters Tooltip{} = True
usedByClusters UnknownAttribute{} = True
usedByClusters _ = False
usedBySubGraphs :: Attribute -> Bool
usedBySubGraphs Rank{} = True
usedBySubGraphs UnknownAttribute{} = True
usedBySubGraphs _ = False
usedByNodes :: Attribute -> Bool
usedByNodes URL{} = True
usedByNodes Area{} = True
usedByNodes Color{} = True
usedByNodes ColorScheme{} = True
usedByNodes Comment{} = True
usedByNodes Distortion{} = True
usedByNodes FillColor{} = True
usedByNodes FixedSize{} = True
usedByNodes FontColor{} = True
usedByNodes FontName{} = True
usedByNodes FontSize{} = True
usedByNodes GradientAngle{} = True
usedByNodes Group{} = True
usedByNodes Height{} = True
usedByNodes ID{} = True
usedByNodes Image{} = True
usedByNodes ImageScale{} = True
usedByNodes Label{} = True
usedByNodes LabelLoc{} = True
usedByNodes Layer{} = True
usedByNodes Margin{} = True
usedByNodes NoJustify{} = True
usedByNodes Ordering{} = True
usedByNodes Orientation{} = True
usedByNodes PenWidth{} = True
usedByNodes Peripheries{} = True
usedByNodes Pin{} = True
usedByNodes Pos{} = True
usedByNodes Rects{} = True
usedByNodes Regular{} = True
usedByNodes Root{} = True
usedByNodes SamplePoints{} = True
usedByNodes Shape{} = True
usedByNodes ShowBoxes{} = True
usedByNodes Sides{} = True
usedByNodes Skew{} = True
usedByNodes SortV{} = True
usedByNodes Style{} = True
usedByNodes Target{} = True
usedByNodes Tooltip{} = True
usedByNodes Vertices{} = True
usedByNodes Width{} = True
usedByNodes XLabel{} = True
usedByNodes XLP{} = True
usedByNodes UnknownAttribute{} = True
usedByNodes _ = False
usedByEdges :: Attribute -> Bool
usedByEdges URL{} = True
usedByEdges ArrowHead{} = True
usedByEdges ArrowSize{} = True
usedByEdges ArrowTail{} = True
usedByEdges Color{} = True
usedByEdges ColorScheme{} = True
usedByEdges Comment{} = True
usedByEdges Constraint{} = True
usedByEdges Decorate{} = True
usedByEdges Dir{} = True
usedByEdges EdgeURL{} = True
usedByEdges EdgeTarget{} = True
usedByEdges EdgeTooltip{} = True
usedByEdges FillColor{} = True
usedByEdges FontColor{} = True
usedByEdges FontName{} = True
usedByEdges FontSize{} = True
usedByEdges HeadURL{} = True
usedByEdges Head_LP{} = True
usedByEdges HeadClip{} = True
usedByEdges HeadLabel{} = True
usedByEdges HeadPort{} = True
usedByEdges HeadTarget{} = True
usedByEdges HeadTooltip{} = True
usedByEdges ID{} = True
usedByEdges Label{} = True
usedByEdges LabelURL{} = True
usedByEdges LabelAngle{} = True
usedByEdges LabelDistance{} = True
usedByEdges LabelFloat{} = True
usedByEdges LabelFontColor{} = True
usedByEdges LabelFontName{} = True
usedByEdges LabelFontSize{} = True
usedByEdges LabelTarget{} = True
usedByEdges LabelTooltip{} = True
usedByEdges Layer{} = True
usedByEdges Len{} = True
usedByEdges LHead{} = True
usedByEdges LPos{} = True
usedByEdges LTail{} = True
usedByEdges MinLen{} = True
usedByEdges NoJustify{} = True
usedByEdges PenWidth{} = True
usedByEdges Pos{} = True
usedByEdges SameHead{} = True
usedByEdges SameTail{} = True
usedByEdges ShowBoxes{} = True
usedByEdges Style{} = True
usedByEdges TailURL{} = True
usedByEdges Tail_LP{} = True
usedByEdges TailClip{} = True
usedByEdges TailLabel{} = True
usedByEdges TailPort{} = True
usedByEdges TailTarget{} = True
usedByEdges TailTooltip{} = True
usedByEdges Target{} = True
usedByEdges Tooltip{} = True
usedByEdges Weight{} = True
usedByEdges XLabel{} = True
usedByEdges XLP{} = True
usedByEdges UnknownAttribute{} = True
usedByEdges _ = False
sameAttribute :: Attribute -> Attribute -> Bool
sameAttribute Damping{} Damping{} = True
sameAttribute K{} K{} = True
sameAttribute URL{} URL{} = True
sameAttribute Area{} Area{} = True
sameAttribute ArrowHead{} ArrowHead{} = True
sameAttribute ArrowSize{} ArrowSize{} = True
sameAttribute ArrowTail{} ArrowTail{} = True
sameAttribute Aspect{} Aspect{} = True
sameAttribute BoundingBox{} BoundingBox{} = True
sameAttribute BgColor{} BgColor{} = True
sameAttribute Center{} Center{} = True
sameAttribute ClusterRank{} ClusterRank{} = True
sameAttribute Color{} Color{} = True
sameAttribute ColorScheme{} ColorScheme{} = True
sameAttribute Comment{} Comment{} = True
sameAttribute Compound{} Compound{} = True
sameAttribute Concentrate{} Concentrate{} = True
sameAttribute Constraint{} Constraint{} = True
sameAttribute Decorate{} Decorate{} = True
sameAttribute DefaultDist{} DefaultDist{} = True
sameAttribute Dim{} Dim{} = True
sameAttribute Dimen{} Dimen{} = True
sameAttribute Dir{} Dir{} = True
sameAttribute DirEdgeConstraints{} DirEdgeConstraints{} = True
sameAttribute Distortion{} Distortion{} = True
sameAttribute DPI{} DPI{} = True
sameAttribute EdgeURL{} EdgeURL{} = True
sameAttribute EdgeTarget{} EdgeTarget{} = True
sameAttribute EdgeTooltip{} EdgeTooltip{} = True
sameAttribute Epsilon{} Epsilon{} = True
sameAttribute ESep{} ESep{} = True
sameAttribute FillColor{} FillColor{} = True
sameAttribute FixedSize{} FixedSize{} = True
sameAttribute FontColor{} FontColor{} = True
sameAttribute FontName{} FontName{} = True
sameAttribute FontNames{} FontNames{} = True
sameAttribute FontPath{} FontPath{} = True
sameAttribute FontSize{} FontSize{} = True
sameAttribute ForceLabels{} ForceLabels{} = True
sameAttribute GradientAngle{} GradientAngle{} = True
sameAttribute Group{} Group{} = True
sameAttribute HeadURL{} HeadURL{} = True
sameAttribute Head_LP{} Head_LP{} = True
sameAttribute HeadClip{} HeadClip{} = True
sameAttribute HeadLabel{} HeadLabel{} = True
sameAttribute HeadPort{} HeadPort{} = True
sameAttribute HeadTarget{} HeadTarget{} = True
sameAttribute HeadTooltip{} HeadTooltip{} = True
sameAttribute Height{} Height{} = True
sameAttribute ID{} ID{} = True
sameAttribute Image{} Image{} = True
sameAttribute ImagePath{} ImagePath{} = True
sameAttribute ImageScale{} ImageScale{} = True
sameAttribute Label{} Label{} = True
sameAttribute LabelURL{} LabelURL{} = True
sameAttribute LabelScheme{} LabelScheme{} = True
sameAttribute LabelAngle{} LabelAngle{} = True
sameAttribute LabelDistance{} LabelDistance{} = True
sameAttribute LabelFloat{} LabelFloat{} = True
sameAttribute LabelFontColor{} LabelFontColor{} = True
sameAttribute LabelFontName{} LabelFontName{} = True
sameAttribute LabelFontSize{} LabelFontSize{} = True
sameAttribute LabelJust{} LabelJust{} = True
sameAttribute LabelLoc{} LabelLoc{} = True
sameAttribute LabelTarget{} LabelTarget{} = True
sameAttribute LabelTooltip{} LabelTooltip{} = True
sameAttribute Landscape{} Landscape{} = True
sameAttribute Layer{} Layer{} = True
sameAttribute LayerListSep{} LayerListSep{} = True
sameAttribute Layers{} Layers{} = True
sameAttribute LayerSelect{} LayerSelect{} = True
sameAttribute LayerSep{} LayerSep{} = True
sameAttribute Layout{} Layout{} = True
sameAttribute Len{} Len{} = True
sameAttribute Levels{} Levels{} = True
sameAttribute LevelsGap{} LevelsGap{} = True
sameAttribute LHead{} LHead{} = True
sameAttribute LHeight{} LHeight{} = True
sameAttribute LPos{} LPos{} = True
sameAttribute LTail{} LTail{} = True
sameAttribute LWidth{} LWidth{} = True
sameAttribute Margin{} Margin{} = True
sameAttribute MaxIter{} MaxIter{} = True
sameAttribute MCLimit{} MCLimit{} = True
sameAttribute MinDist{} MinDist{} = True
sameAttribute MinLen{} MinLen{} = True
sameAttribute Mode{} Mode{} = True
sameAttribute Model{} Model{} = True
sameAttribute Mosek{} Mosek{} = True
sameAttribute NodeSep{} NodeSep{} = True
sameAttribute NoJustify{} NoJustify{} = True
sameAttribute Normalize{} Normalize{} = True
sameAttribute Nslimit{} Nslimit{} = True
sameAttribute Nslimit1{} Nslimit1{} = True
sameAttribute Ordering{} Ordering{} = True
sameAttribute Orientation{} Orientation{} = True
sameAttribute OutputOrder{} OutputOrder{} = True
sameAttribute Overlap{} Overlap{} = True
sameAttribute OverlapScaling{} OverlapScaling{} = True
sameAttribute Pack{} Pack{} = True
sameAttribute PackMode{} PackMode{} = True
sameAttribute Pad{} Pad{} = True
sameAttribute Page{} Page{} = True
sameAttribute PageDir{} PageDir{} = True
sameAttribute PenColor{} PenColor{} = True
sameAttribute PenWidth{} PenWidth{} = True
sameAttribute Peripheries{} Peripheries{} = True
sameAttribute Pin{} Pin{} = True
sameAttribute Pos{} Pos{} = True
sameAttribute QuadTree{} QuadTree{} = True
sameAttribute Quantum{} Quantum{} = True
sameAttribute Rank{} Rank{} = True
sameAttribute RankDir{} RankDir{} = True
sameAttribute RankSep{} RankSep{} = True
sameAttribute Ratio{} Ratio{} = True
sameAttribute Rects{} Rects{} = True
sameAttribute Regular{} Regular{} = True
sameAttribute ReMinCross{} ReMinCross{} = True
sameAttribute RepulsiveForce{} RepulsiveForce{} = True
sameAttribute Root{} Root{} = True
sameAttribute Rotate{} Rotate{} = True
sameAttribute Rotation{} Rotation{} = True
sameAttribute SameHead{} SameHead{} = True
sameAttribute SameTail{} SameTail{} = True
sameAttribute SamplePoints{} SamplePoints{} = True
sameAttribute Scale{} Scale{} = True
sameAttribute SearchSize{} SearchSize{} = True
sameAttribute Sep{} Sep{} = True
sameAttribute Shape{} Shape{} = True
sameAttribute ShowBoxes{} ShowBoxes{} = True
sameAttribute Sides{} Sides{} = True
sameAttribute Size{} Size{} = True
sameAttribute Skew{} Skew{} = True
sameAttribute Smoothing{} Smoothing{} = True
sameAttribute SortV{} SortV{} = True
sameAttribute Splines{} Splines{} = True
sameAttribute Start{} Start{} = True
sameAttribute Style{} Style{} = True
sameAttribute StyleSheet{} StyleSheet{} = True
sameAttribute TailURL{} TailURL{} = True
sameAttribute Tail_LP{} Tail_LP{} = True
sameAttribute TailClip{} TailClip{} = True
sameAttribute TailLabel{} TailLabel{} = True
sameAttribute TailPort{} TailPort{} = True
sameAttribute TailTarget{} TailTarget{} = True
sameAttribute TailTooltip{} TailTooltip{} = True
sameAttribute Target{} Target{} = True
sameAttribute Tooltip{} Tooltip{} = True
sameAttribute TrueColor{} TrueColor{} = True
sameAttribute Vertices{} Vertices{} = True
sameAttribute ViewPort{} ViewPort{} = True
sameAttribute VoroMargin{} VoroMargin{} = True
sameAttribute Weight{} Weight{} = True
sameAttribute Width{} Width{} = True
sameAttribute XLabel{} XLabel{} = True
sameAttribute XLP{} XLP{} = True
sameAttribute (UnknownAttribute a1 _) (UnknownAttribute a2 _) = a1 == a2
sameAttribute _ _ = False
defaultAttributeValue :: Attribute -> Maybe Attribute
defaultAttributeValue Damping{} = Just $ Damping 0.99
defaultAttributeValue K{} = Just $ K 0.3
defaultAttributeValue URL{} = Just $ URL ""
defaultAttributeValue Area{} = Just $ Area 1.0
defaultAttributeValue ArrowHead{} = Just $ ArrowHead normal
defaultAttributeValue ArrowSize{} = Just $ ArrowSize 1.0
defaultAttributeValue ArrowTail{} = Just $ ArrowTail normal
defaultAttributeValue BgColor{} = Just $ BgColor []
defaultAttributeValue Center{} = Just $ Center False
defaultAttributeValue ClusterRank{} = Just $ ClusterRank Local
defaultAttributeValue Color{} = Just $ Color [toWColor Black]
defaultAttributeValue ColorScheme{} = Just $ ColorScheme X11
defaultAttributeValue Comment{} = Just $ Comment ""
defaultAttributeValue Compound{} = Just $ Compound False
defaultAttributeValue Concentrate{} = Just $ Concentrate False
defaultAttributeValue Constraint{} = Just $ Constraint True
defaultAttributeValue Decorate{} = Just $ Decorate False
defaultAttributeValue Dim{} = Just $ Dim 2
defaultAttributeValue Dimen{} = Just $ Dimen 2
defaultAttributeValue DirEdgeConstraints{} = Just $ DirEdgeConstraints NoConstraints
defaultAttributeValue Distortion{} = Just $ Distortion 0.0
defaultAttributeValue DPI{} = Just $ DPI 96.0
defaultAttributeValue EdgeURL{} = Just $ EdgeURL ""
defaultAttributeValue EdgeTooltip{} = Just $ EdgeTooltip ""
defaultAttributeValue ESep{} = Just $ ESep (DVal 3)
defaultAttributeValue FillColor{} = Just $ FillColor [toWColor Black]
defaultAttributeValue FixedSize{} = Just $ FixedSize False
defaultAttributeValue FontColor{} = Just $ FontColor (X11Color Black)
defaultAttributeValue FontName{} = Just $ FontName "Times-Roman"
defaultAttributeValue FontNames{} = Just $ FontNames SvgNames
defaultAttributeValue FontSize{} = Just $ FontSize 14.0
defaultAttributeValue ForceLabels{} = Just $ ForceLabels True
defaultAttributeValue GradientAngle{} = Just $ GradientAngle 0
defaultAttributeValue Group{} = Just $ Group ""
defaultAttributeValue HeadURL{} = Just $ HeadURL ""
defaultAttributeValue HeadClip{} = Just $ HeadClip True
defaultAttributeValue HeadLabel{} = Just $ HeadLabel (StrLabel "")
defaultAttributeValue HeadPort{} = Just $ HeadPort (CompassPoint CenterPoint)
defaultAttributeValue HeadTarget{} = Just $ HeadTarget ""
defaultAttributeValue HeadTooltip{} = Just $ HeadTooltip ""
defaultAttributeValue Height{} = Just $ Height 0.5
defaultAttributeValue ID{} = Just $ ID ""
defaultAttributeValue Image{} = Just $ Image ""
defaultAttributeValue ImagePath{} = Just $ ImagePath (Paths [])
defaultAttributeValue ImageScale{} = Just $ ImageScale NoScale
defaultAttributeValue Label{} = Just $ Label (StrLabel "")
defaultAttributeValue LabelURL{} = Just $ LabelURL ""
defaultAttributeValue LabelScheme{} = Just $ LabelScheme NotEdgeLabel
defaultAttributeValue LabelAngle{} = Just $ LabelAngle (25.0)
defaultAttributeValue LabelDistance{} = Just $ LabelDistance 1.0
defaultAttributeValue LabelFloat{} = Just $ LabelFloat False
defaultAttributeValue LabelFontColor{} = Just $ LabelFontColor (X11Color Black)
defaultAttributeValue LabelFontName{} = Just $ LabelFontName "Times-Roman"
defaultAttributeValue LabelFontSize{} = Just $ LabelFontSize 14.0
defaultAttributeValue LabelJust{} = Just $ LabelJust JCenter
defaultAttributeValue LabelLoc{} = Just $ LabelLoc VTop
defaultAttributeValue LabelTarget{} = Just $ LabelTarget ""
defaultAttributeValue LabelTooltip{} = Just $ LabelTooltip ""
defaultAttributeValue Landscape{} = Just $ Landscape False
defaultAttributeValue Layer{} = Just $ Layer []
defaultAttributeValue LayerListSep{} = Just $ LayerListSep (LLSep ",")
defaultAttributeValue Layers{} = Just $ Layers (LL [])
defaultAttributeValue LayerSelect{} = Just $ LayerSelect []
defaultAttributeValue LayerSep{} = Just $ LayerSep (LSep " :\t")
defaultAttributeValue Levels{} = Just $ Levels maxBound
defaultAttributeValue LevelsGap{} = Just $ LevelsGap 0.0
defaultAttributeValue LHead{} = Just $ LHead ""
defaultAttributeValue LTail{} = Just $ LTail ""
defaultAttributeValue MCLimit{} = Just $ MCLimit 1.0
defaultAttributeValue MinDist{} = Just $ MinDist 1.0
defaultAttributeValue MinLen{} = Just $ MinLen 1
defaultAttributeValue Mode{} = Just $ Mode Major
defaultAttributeValue Model{} = Just $ Model ShortPath
defaultAttributeValue Mosek{} = Just $ Mosek False
defaultAttributeValue NodeSep{} = Just $ NodeSep 0.25
defaultAttributeValue NoJustify{} = Just $ NoJustify False
defaultAttributeValue Normalize{} = Just $ Normalize False
defaultAttributeValue Orientation{} = Just $ Orientation 0.0
defaultAttributeValue OutputOrder{} = Just $ OutputOrder BreadthFirst
defaultAttributeValue Overlap{} = Just $ Overlap KeepOverlaps
defaultAttributeValue OverlapScaling{} = Just $ OverlapScaling (4)
defaultAttributeValue Pack{} = Just $ Pack DontPack
defaultAttributeValue PackMode{} = Just $ PackMode PackNode
defaultAttributeValue Pad{} = Just $ Pad (DVal 0.0555)
defaultAttributeValue PageDir{} = Just $ PageDir Bl
defaultAttributeValue PenColor{} = Just $ PenColor (X11Color Black)
defaultAttributeValue PenWidth{} = Just $ PenWidth 1.0
defaultAttributeValue Peripheries{} = Just $ Peripheries 1
defaultAttributeValue Pin{} = Just $ Pin False
defaultAttributeValue QuadTree{} = Just $ QuadTree NormalQT
defaultAttributeValue Quantum{} = Just $ Quantum 0
defaultAttributeValue RankDir{} = Just $ RankDir FromTop
defaultAttributeValue Regular{} = Just $ Regular False
defaultAttributeValue ReMinCross{} = Just $ ReMinCross False
defaultAttributeValue RepulsiveForce{} = Just $ RepulsiveForce 1.0
defaultAttributeValue Root{} = Just $ Root (NodeName "")
defaultAttributeValue Rotate{} = Just $ Rotate 0
defaultAttributeValue Rotation{} = Just $ Rotation 0
defaultAttributeValue SameHead{} = Just $ SameHead ""
defaultAttributeValue SameTail{} = Just $ SameTail ""
defaultAttributeValue SearchSize{} = Just $ SearchSize 30
defaultAttributeValue Sep{} = Just $ Sep (DVal 4)
defaultAttributeValue Shape{} = Just $ Shape Ellipse
defaultAttributeValue ShowBoxes{} = Just $ ShowBoxes 0
defaultAttributeValue Sides{} = Just $ Sides 4
defaultAttributeValue Skew{} = Just $ Skew 0.0
defaultAttributeValue Smoothing{} = Just $ Smoothing NoSmooth
defaultAttributeValue SortV{} = Just $ SortV 0
defaultAttributeValue StyleSheet{} = Just $ StyleSheet ""
defaultAttributeValue TailURL{} = Just $ TailURL ""
defaultAttributeValue TailClip{} = Just $ TailClip True
defaultAttributeValue TailLabel{} = Just $ TailLabel (StrLabel "")
defaultAttributeValue TailPort{} = Just $ TailPort (CompassPoint CenterPoint)
defaultAttributeValue TailTarget{} = Just $ TailTarget ""
defaultAttributeValue TailTooltip{} = Just $ TailTooltip ""
defaultAttributeValue Target{} = Just $ Target ""
defaultAttributeValue Tooltip{} = Just $ Tooltip ""
defaultAttributeValue VoroMargin{} = Just $ VoroMargin 0.05
defaultAttributeValue Weight{} = Just $ Weight 1.0
defaultAttributeValue Width{} = Just $ Width 0.75
defaultAttributeValue XLabel{} = Just $ XLabel (StrLabel "")
defaultAttributeValue _ = Nothing
validUnknown :: AttributeName -> Bool
validUnknown txt = T.toLower txt `S.notMember` names
&& isIDString txt
where
names = (S.fromList . map T.toLower
$ [ "Damping"
, "K"
, "URL"
, "href"
, "area"
, "arrowhead"
, "arrowsize"
, "arrowtail"
, "aspect"
, "bb"
, "bgcolor"
, "center"
, "clusterrank"
, "color"
, "colorscheme"
, "comment"
, "compound"
, "concentrate"
, "constraint"
, "decorate"
, "defaultdist"
, "dim"
, "dimen"
, "dir"
, "diredgeconstraints"
, "distortion"
, "dpi"
, "resolution"
, "edgeURL"
, "edgehref"
, "edgetarget"
, "edgetooltip"
, "epsilon"
, "esep"
, "fillcolor"
, "fixedsize"
, "fontcolor"
, "fontname"
, "fontnames"
, "fontpath"
, "fontsize"
, "forcelabels"
, "gradientangle"
, "group"
, "headURL"
, "headhref"
, "head_lp"
, "headclip"
, "headlabel"
, "headport"
, "headtarget"
, "headtooltip"
, "height"
, "id"
, "image"
, "imagepath"
, "imagescale"
, "label"
, "labelURL"
, "labelhref"
, "label_scheme"
, "labelangle"
, "labeldistance"
, "labelfloat"
, "labelfontcolor"
, "labelfontname"
, "labelfontsize"
, "labeljust"
, "labelloc"
, "labeltarget"
, "labeltooltip"
, "landscape"
, "layer"
, "layerlistsep"
, "layers"
, "layerselect"
, "layersep"
, "layout"
, "len"
, "levels"
, "levelsgap"
, "lhead"
, "LHeight"
, "lp"
, "ltail"
, "lwidth"
, "margin"
, "maxiter"
, "mclimit"
, "mindist"
, "minlen"
, "mode"
, "model"
, "mosek"
, "nodesep"
, "nojustify"
, "normalize"
, "nslimit"
, "nslimit1"
, "ordering"
, "orientation"
, "outputorder"
, "overlap"
, "overlap_scaling"
, "pack"
, "packmode"
, "pad"
, "page"
, "pagedir"
, "pencolor"
, "penwidth"
, "peripheries"
, "pin"
, "pos"
, "quadtree"
, "quantum"
, "rank"
, "rankdir"
, "ranksep"
, "ratio"
, "rects"
, "regular"
, "remincross"
, "repulsiveforce"
, "root"
, "rotate"
, "rotation"
, "samehead"
, "sametail"
, "samplepoints"
, "scale"
, "searchsize"
, "sep"
, "shape"
, "showboxes"
, "sides"
, "size"
, "skew"
, "smoothing"
, "sortv"
, "splines"
, "start"
, "style"
, "stylesheet"
, "tailURL"
, "tailhref"
, "tail_lp"
, "tailclip"
, "taillabel"
, "tailport"
, "tailtarget"
, "tailtooltip"
, "target"
, "tooltip"
, "truecolor"
, "vertices"
, "viewport"
, "voro_margin"
, "weight"
, "width"
, "xlabel"
, "xlp"
, "charset"
])
`S.union`
keywords
rmUnwantedAttributes :: Attributes -> Attributes
rmUnwantedAttributes = filter (not . (`any` tests) . flip ($))
where
tests = [isDefault, isColorScheme]
isDefault a = maybe False (a==) $ defaultAttributeValue a
isColorScheme ColorScheme{} = True
isColorScheme _ = False
parseField :: (ParseDot a) => (a -> Attribute) -> String
-> [(String, Parse Attribute)]
parseField c fld = [(fld, liftEqParse fld c)]
parseFields :: (ParseDot a) => (a -> Attribute) -> [String]
-> [(String, Parse Attribute)]
parseFields c = concatMap (parseField c)
parseFieldBool :: (Bool -> Attribute) -> String -> [(String, Parse Attribute)]
parseFieldBool = (`parseFieldDef` True)
parseFieldDef :: (ParseDot a) => (a -> Attribute) -> a -> String
-> [(String, Parse Attribute)]
parseFieldDef c d fld = [(fld, p)]
where
p = liftEqParse fld c
`onFail`
do nxt <- optional $ satisfy restIDString
bool (fail "Not actually the field you were after")
(return $ c d)
(isNothing nxt)
liftEqParse :: (ParseDot a) => String -> (a -> Attribute) -> Parse Attribute
liftEqParse k c = parseEq
*> ( hasDef (fmap c parse)
`adjustErrBad`
(("Unable to parse key=value with key of " ++ k
++ "\n\t") ++)
)
where
hasDef p = maybe p (onFail p . (`stringRep` "\"\""))
. defaultAttributeValue $ c undefined
type CustomAttribute = Attribute
customAttribute :: AttributeName -> Text -> CustomAttribute
customAttribute = UnknownAttribute
isCustom :: Attribute -> Bool
isCustom UnknownAttribute{} = True
isCustom _ = False
isSpecifiedCustom :: AttributeName -> Attribute -> Bool
isSpecifiedCustom nm (UnknownAttribute nm' _) = nm == nm'
isSpecifiedCustom _ _ = False
customValue :: CustomAttribute -> Text
customValue (UnknownAttribute _ v) = v
customValue attr = throw . NotCustomAttr . T.unpack
$ printIt attr
customName :: CustomAttribute -> AttributeName
customName (UnknownAttribute nm _) = nm
customName attr = throw . NotCustomAttr . T.unpack
$ printIt attr
findCustoms :: Attributes -> ([CustomAttribute], Attributes)
findCustoms = partition isCustom
findSpecifiedCustom :: AttributeName -> Attributes
-> Maybe (CustomAttribute, Attributes)
findSpecifiedCustom nm attrs
= case break (isSpecifiedCustom nm) attrs of
(bf,cust:aft) -> Just (cust, bf ++ aft)
_ -> Nothing
deleteCustomAttributes :: Attributes -> Attributes
deleteCustomAttributes = filter (not . isCustom)
deleteSpecifiedCustom :: AttributeName -> Attributes -> Attributes
deleteSpecifiedCustom nm = filter (not . isSpecifiedCustom nm)
data GraphvizCommand = Dot
| Neato
| TwoPi
| Circo
| Fdp
| Sfdp
| Osage
| Patchwork
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot GraphvizCommand where
unqtDot Dot = text "dot"
unqtDot Neato = text "neato"
unqtDot TwoPi = text "twopi"
unqtDot Circo = text "circo"
unqtDot Fdp = text "fdp"
unqtDot Sfdp = text "sfdp"
unqtDot Osage = text "osage"
unqtDot Patchwork = text "patchwork"
instance ParseDot GraphvizCommand where
parseUnqt = stringValue [ ("dot", Dot)
, ("neato", Neato)
, ("twopi", TwoPi)
, ("circo", Circo)
, ("fdp", Fdp)
, ("sfdp", Sfdp)
, ("osage", Osage)
, ("patchwork", Patchwork)
]
type EscString = Text
newtype ArrowType = AType [(ArrowModifier, ArrowShape)]
deriving (Eq, Ord, Show, Read)
normal :: ArrowType
normal = AType [(noMods, Normal)]
eDiamond, openArr, halfOpen, emptyArr, invEmpty :: ArrowType
eDiamond = AType [(openMod, Diamond)]
openArr = AType [(noMods, Vee)]
halfOpen = AType [(ArrMod FilledArrow LeftSide, Vee)]
emptyArr = AType [(openMod, Normal)]
invEmpty = AType [ (noMods, Inv)
, (openMod, Normal)]
instance PrintDot ArrowType where
unqtDot (AType mas) = hcat $ mapM appMod mas
where
appMod (m, a) = unqtDot m <> unqtDot a
instance ParseDot ArrowType where
parseUnqt = specialArrowParse
`onFail`
(AType <$> many1 (liftA2 (,) parseUnqt parseUnqt))
specialArrowParse :: Parse ArrowType
specialArrowParse = stringValue [ ("ediamond", eDiamond)
, ("open", openArr)
, ("halfopen", halfOpen)
, ("empty", emptyArr)
, ("invempty", invEmpty)
]
data ArrowShape = Box
| Crow
| Diamond
| DotArrow
| Inv
| NoArrow
| Normal
| Tee
| Vee
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot ArrowShape where
unqtDot Box = text "box"
unqtDot Crow = text "crow"
unqtDot Diamond = text "diamond"
unqtDot DotArrow = text "dot"
unqtDot Inv = text "inv"
unqtDot NoArrow = text "none"
unqtDot Normal = text "normal"
unqtDot Tee = text "tee"
unqtDot Vee = text "vee"
instance ParseDot ArrowShape where
parseUnqt = stringValue [ ("box", Box)
, ("crow", Crow)
, ("diamond", Diamond)
, ("dot", DotArrow)
, ("inv", Inv)
, ("none", NoArrow)
, ("normal", Normal)
, ("tee", Tee)
, ("vee", Vee)
]
data ArrowModifier = ArrMod { arrowFill :: ArrowFill
, arrowSide :: ArrowSide
}
deriving (Eq, Ord, Show, Read)
noMods :: ArrowModifier
noMods = ArrMod FilledArrow BothSides
openMod :: ArrowModifier
openMod = ArrMod OpenArrow BothSides
instance PrintDot ArrowModifier where
unqtDot (ArrMod f s) = unqtDot f <> unqtDot s
instance ParseDot ArrowModifier where
parseUnqt = liftA2 ArrMod parseUnqt parseUnqt
data ArrowFill = OpenArrow
| FilledArrow
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot ArrowFill where
unqtDot OpenArrow = char 'o'
unqtDot FilledArrow = empty
instance ParseDot ArrowFill where
parseUnqt = bool FilledArrow OpenArrow . isJust <$> optional (character 'o')
parse = parseUnqt
data ArrowSide = LeftSide
| RightSide
| BothSides
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot ArrowSide where
unqtDot LeftSide = char 'l'
unqtDot RightSide = char 'r'
unqtDot BothSides = empty
instance ParseDot ArrowSide where
parseUnqt = getSideType <$> optional (oneOf $ map character ['l', 'r'])
where
getSideType = maybe BothSides
(bool RightSide LeftSide . (==) 'l')
parse = parseUnqt
data AspectType = RatioOnly Double
| RatioPassCount Double Int
deriving (Eq, Ord, Show, Read)
instance PrintDot AspectType where
unqtDot (RatioOnly r) = unqtDot r
unqtDot (RatioPassCount r p) = commaDel r p
toDot at@RatioOnly{} = unqtDot at
toDot at@RatioPassCount{} = dquotes $ unqtDot at
instance ParseDot AspectType where
parseUnqt = fmap (uncurry RatioPassCount) commaSepUnqt
`onFail`
fmap RatioOnly parseUnqt
parse = quotedParse (uncurry RatioPassCount <$> commaSepUnqt)
`onFail`
fmap RatioOnly parse
data Rect = Rect Point Point
deriving (Eq, Ord, Show, Read)
instance PrintDot Rect where
unqtDot (Rect p1 p2) = printPoint2DUnqt p1 <> comma <> printPoint2DUnqt p2
toDot = dquotes . unqtDot
unqtListToDot = hsep . mapM unqtDot
instance ParseDot Rect where
parseUnqt = uncurry Rect <$> commaSep' parsePoint2D parsePoint2D
parse = quotedParse parseUnqt
parseUnqtList = sepBy1 parseUnqt whitespace1
data ClusterMode = Local
| Global
| NoCluster
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot ClusterMode where
unqtDot Local = text "local"
unqtDot Global = text "global"
unqtDot NoCluster = text "none"
instance ParseDot ClusterMode where
parseUnqt = oneOf [ stringRep Local "local"
, stringRep Global "global"
, stringRep NoCluster "none"
]
data DirType = Forward
| Back
| Both
| NoDir
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot DirType where
unqtDot Forward = text "forward"
unqtDot Back = text "back"
unqtDot Both = text "both"
unqtDot NoDir = text "none"
instance ParseDot DirType where
parseUnqt = oneOf [ stringRep Forward "forward"
, stringRep Back "back"
, stringRep Both "both"
, stringRep NoDir "none"
]
data DEConstraints = EdgeConstraints
| NoConstraints
| HierConstraints
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot DEConstraints where
unqtDot EdgeConstraints = unqtDot True
unqtDot NoConstraints = unqtDot False
unqtDot HierConstraints = text "hier"
instance ParseDot DEConstraints where
parseUnqt = fmap (bool NoConstraints EdgeConstraints) parse
`onFail`
stringRep HierConstraints "hier"
data DPoint = DVal Double
| PVal Point
deriving (Eq, Ord, Show, Read)
instance PrintDot DPoint where
unqtDot (DVal d) = unqtDot d
unqtDot (PVal p) = printPoint2DUnqt p
toDot (DVal d) = toDot d
toDot (PVal p) = printPoint2D p
instance ParseDot DPoint where
parseUnqt = optional (character '+')
*> oneOf [ PVal <$> parsePoint2D
, DVal <$> parseUnqt
]
parse = quotedParse parseUnqt
`onFail`
fmap DVal parseUnqt
data SVGFontNames = SvgNames
| PostScriptNames
| FontConfigNames
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot SVGFontNames where
unqtDot SvgNames = text "svg"
unqtDot PostScriptNames = text "ps"
unqtDot FontConfigNames = text "gd"
instance ParseDot SVGFontNames where
parseUnqt = oneOf [ stringRep SvgNames "svg"
, stringRep PostScriptNames "ps"
, stringRep FontConfigNames "gd"
]
parse = stringRep SvgNames "\"\""
`onFail`
optionalQuoted parseUnqt
data GraphSize = GSize { width :: Double
, height :: Maybe Double
, desiredSize :: Bool
}
deriving (Eq, Ord, Show, Read)
instance PrintDot GraphSize where
unqtDot (GSize w mh ds) = bool id (<> char '!') ds
. maybe id (\h -> (<> unqtDot h) . (<> comma)) mh
$ unqtDot w
toDot (GSize w Nothing False) = toDot w
toDot gs = dquotes $ unqtDot gs
instance ParseDot GraphSize where
parseUnqt = GSize <$> parseUnqt
<*> optional (parseComma *> whitespace *> parseUnqt)
<*> (isJust <$> optional (character '!'))
parse = quotedParse parseUnqt
`onFail`
fmap (\ w -> GSize w Nothing False) parseUnqt
data ModeType = Major
| KK
| Hier
| IpSep
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot ModeType where
unqtDot Major = text "major"
unqtDot KK = text "KK"
unqtDot Hier = text "hier"
unqtDot IpSep = text "ipsep"
instance ParseDot ModeType where
parseUnqt = oneOf [ stringRep Major "major"
, stringRep KK "KK"
, stringRep Hier "hier"
, stringRep IpSep "ipsep"
]
data Model = ShortPath
| SubSet
| Circuit
| MDS
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot Model where
unqtDot ShortPath = text "shortpath"
unqtDot SubSet = text "subset"
unqtDot Circuit = text "circuit"
unqtDot MDS = text "mds"
instance ParseDot Model where
parseUnqt = oneOf [ stringRep ShortPath "shortpath"
, stringRep SubSet "subset"
, stringRep Circuit "circuit"
, stringRep MDS "mds"
]
data Label = StrLabel EscString
| HtmlLabel Html.Label
| RecordLabel RecordFields
deriving (Eq, Ord, Show, Read)
instance PrintDot Label where
unqtDot (StrLabel s) = unqtDot s
unqtDot (HtmlLabel h) = angled $ unqtDot h
unqtDot (RecordLabel fs) = unqtDot fs
toDot (StrLabel s) = toDot s
toDot h@HtmlLabel{} = unqtDot h
toDot (RecordLabel fs) = toDot fs
instance ParseDot Label where
parseUnqt = oneOf [ HtmlLabel <$> parseAngled parseUnqt
, RecordLabel <$> parseUnqt
, StrLabel <$> parseUnqt
]
parse = oneOf [ HtmlLabel <$> parseAngled parse
, RecordLabel <$> parse
, StrLabel <$> parse
]
type RecordFields = [RecordField]
data RecordField = LabelledTarget PortName EscString
| PortName PortName
| FieldLabel EscString
| FlipFields RecordFields
deriving (Eq, Ord, Show, Read)
instance PrintDot RecordField where
unqtDot (LabelledTarget t s) = printPortName t <+> unqtRecordString s
unqtDot (PortName t) = printPortName t
unqtDot (FieldLabel s) = unqtRecordString s
unqtDot (FlipFields rs) = braces $ unqtDot rs
toDot (FieldLabel s) = printEscaped recordEscChars s
toDot rf = dquotes $ unqtDot rf
unqtListToDot [f] = unqtDot f
unqtListToDot fs = hcat . punctuate (char '|') $ mapM unqtDot fs
listToDot [f] = toDot f
listToDot fs = dquotes $ unqtListToDot fs
instance ParseDot RecordField where
parseUnqt = (liftA2 maybe PortName LabelledTarget
<$> (PN <$> parseAngled parseRecord)
<*> optional (whitespace1 *> parseRecord)
)
`onFail`
fmap FieldLabel parseRecord
`onFail`
fmap FlipFields (parseBraced parseUnqt)
`onFail`
fail "Unable to parse RecordField"
parse = quotedParse parseUnqt
parseUnqtList = wrapWhitespace $ sepBy1 parseUnqt (wrapWhitespace $ character '|')
parseList = do rfs <- quotedParse parseUnqtList
if validRFs rfs
then return rfs
else fail "This is a StrLabel, not a RecordLabel"
where
validRFs [FieldLabel str] = T.any (`elem` recordEscChars) str
validRFs _ = True
printPortName :: PortName -> DotCode
printPortName = angled . unqtRecordString . portName
parseRecord :: Parse Text
parseRecord = parseEscaped False recordEscChars []
unqtRecordString :: Text -> DotCode
unqtRecordString = unqtEscaped recordEscChars
recordEscChars :: [Char]
recordEscChars = ['{', '}', '|', ' ', '<', '>']
data LabelScheme = NotEdgeLabel
| CloseToCenter
| CloseToOldCenter
| RemoveAndStraighten
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot LabelScheme where
unqtDot NotEdgeLabel = int 0
unqtDot CloseToCenter = int 1
unqtDot CloseToOldCenter = int 2
unqtDot RemoveAndStraighten = int 3
instance ParseDot LabelScheme where
parseUnqt = stringValue [ ("0", NotEdgeLabel)
, ("1", CloseToCenter)
, ("2", CloseToOldCenter)
, ("3", RemoveAndStraighten)
]
data Point = Point { xCoord :: Double
, yCoord :: Double
, zCoord :: Maybe Double
, forcePos :: Bool
}
deriving (Eq, Ord, Show, Read)
createPoint :: Double -> Double -> Point
createPoint x y = Point x y Nothing False
printPoint2DUnqt :: Point -> DotCode
printPoint2DUnqt p = commaDel (xCoord p) (yCoord p)
printPoint2D :: Point -> DotCode
printPoint2D = dquotes . printPoint2DUnqt
parsePoint2D :: Parse Point
parsePoint2D = uncurry createPoint <$> commaSepUnqt
instance PrintDot Point where
unqtDot (Point x y mz frs) = bool id (<> char '!') frs
. maybe id (\ z -> (<> unqtDot z) . (<> comma)) mz
$ commaDel x y
toDot = dquotes . unqtDot
unqtListToDot = hsep . mapM unqtDot
listToDot = dquotes . unqtListToDot
instance ParseDot Point where
parseUnqt = uncurry Point
<$> commaSepUnqt
<*> optional (parseComma *> parseUnqt)
<*> (isJust <$> optional (character '!'))
parse = quotedParse parseUnqt
parseUnqtList = sepBy1 parseUnqt whitespace1
data Overlap = KeepOverlaps
| ScaleOverlaps
| ScaleXYOverlaps
| PrismOverlap (Maybe Word16)
| VoronoiOverlap
| CompressOverlap
| VpscOverlap
| IpsepOverlap
deriving (Eq, Ord, Show, Read)
instance PrintDot Overlap where
unqtDot KeepOverlaps = unqtDot True
unqtDot ScaleOverlaps = text "scale"
unqtDot ScaleXYOverlaps = text "scalexy"
unqtDot (PrismOverlap i) = maybe id (flip (<>) . unqtDot) i $ text "prism"
unqtDot VoronoiOverlap = text "voronoi"
unqtDot CompressOverlap = text "compress"
unqtDot VpscOverlap = text "vpsc"
unqtDot IpsepOverlap = text "ipsep"
instance ParseDot Overlap where
parseUnqt = oneOf [ stringRep KeepOverlaps "true"
, stringRep ScaleXYOverlaps "scalexy"
, stringRep ScaleOverlaps "scale"
, string "prism" *> fmap PrismOverlap (optional parse)
, stringRep (PrismOverlap Nothing) "false"
, stringRep VoronoiOverlap "voronoi"
, stringRep CompressOverlap "compress"
, stringRep VpscOverlap "vpsc"
, stringRep IpsepOverlap "ipsep"
]
newtype LayerSep = LSep Text
deriving (Eq, Ord, Show, Read)
instance PrintDot LayerSep where
unqtDot (LSep ls) = setLayerSep (T.unpack ls) *> unqtDot ls
toDot (LSep ls) = setLayerSep (T.unpack ls) *> toDot ls
instance ParseDot LayerSep where
parseUnqt = do ls <- parseUnqt
setLayerSep $ T.unpack ls
return $ LSep ls
parse = do ls <- parse
setLayerSep $ T.unpack ls
return $ LSep ls
newtype LayerListSep = LLSep Text
deriving (Eq, Ord, Show, Read)
instance PrintDot LayerListSep where
unqtDot (LLSep ls) = setLayerListSep (T.unpack ls) *> unqtDot ls
toDot (LLSep ls) = setLayerListSep (T.unpack ls) *> toDot ls
instance ParseDot LayerListSep where
parseUnqt = do ls <- parseUnqt
setLayerListSep $ T.unpack ls
return $ LLSep ls
parse = do ls <- parse
setLayerListSep $ T.unpack ls
return $ LLSep ls
type LayerRange = [LayerRangeElem]
data LayerRangeElem = LRID LayerID
| LRS LayerID LayerID
deriving (Eq, Ord, Show, Read)
instance PrintDot LayerRangeElem where
unqtDot (LRID lid) = unqtDot lid
unqtDot (LRS id1 id2) = do ls <- getLayerSep
let s = unqtDot $ head ls
unqtDot id1 <> s <> unqtDot id2
toDot (LRID lid) = toDot lid
toDot lrs = dquotes $ unqtDot lrs
unqtListToDot lr = do lls <- getLayerListSep
let s = unqtDot $ head lls
hcat . punctuate s $ mapM unqtDot lr
listToDot [lre] = toDot lre
listToDot lrs = dquotes $ unqtListToDot lrs
instance ParseDot LayerRangeElem where
parseUnqt = ignoreSep LRS parseUnqt parseLayerSep parseUnqt
`onFail`
fmap LRID parseUnqt
parse = quotedParse (ignoreSep LRS parseUnqt parseLayerSep parseUnqt)
`onFail`
fmap LRID parse
parseUnqtList = sepBy parseUnqt parseLayerListSep
parseList = quotedParse parseUnqtList
`onFail`
fmap ((:[]) . LRID) parse
parseLayerSep :: Parse ()
parseLayerSep = do ls <- getLayerSep
many1Satisfy (`elem` ls) *> return ()
parseLayerName :: Parse Text
parseLayerName = parseEscaped False [] =<< liftA2 (++) getLayerSep getLayerListSep
parseLayerName' :: Parse Text
parseLayerName' = stringBlock
`onFail`
quotedParse parseLayerName
parseLayerListSep :: Parse ()
parseLayerListSep = do lls <- getLayerListSep
many1Satisfy (`elem` lls) *> return ()
data LayerID = AllLayers
| LRInt Int
| LRName Text
deriving (Eq, Ord, Show, Read)
instance PrintDot LayerID where
unqtDot AllLayers = text "all"
unqtDot (LRInt n) = unqtDot n
unqtDot (LRName nm) = unqtDot nm
toDot (LRName nm) = toDot nm
toDot li = unqtDot li
unqtListToDot ll = do ls <- getLayerSep
let s = unqtDot $ head ls
hcat . punctuate s $ mapM unqtDot ll
listToDot [l] = toDot l
listToDot ll = dquotes $ unqtDot ll
instance ParseDot LayerID where
parseUnqt = checkLayerName <$> parseLayerName
parse = oneOf [ checkLayerName <$> parseLayerName'
, LRInt <$> parse
]
checkLayerName :: Text -> LayerID
checkLayerName str = maybe checkAll LRInt $ stringToInt str
where
checkAll = if T.toLower str == "all"
then AllLayers
else LRName str
newtype LayerList = LL [LayerID]
deriving (Eq, Ord, Show, Read)
instance PrintDot LayerList where
unqtDot (LL ll) = unqtDot ll
toDot (LL ll) = toDot ll
instance ParseDot LayerList where
parseUnqt = LL <$> sepBy1 parseUnqt parseLayerSep
parse = quotedParse parseUnqt
`onFail`
fmap (LL . (:[]) . LRName) stringBlock
`onFail`
quotedParse (stringRep (LL []) "")
data Order = OutEdges
| InEdges
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot Order where
unqtDot OutEdges = text "out"
unqtDot InEdges = text "in"
instance ParseDot Order where
parseUnqt = oneOf [ stringRep OutEdges "out"
, stringRep InEdges "in"
]
data OutputMode = BreadthFirst | NodesFirst | EdgesFirst
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot OutputMode where
unqtDot BreadthFirst = text "breadthfirst"
unqtDot NodesFirst = text "nodesfirst"
unqtDot EdgesFirst = text "edgesfirst"
instance ParseDot OutputMode where
parseUnqt = oneOf [ stringRep BreadthFirst "breadthfirst"
, stringRep NodesFirst "nodesfirst"
, stringRep EdgesFirst "edgesfirst"
]
data Pack = DoPack
| DontPack
| PackMargin Int
deriving (Eq, Ord, Show, Read)
instance PrintDot Pack where
unqtDot DoPack = unqtDot True
unqtDot DontPack = unqtDot False
unqtDot (PackMargin m) = unqtDot m
instance ParseDot Pack where
parseUnqt = oneOf [ PackMargin <$> parseUnqt
, bool DontPack DoPack <$> onlyBool
]
data PackMode = PackNode
| PackClust
| PackGraph
| PackArray Bool Bool (Maybe Int)
deriving (Eq, Ord, Show, Read)
instance PrintDot PackMode where
unqtDot PackNode = text "node"
unqtDot PackClust = text "clust"
unqtDot PackGraph = text "graph"
unqtDot (PackArray c u mi) = addNum . isU . isC . isUnder
$ text "array"
where
addNum = maybe id (flip (<>) . unqtDot) mi
isUnder = if c || u
then (<> char '_')
else id
isC = if c
then (<> char 'c')
else id
isU = if u
then (<> char 'u')
else id
instance ParseDot PackMode where
parseUnqt = oneOf [ stringRep PackNode "node"
, stringRep PackClust "clust"
, stringRep PackGraph "graph"
, do string "array"
mcu <- optional $ character '_' *> many1 (satisfy isCU)
let c = hasCharacter mcu 'c'
u = hasCharacter mcu 'u'
mi <- optional parseUnqt
return $ PackArray c u mi
]
where
hasCharacter ms c = maybe False (elem c) ms
isCU = (`elem` ['c', 'u'])
data Pos = PointPos Point
| SplinePos [Spline]
deriving (Eq, Ord, Show, Read)
instance PrintDot Pos where
unqtDot (PointPos p) = unqtDot p
unqtDot (SplinePos ss) = unqtDot ss
toDot (PointPos p) = toDot p
toDot (SplinePos ss) = toDot ss
instance ParseDot Pos where
parseUnqt = do splns <- parseUnqt
case splns of
[Spline Nothing Nothing [p]] -> return $ PointPos p
_ -> return $ SplinePos splns
parse = quotedParse parseUnqt
data EdgeType = SplineEdges
| LineEdges
| NoEdges
| PolyLine
| Ortho
| Curved
| CompoundEdge
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot EdgeType where
unqtDot SplineEdges = text "spline"
unqtDot LineEdges = text "line"
unqtDot NoEdges = empty
unqtDot PolyLine = text "polyline"
unqtDot Ortho = text "ortho"
unqtDot Curved = text "curved"
unqtDot CompoundEdge = text "compound"
toDot NoEdges = dquotes empty
toDot et = unqtDot et
instance ParseDot EdgeType where
parseUnqt = oneOf [ bool LineEdges SplineEdges <$> parse
, stringRep SplineEdges "spline"
, stringRep LineEdges "line"
, stringRep NoEdges "none"
, stringRep PolyLine "polyline"
, stringRep Ortho "ortho"
, stringRep Curved "curved"
, stringRep CompoundEdge "compound"
]
parse = stringRep NoEdges "\"\""
`onFail`
optionalQuoted parseUnqt
data PageDir = Bl | Br | Tl | Tr | Rb | Rt | Lb | Lt
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot PageDir where
unqtDot Bl = text "BL"
unqtDot Br = text "BR"
unqtDot Tl = text "TL"
unqtDot Tr = text "TR"
unqtDot Rb = text "RB"
unqtDot Rt = text "RT"
unqtDot Lb = text "LB"
unqtDot Lt = text "LT"
instance ParseDot PageDir where
parseUnqt = stringValue [ ("BL", Bl)
, ("BR", Br)
, ("TL", Tl)
, ("TR", Tr)
, ("RB", Rb)
, ("RT", Rt)
, ("LB", Lb)
, ("LT", Lt)
]
data Spline = Spline { endPoint :: Maybe Point
, startPoint :: Maybe Point
, splinePoints :: [Point]
}
deriving (Eq, Ord, Show, Read)
instance PrintDot Spline where
unqtDot (Spline me ms ps) = addE . addS
. hsep
$ mapM unqtDot ps
where
addP t = maybe id ((<+>) . commaDel t)
addS = addP 's' ms
addE = addP 'e' me
toDot = dquotes . unqtDot
unqtListToDot = hcat . punctuate semi . mapM unqtDot
listToDot = dquotes . unqtListToDot
instance ParseDot Spline where
parseUnqt = Spline <$> parseP 'e' <*> parseP 's'
<*> sepBy1 parseUnqt whitespace1
where
parseP t = optional (character t *> parseComma *> parseUnqt <* whitespace1)
parse = quotedParse parseUnqt
parseUnqtList = sepBy1 parseUnqt (character ';')
data QuadType = NormalQT
| FastQT
| NoQT
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot QuadType where
unqtDot NormalQT = text "normal"
unqtDot FastQT = text "fast"
unqtDot NoQT = text "none"
instance ParseDot QuadType where
parseUnqt = oneOf [ stringRep NormalQT "normal"
, stringRep FastQT "fast"
, stringRep NoQT "none"
, character '2' *> return FastQT
, bool NoQT NormalQT <$> parse
]
data Root = IsCentral
| NotCentral
| NodeName Text
deriving (Eq, Ord, Show, Read)
instance PrintDot Root where
unqtDot IsCentral = unqtDot True
unqtDot NotCentral = unqtDot False
unqtDot (NodeName n) = unqtDot n
toDot (NodeName n) = toDot n
toDot r = unqtDot r
instance ParseDot Root where
parseUnqt = fmap (bool NotCentral IsCentral) onlyBool
`onFail`
fmap NodeName parseUnqt
parse = optionalQuoted (bool NotCentral IsCentral <$> onlyBool)
`onFail`
fmap NodeName parse
data RankType = SameRank
| MinRank
| SourceRank
| MaxRank
| SinkRank
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot RankType where
unqtDot SameRank = text "same"
unqtDot MinRank = text "min"
unqtDot SourceRank = text "source"
unqtDot MaxRank = text "max"
unqtDot SinkRank = text "sink"
instance ParseDot RankType where
parseUnqt = stringValue [ ("same", SameRank)
, ("min", MinRank)
, ("source", SourceRank)
, ("max", MaxRank)
, ("sink", SinkRank)
]
data RankDir = FromTop
| FromLeft
| FromBottom
| FromRight
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot RankDir where
unqtDot FromTop = text "TB"
unqtDot FromLeft = text "LR"
unqtDot FromBottom = text "BT"
unqtDot FromRight = text "RL"
instance ParseDot RankDir where
parseUnqt = oneOf [ stringRep FromTop "TB"
, stringRep FromLeft "LR"
, stringRep FromBottom "BT"
, stringRep FromRight "RL"
]
data Shape
= BoxShape
| Polygon
| Ellipse
| Circle
| PointShape
| Egg
| Triangle
| PlainText
| DiamondShape
| Trapezium
| Parallelogram
| House
| Pentagon
| Hexagon
| Septagon
| Octagon
| DoubleCircle
| DoubleOctagon
| TripleOctagon
| InvTriangle
| InvTrapezium
| InvHouse
| MDiamond
| MSquare
| MCircle
| Note
| Tab
| Folder
| Box3D
| Component
| Promoter
| CDS
| Terminator
| UTR
| PrimerSite
| RestrictionSite
| FivePovOverhang
| ThreePovOverhang
| NoOverhang
| Assembly
| Signature
| Insulator
| Ribosite
| RNAStab
| ProteaseSite
| ProteinStab
| RPromoter
| RArrow
| LArrow
| LPromoter
| Record
| MRecord
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot Shape where
unqtDot BoxShape = text "box"
unqtDot Polygon = text "polygon"
unqtDot Ellipse = text "ellipse"
unqtDot Circle = text "circle"
unqtDot PointShape = text "point"
unqtDot Egg = text "egg"
unqtDot Triangle = text "triangle"
unqtDot PlainText = text "plaintext"
unqtDot DiamondShape = text "diamond"
unqtDot Trapezium = text "trapezium"
unqtDot Parallelogram = text "parallelogram"
unqtDot House = text "house"
unqtDot Pentagon = text "pentagon"
unqtDot Hexagon = text "hexagon"
unqtDot Septagon = text "septagon"
unqtDot Octagon = text "octagon"
unqtDot DoubleCircle = text "doublecircle"
unqtDot DoubleOctagon = text "doubleoctagon"
unqtDot TripleOctagon = text "tripleoctagon"
unqtDot InvTriangle = text "invtriangle"
unqtDot InvTrapezium = text "invtrapezium"
unqtDot InvHouse = text "invhouse"
unqtDot MDiamond = text "Mdiamond"
unqtDot MSquare = text "Msquare"
unqtDot MCircle = text "Mcircle"
unqtDot Note = text "note"
unqtDot Tab = text "tab"
unqtDot Folder = text "folder"
unqtDot Box3D = text "box3d"
unqtDot Component = text "component"
unqtDot Promoter = text "promoter"
unqtDot CDS = text "cds"
unqtDot Terminator = text "terminator"
unqtDot UTR = text "utr"
unqtDot PrimerSite = text "primersite"
unqtDot RestrictionSite = text "restrictionsite"
unqtDot FivePovOverhang = text "fivepovoverhang"
unqtDot ThreePovOverhang = text "threepovoverhang"
unqtDot NoOverhang = text "nooverhang"
unqtDot Assembly = text "assembly"
unqtDot Signature = text "signature"
unqtDot Insulator = text "insulator"
unqtDot Ribosite = text "ribosite"
unqtDot RNAStab = text "rnastab"
unqtDot ProteaseSite = text "proteasesite"
unqtDot ProteinStab = text "proteinstab"
unqtDot RPromoter = text "rpromoter"
unqtDot RArrow = text "rarrow"
unqtDot LArrow = text "larrow"
unqtDot LPromoter = text "lpromoter"
unqtDot Record = text "record"
unqtDot MRecord = text "Mrecord"
instance ParseDot Shape where
parseUnqt = stringValue [ ("box3d", Box3D)
, ("box", BoxShape)
, ("rectangle", BoxShape)
, ("rect", BoxShape)
, ("polygon", Polygon)
, ("ellipse", Ellipse)
, ("oval", Ellipse)
, ("circle", Circle)
, ("point", PointShape)
, ("egg", Egg)
, ("triangle", Triangle)
, ("plaintext", PlainText)
, ("none", PlainText)
, ("diamond", DiamondShape)
, ("trapezium", Trapezium)
, ("parallelogram", Parallelogram)
, ("house", House)
, ("pentagon", Pentagon)
, ("hexagon", Hexagon)
, ("septagon", Septagon)
, ("octagon", Octagon)
, ("doublecircle", DoubleCircle)
, ("doubleoctagon", DoubleOctagon)
, ("tripleoctagon", TripleOctagon)
, ("invtriangle", InvTriangle)
, ("invtrapezium", InvTrapezium)
, ("invhouse", InvHouse)
, ("Mdiamond", MDiamond)
, ("Msquare", MSquare)
, ("Mcircle", MCircle)
, ("note", Note)
, ("tab", Tab)
, ("folder", Folder)
, ("component", Component)
, ("promoter", Promoter)
, ("cds", CDS)
, ("terminator", Terminator)
, ("utr", UTR)
, ("primersite", PrimerSite)
, ("restrictionsite", RestrictionSite)
, ("fivepovoverhang", FivePovOverhang)
, ("threepovoverhang", ThreePovOverhang)
, ("nooverhang", NoOverhang)
, ("assembly", Assembly)
, ("signature", Signature)
, ("insulator", Insulator)
, ("ribosite", Ribosite)
, ("rnastab", RNAStab)
, ("proteasesite", ProteaseSite)
, ("proteinstab", ProteinStab)
, ("rpromoter", RPromoter)
, ("rarrow", RArrow)
, ("larrow", LArrow)
, ("lpromoter", LPromoter)
, ("record", Record)
, ("Mrecord", MRecord)
]
data SmoothType = NoSmooth
| AvgDist
| GraphDist
| PowerDist
| RNG
| Spring
| TriangleSmooth
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot SmoothType where
unqtDot NoSmooth = text "none"
unqtDot AvgDist = text "avg_dist"
unqtDot GraphDist = text "graph_dist"
unqtDot PowerDist = text "power_dist"
unqtDot RNG = text "rng"
unqtDot Spring = text "spring"
unqtDot TriangleSmooth = text "triangle"
instance ParseDot SmoothType where
parseUnqt = oneOf [ stringRep NoSmooth "none"
, stringRep AvgDist "avg_dist"
, stringRep GraphDist "graph_dist"
, stringRep PowerDist "power_dist"
, stringRep RNG "rng"
, stringRep Spring "spring"
, stringRep TriangleSmooth "triangle"
]
data StartType = StartStyle STStyle
| StartSeed Int
| StartStyleSeed STStyle Int
deriving (Eq, Ord, Show, Read)
instance PrintDot StartType where
unqtDot (StartStyle ss) = unqtDot ss
unqtDot (StartSeed s) = unqtDot s
unqtDot (StartStyleSeed ss s) = unqtDot ss <> unqtDot s
instance ParseDot StartType where
parseUnqt = oneOf [ liftA2 StartStyleSeed parseUnqt parseUnqt
, StartStyle <$> parseUnqt
, StartSeed <$> parseUnqt
]
data STStyle = RegularStyle
| SelfStyle
| RandomStyle
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot STStyle where
unqtDot RegularStyle = text "regular"
unqtDot SelfStyle = text "self"
unqtDot RandomStyle = text "random"
instance ParseDot STStyle where
parseUnqt = oneOf [ stringRep RegularStyle "regular"
, stringRep SelfStyle "self"
, stringRep RandomStyle "random"
]
data StyleItem = SItem StyleName [Text]
deriving (Eq, Ord, Show, Read)
instance PrintDot StyleItem where
unqtDot (SItem nm args)
| null args = dnm
| otherwise = dnm <> parens args'
where
dnm = unqtDot nm
args' = hcat . punctuate comma $ mapM unqtDot args
toDot si@(SItem nm args)
| null args = toDot nm
| otherwise = dquotes $ unqtDot si
unqtListToDot = hcat . punctuate comma . mapM unqtDot
listToDot [SItem nm []] = toDot nm
listToDot sis = dquotes $ unqtListToDot sis
instance ParseDot StyleItem where
parseUnqt = liftA2 SItem parseUnqt (tryParseList' parseArgs)
parse = quotedParse (liftA2 SItem parseUnqt parseArgs)
`onFail`
fmap (`SItem` []) parse
parseUnqtList = sepBy1 parseUnqt parseComma
parseList = quotedParse parseUnqtList
`onFail`
fmap return parse
parseArgs :: Parse [Text]
parseArgs = bracketSep (character '(')
parseComma
(character ')')
parseStyleName
data StyleName = Dashed
| Dotted
| Solid
| Bold
| Invisible
| Filled
| Striped
| Wedged
| Diagonals
| Rounded
| Tapered
| Radial
| DD Text
deriving (Eq, Ord, Show, Read)
instance PrintDot StyleName where
unqtDot Dashed = text "dashed"
unqtDot Dotted = text "dotted"
unqtDot Solid = text "solid"
unqtDot Bold = text "bold"
unqtDot Invisible = text "invis"
unqtDot Filled = text "filled"
unqtDot Striped = text "striped"
unqtDot Wedged = text "wedged"
unqtDot Diagonals = text "diagonals"
unqtDot Rounded = text "rounded"
unqtDot Tapered = text "tapered"
unqtDot Radial = text "radial"
unqtDot (DD nm) = unqtDot nm
toDot (DD nm) = toDot nm
toDot sn = unqtDot sn
instance ParseDot StyleName where
parseUnqt = checkDD <$> parseStyleName
parse = quotedParse parseUnqt
`onFail`
fmap checkDD quotelessString
checkDD :: Text -> StyleName
checkDD str = case T.toLower str of
"dashed" -> Dashed
"dotted" -> Dotted
"solid" -> Solid
"bold" -> Bold
"invis" -> Invisible
"filled" -> Filled
"striped" -> Striped
"wedged" -> Wedged
"diagonals" -> Diagonals
"rounded" -> Rounded
"tapered" -> Tapered
"radial" -> Radial
_ -> DD str
parseStyleName :: Parse Text
parseStyleName = liftA2 T.cons (orEscaped . noneOf $ ' ' : disallowedChars)
(parseEscaped True [] disallowedChars)
where
disallowedChars = [quoteChar, '(', ')', ',']
orSlash p = stringRep '\\' "\\\\" `onFail` p
orEscaped = orQuote . orSlash
data ViewPort = VP { wVal :: Double
, hVal :: Double
, zVal :: Double
, focus :: Maybe FocusType
}
deriving (Eq, Ord, Show, Read)
instance PrintDot ViewPort where
unqtDot vp = maybe vs ((<>) (vs <> comma) . unqtDot)
$ focus vp
where
vs = hcat . punctuate comma
$ mapM (unqtDot . ($vp)) [wVal, hVal, zVal]
toDot = dquotes . unqtDot
instance ParseDot ViewPort where
parseUnqt = VP <$> parseUnqt
<* parseComma
<*> parseUnqt
<* parseComma
<*> parseUnqt
<*> optional (parseComma *> parseUnqt)
parse = quotedParse parseUnqt
data FocusType = XY Point
| NodeFocus Text
deriving (Eq, Ord, Show, Read)
instance PrintDot FocusType where
unqtDot (XY p) = unqtDot p
unqtDot (NodeFocus nm) = unqtDot nm
toDot (XY p) = toDot p
toDot (NodeFocus nm) = toDot nm
instance ParseDot FocusType where
parseUnqt = fmap XY parseUnqt
`onFail`
fmap NodeFocus parseUnqt
parse = fmap XY parse
`onFail`
fmap NodeFocus parse
data VerticalPlacement = VTop
| VCenter
| VBottom
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot VerticalPlacement where
unqtDot VTop = char 't'
unqtDot VCenter = char 'c'
unqtDot VBottom = char 'b'
instance ParseDot VerticalPlacement where
parseUnqt = oneOf [ stringRep VTop "t"
, stringRep VCenter "c"
, stringRep VBottom "b"
]
newtype Paths = Paths { paths :: [FilePath] }
deriving (Eq, Ord, Show, Read)
instance PrintDot Paths where
unqtDot = unqtDot . intercalate [searchPathSeparator] . paths
toDot (Paths [p]) = toDot p
toDot ps = dquotes $ unqtDot ps
instance ParseDot Paths where
parseUnqt = Paths . splitSearchPath <$> parseUnqt
parse = quotedParse parseUnqt
`onFail`
fmap (Paths . (:[]) . T.unpack) quotelessString
data ScaleType = UniformScale
| NoScale
| FillWidth
| FillHeight
| FillBoth
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot ScaleType where
unqtDot UniformScale = unqtDot True
unqtDot NoScale = unqtDot False
unqtDot FillWidth = text "width"
unqtDot FillHeight = text "height"
unqtDot FillBoth = text "both"
instance ParseDot ScaleType where
parseUnqt = oneOf [ stringRep UniformScale "true"
, stringRep NoScale "false"
, stringRep FillWidth "width"
, stringRep FillHeight "height"
, stringRep FillBoth "both"
]
data Justification = JLeft
| JRight
| JCenter
deriving (Eq, Ord, Bounded, Enum, Show, Read)
instance PrintDot Justification where
unqtDot JLeft = char 'l'
unqtDot JRight = char 'r'
unqtDot JCenter = char 'c'
instance ParseDot Justification where
parseUnqt = oneOf [ stringRep JLeft "l"
, stringRep JRight "r"
, stringRep JCenter "c"
]
data Ratios = AspectRatio Double
| FillRatio
| CompressRatio
| ExpandRatio
| AutoRatio
deriving (Eq, Ord, Show, Read)
instance PrintDot Ratios where
unqtDot (AspectRatio r) = unqtDot r
unqtDot FillRatio = text "fill"
unqtDot CompressRatio = text "compress"
unqtDot ExpandRatio = text "expand"
unqtDot AutoRatio = text "auto"
instance ParseDot Ratios where
parseUnqt = oneOf [ AspectRatio <$> parseUnqt
, stringRep FillRatio "fill"
, stringRep CompressRatio "compress"
, stringRep ExpandRatio "expand"
, stringRep AutoRatio "auto"
]